LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zchkaa.f
Go to the documentation of this file.
1 *> \brief \b ZCHKAA
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * PROGRAM ZCHKAA
12 *
13 *
14 *> \par Purpose:
15 * =============
16 *>
17 *> \verbatim
18 *>
19 *> ZCHKAA is the main test program for the COMPLEX*16 linear equation
20 *> routines.
21 *>
22 *> The program must be driven by a short data file. The first 15 records
23 *> (not including the first comment line) specify problem dimensions
24 *> and program options using list-directed input. The remaining lines
25 *> specify the LAPACK test paths and the number of matrix types to use
26 *> in testing. An annotated example of a data file can be obtained by
27 *> deleting the first 3 characters from the following 42 lines:
28 *> Data file for testing COMPLEX*16 LAPACK linear equation routines
29 *> 7 Number of values of M
30 *> 0 1 2 3 5 10 16 Values of M (row dimension)
31 *> 7 Number of values of N
32 *> 0 1 2 3 5 10 16 Values of N (column dimension)
33 *> 1 Number of values of NRHS
34 *> 2 Values of NRHS (number of right hand sides)
35 *> 5 Number of values of NB
36 *> 1 3 3 3 20 Values of NB (the blocksize)
37 *> 1 0 5 9 1 Values of NX (crossover point)
38 *> 3 Number of values of RANK
39 *> 30 50 90 Values of rank (as a % of N)
40 *> 30.0 Threshold value of test ratio
41 *> T Put T to test the LAPACK routines
42 *> T Put T to test the driver routines
43 *> T Put T to test the error exits
44 *> ZGE 11 List types on next line if 0 < NTYPES < 11
45 *> ZGB 8 List types on next line if 0 < NTYPES < 8
46 *> ZGT 12 List types on next line if 0 < NTYPES < 12
47 *> ZPO 9 List types on next line if 0 < NTYPES < 9
48 *> ZPS 9 List types on next line if 0 < NTYPES < 9
49 *> ZPP 9 List types on next line if 0 < NTYPES < 9
50 *> ZPB 8 List types on next line if 0 < NTYPES < 8
51 *> ZPT 12 List types on next line if 0 < NTYPES < 12
52 *> ZHE 10 List types on next line if 0 < NTYPES < 10
53 *> ZHR 10 List types on next line if 0 < NTYPES < 10
54 *> ZHP 10 List types on next line if 0 < NTYPES < 10
55 *> ZSY 11 List types on next line if 0 < NTYPES < 11
56 *> ZSR 11 List types on next line if 0 < NTYPES < 11
57 *> ZSP 11 List types on next line if 0 < NTYPES < 11
58 *> ZTR 18 List types on next line if 0 < NTYPES < 18
59 *> ZTP 18 List types on next line if 0 < NTYPES < 18
60 *> ZTB 17 List types on next line if 0 < NTYPES < 17
61 *> ZQR 8 List types on next line if 0 < NTYPES < 8
62 *> ZRQ 8 List types on next line if 0 < NTYPES < 8
63 *> ZLQ 8 List types on next line if 0 < NTYPES < 8
64 *> ZQL 8 List types on next line if 0 < NTYPES < 8
65 *> ZQP 6 List types on next line if 0 < NTYPES < 6
66 *> ZTZ 3 List types on next line if 0 < NTYPES < 3
67 *> ZLS 6 List types on next line if 0 < NTYPES < 6
68 *> ZEQ
69 *> ZQT
70 *> ZQX
71 *> \endverbatim
72 *
73 * Parameters:
74 * ==========
75 *
76 *> \verbatim
77 *> NMAX INTEGER
78 *> The maximum allowable value for M and N.
79 *>
80 *> MAXIN INTEGER
81 *> The number of different values that can be used for each of
82 *> M, N, NRHS, NB, NX and RANK
83 *>
84 *> MAXRHS INTEGER
85 *> The maximum number of right hand sides
86 *>
87 *> MATMAX INTEGER
88 *> The maximum number of matrix types to use for testing
89 *>
90 *> NIN INTEGER
91 *> The unit number for input
92 *>
93 *> NOUT INTEGER
94 *> The unit number for output
95 *> \endverbatim
96 *
97 * Authors:
98 * ========
99 *
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
103 *> \author NAG Ltd.
104 *
105 *> \date November 2015
106 *
107 *> \ingroup complex16_lin
108 *
109 * =====================================================================
110  PROGRAM zchkaa
111 *
112 * -- LAPACK test routine (version 3.6.0) --
113 * -- LAPACK is a software package provided by Univ. of Tennessee, --
114 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115 * November 2015
116 *
117 * =====================================================================
118 *
119 * .. Parameters ..
120  INTEGER NMAX
121  parameter ( nmax = 132 )
122  INTEGER MAXIN
123  parameter ( maxin = 12 )
124  INTEGER MAXRHS
125  parameter ( maxrhs = 16 )
126  INTEGER MATMAX
127  parameter ( matmax = 30 )
128  INTEGER NIN, NOUT
129  parameter ( nin = 5, nout = 6 )
130  INTEGER KDMAX
131  parameter ( kdmax = nmax+( nmax+1 ) / 4 )
132 * ..
133 * .. Local Scalars ..
134  LOGICAL FATAL, TSTCHK, TSTDRV, TSTERR
135  CHARACTER C1
136  CHARACTER*2 C2
137  CHARACTER*3 PATH
138  CHARACTER*10 INTSTR
139  CHARACTER*72 ALINE
140  INTEGER I, IC, J, K, LA, LAFAC, LDA, NB, NM, NMATS, NN,
141  $ nnb, nnb2, nns, nrhs, ntypes, nrank,
142  $ vers_major, vers_minor, vers_patch
143  DOUBLE PRECISION EPS, S1, S2, THREQ, THRESH
144 * ..
145 * .. Local Arrays ..
146  LOGICAL DOTYPE( matmax )
147  INTEGER IWORK( 25*nmax ), MVAL( maxin ),
148  $ nbval( maxin ), nbval2( maxin ),
149  $ nsval( maxin ), nval( maxin ), nxval( maxin ),
150  $ rankval( maxin ), piv( nmax )
151  DOUBLE PRECISION RWORK( 150*nmax+2*maxrhs ), S( 2*nmax )
152  COMPLEX*16 A( ( kdmax+1 )*nmax, 7 ), B( nmax*maxrhs, 4 ),
153  $ work( nmax, nmax+maxrhs+10 )
154 * ..
155 * .. External Functions ..
156  LOGICAL LSAME, LSAMEN
157  DOUBLE PRECISION DLAMCH, DSECND
158  EXTERNAL lsame, lsamen, dlamch, dsecnd
159 * ..
160 * .. External Subroutines ..
161  EXTERNAL alareq, zchkeq, zchkgb, zchkge, zchkgt, zchkhe,
169 * ..
170 * .. Scalars in Common ..
171  LOGICAL LERR, OK
172  CHARACTER*32 SRNAMT
173  INTEGER INFOT, NUNIT
174 * ..
175 * .. Arrays in Common ..
176  INTEGER IPARMS( 100 )
177 * ..
178 * .. Common blocks ..
179  COMMON / infoc / infot, nunit, ok, lerr
180  COMMON / srnamc / srnamt
181  COMMON / claenv / iparms
182 * ..
183 * .. Data statements ..
184  DATA threq / 2.0d0 / , intstr / '0123456789' /
185 * ..
186 * .. Executable Statements ..
187 *
188  s1 = dsecnd( )
189  lda = nmax
190  fatal = .false.
191 *
192 * Read a dummy line.
193 *
194  READ( nin, fmt = * )
195 *
196 * Report values of parameters.
197 *
198  CALL ilaver( vers_major, vers_minor, vers_patch )
199  WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
200 *
201 * Read the values of M
202 *
203  READ( nin, fmt = * )nm
204  IF( nm.LT.1 ) THEN
205  WRITE( nout, fmt = 9996 )' NM ', nm, 1
206  nm = 0
207  fatal = .true.
208  ELSE IF( nm.GT.maxin ) THEN
209  WRITE( nout, fmt = 9995 )' NM ', nm, maxin
210  nm = 0
211  fatal = .true.
212  END IF
213  READ( nin, fmt = * )( mval( i ), i = 1, nm )
214  DO 10 i = 1, nm
215  IF( mval( i ).LT.0 ) THEN
216  WRITE( nout, fmt = 9996 )' M ', mval( i ), 0
217  fatal = .true.
218  ELSE IF( mval( i ).GT.nmax ) THEN
219  WRITE( nout, fmt = 9995 )' M ', mval( i ), nmax
220  fatal = .true.
221  END IF
222  10 CONTINUE
223  IF( nm.GT.0 )
224  $ WRITE( nout, fmt = 9993 )'M ', ( mval( i ), i = 1, nm )
225 *
226 * Read the values of N
227 *
228  READ( nin, fmt = * )nn
229  IF( nn.LT.1 ) THEN
230  WRITE( nout, fmt = 9996 )' NN ', nn, 1
231  nn = 0
232  fatal = .true.
233  ELSE IF( nn.GT.maxin ) THEN
234  WRITE( nout, fmt = 9995 )' NN ', nn, maxin
235  nn = 0
236  fatal = .true.
237  END IF
238  READ( nin, fmt = * )( nval( i ), i = 1, nn )
239  DO 20 i = 1, nn
240  IF( nval( i ).LT.0 ) THEN
241  WRITE( nout, fmt = 9996 )' N ', nval( i ), 0
242  fatal = .true.
243  ELSE IF( nval( i ).GT.nmax ) THEN
244  WRITE( nout, fmt = 9995 )' N ', nval( i ), nmax
245  fatal = .true.
246  END IF
247  20 CONTINUE
248  IF( nn.GT.0 )
249  $ WRITE( nout, fmt = 9993 )'N ', ( nval( i ), i = 1, nn )
250 *
251 * Read the values of NRHS
252 *
253  READ( nin, fmt = * )nns
254  IF( nns.LT.1 ) THEN
255  WRITE( nout, fmt = 9996 )' NNS', nns, 1
256  nns = 0
257  fatal = .true.
258  ELSE IF( nns.GT.maxin ) THEN
259  WRITE( nout, fmt = 9995 )' NNS', nns, maxin
260  nns = 0
261  fatal = .true.
262  END IF
263  READ( nin, fmt = * )( nsval( i ), i = 1, nns )
264  DO 30 i = 1, nns
265  IF( nsval( i ).LT.0 ) THEN
266  WRITE( nout, fmt = 9996 )'NRHS', nsval( i ), 0
267  fatal = .true.
268  ELSE IF( nsval( i ).GT.maxrhs ) THEN
269  WRITE( nout, fmt = 9995 )'NRHS', nsval( i ), maxrhs
270  fatal = .true.
271  END IF
272  30 CONTINUE
273  IF( nns.GT.0 )
274  $ WRITE( nout, fmt = 9993 )'NRHS', ( nsval( i ), i = 1, nns )
275 *
276 * Read the values of NB
277 *
278  READ( nin, fmt = * )nnb
279  IF( nnb.LT.1 ) THEN
280  WRITE( nout, fmt = 9996 )'NNB ', nnb, 1
281  nnb = 0
282  fatal = .true.
283  ELSE IF( nnb.GT.maxin ) THEN
284  WRITE( nout, fmt = 9995 )'NNB ', nnb, maxin
285  nnb = 0
286  fatal = .true.
287  END IF
288  READ( nin, fmt = * )( nbval( i ), i = 1, nnb )
289  DO 40 i = 1, nnb
290  IF( nbval( i ).LT.0 ) THEN
291  WRITE( nout, fmt = 9996 )' NB ', nbval( i ), 0
292  fatal = .true.
293  END IF
294  40 CONTINUE
295  IF( nnb.GT.0 )
296  $ WRITE( nout, fmt = 9993 )'NB ', ( nbval( i ), i = 1, nnb )
297 *
298 * Set NBVAL2 to be the set of unique values of NB
299 *
300  nnb2 = 0
301  DO 60 i = 1, nnb
302  nb = nbval( i )
303  DO 50 j = 1, nnb2
304  IF( nb.EQ.nbval2( j ) )
305  $ GO TO 60
306  50 CONTINUE
307  nnb2 = nnb2 + 1
308  nbval2( nnb2 ) = nb
309  60 CONTINUE
310 *
311 * Read the values of NX
312 *
313  READ( nin, fmt = * )( nxval( i ), i = 1, nnb )
314  DO 70 i = 1, nnb
315  IF( nxval( i ).LT.0 ) THEN
316  WRITE( nout, fmt = 9996 )' NX ', nxval( i ), 0
317  fatal = .true.
318  END IF
319  70 CONTINUE
320  IF( nnb.GT.0 )
321  $ WRITE( nout, fmt = 9993 )'NX ', ( nxval( i ), i = 1, nnb )
322 *
323 * Read the values of RANKVAL
324 *
325  READ( nin, fmt = * )nrank
326  IF( nn.LT.1 ) THEN
327  WRITE( nout, fmt = 9996 )' NRANK ', nrank, 1
328  nrank = 0
329  fatal = .true.
330  ELSE IF( nn.GT.maxin ) THEN
331  WRITE( nout, fmt = 9995 )' NRANK ', nrank, maxin
332  nrank = 0
333  fatal = .true.
334  END IF
335  READ( nin, fmt = * )( rankval( i ), i = 1, nrank )
336  DO i = 1, nrank
337  IF( rankval( i ).LT.0 ) THEN
338  WRITE( nout, fmt = 9996 )' RANK ', rankval( i ), 0
339  fatal = .true.
340  ELSE IF( rankval( i ).GT.100 ) THEN
341  WRITE( nout, fmt = 9995 )' RANK ', rankval( i ), 100
342  fatal = .true.
343  END IF
344  END DO
345  IF( nrank.GT.0 )
346  $ WRITE( nout, fmt = 9993 )'RANK % OF N',
347  $ ( rankval( i ), i = 1, nrank )
348 *
349 * Read the threshold value for the test ratios.
350 *
351  READ( nin, fmt = * )thresh
352  WRITE( nout, fmt = 9992 )thresh
353 *
354 * Read the flag that indicates whether to test the LAPACK routines.
355 *
356  READ( nin, fmt = * )tstchk
357 *
358 * Read the flag that indicates whether to test the driver routines.
359 *
360  READ( nin, fmt = * )tstdrv
361 *
362 * Read the flag that indicates whether to test the error exits.
363 *
364  READ( nin, fmt = * )tsterr
365 *
366  IF( fatal ) THEN
367  WRITE( nout, fmt = 9999 )
368  stop
369  END IF
370 *
371 * Calculate and print the machine dependent constants.
372 *
373  eps = dlamch( 'Underflow threshold' )
374  WRITE( nout, fmt = 9991 )'underflow', eps
375  eps = dlamch( 'Overflow threshold' )
376  WRITE( nout, fmt = 9991 )'overflow ', eps
377  eps = dlamch( 'Epsilon' )
378  WRITE( nout, fmt = 9991 )'precision', eps
379  WRITE( nout, fmt = * )
380  nrhs = nsval( 1 )
381 *
382  80 CONTINUE
383 *
384 * Read a test path and the number of matrix types to use.
385 *
386  READ( nin, fmt = '(A72)', end = 140 )aline
387  path = aline( 1: 3 )
388  nmats = matmax
389  i = 3
390  90 CONTINUE
391  i = i + 1
392  IF( i.GT.72 )
393  $ GO TO 130
394  IF( aline( i: i ).EQ.' ' )
395  $ GO TO 90
396  nmats = 0
397  100 CONTINUE
398  c1 = aline( i: i )
399  DO 110 k = 1, 10
400  IF( c1.EQ.intstr( k: k ) ) THEN
401  ic = k - 1
402  GO TO 120
403  END IF
404  110 CONTINUE
405  GO TO 130
406  120 CONTINUE
407  nmats = nmats*10 + ic
408  i = i + 1
409  IF( i.GT.72 )
410  $ GO TO 130
411  GO TO 100
412  130 CONTINUE
413  c1 = path( 1: 1 )
414  c2 = path( 2: 3 )
415 *
416 * Check first character for correct precision.
417 *
418  IF( .NOT.lsame( c1, 'Zomplex precision' ) ) THEN
419  WRITE( nout, fmt = 9990 )path
420 *
421  ELSE IF( nmats.LE.0 ) THEN
422 *
423 * Check for a positive number of tests requested.
424 *
425  WRITE( nout, fmt = 9989 )path
426 *
427  ELSE IF( lsamen( 2, c2, 'GE' ) ) THEN
428 *
429 * GE: general matrices
430 *
431  ntypes = 11
432  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
433 *
434  IF( tstchk ) THEN
435  CALL zchkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
436  $ nsval, thresh, tsterr, lda, a( 1, 1 ),
437  $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
438  $ b( 1, 3 ), work, rwork, iwork, nout )
439  ELSE
440  WRITE( nout, fmt = 9989 )path
441  END IF
442 *
443  IF( tstdrv ) THEN
444  CALL zdrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
445  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
446  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
447  $ rwork, iwork, nout )
448  ELSE
449  WRITE( nout, fmt = 9988 )path
450  END IF
451 *
452  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
453 *
454 * GB: general banded matrices
455 *
456  la = ( 2*kdmax+1 )*nmax
457  lafac = ( 3*kdmax+1 )*nmax
458  ntypes = 8
459  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
460 *
461  IF( tstchk ) THEN
462  CALL zchkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
463  $ nsval, thresh, tsterr, a( 1, 1 ), la,
464  $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
465  $ b( 1, 3 ), work, rwork, iwork, nout )
466  ELSE
467  WRITE( nout, fmt = 9989 )path
468  END IF
469 *
470  IF( tstdrv ) THEN
471  CALL zdrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
472  $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
473  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
474  $ work, rwork, iwork, nout )
475  ELSE
476  WRITE( nout, fmt = 9988 )path
477  END IF
478 *
479  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
480 *
481 * GT: general tridiagonal matrices
482 *
483  ntypes = 12
484  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
485 *
486  IF( tstchk ) THEN
487  CALL zchkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
488  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
489  $ b( 1, 3 ), work, rwork, iwork, nout )
490  ELSE
491  WRITE( nout, fmt = 9989 )path
492  END IF
493 *
494  IF( tstdrv ) THEN
495  CALL zdrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
496  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
497  $ b( 1, 3 ), work, rwork, iwork, nout )
498  ELSE
499  WRITE( nout, fmt = 9988 )path
500  END IF
501 *
502  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
503 *
504 * PO: positive definite matrices
505 *
506  ntypes = 9
507  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
508 *
509  IF( tstchk ) THEN
510  CALL zchkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
511  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
512  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
513  $ work, rwork, nout )
514  ELSE
515  WRITE( nout, fmt = 9989 )path
516  END IF
517 *
518  IF( tstdrv ) THEN
519  CALL zdrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
520  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
521  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
522  $ rwork, nout )
523  ELSE
524  WRITE( nout, fmt = 9988 )path
525  END IF
526 *
527  ELSE IF( lsamen( 2, c2, 'PS' ) ) THEN
528 *
529 * PS: positive semi-definite matrices
530 *
531  ntypes = 9
532 *
533  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
534 *
535  IF( tstchk ) THEN
536  CALL zchkps( dotype, nn, nval, nnb2, nbval2, nrank,
537  $ rankval, thresh, tsterr, lda, a( 1, 1 ),
538  $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
539  $ nout )
540  ELSE
541  WRITE( nout, fmt = 9989 )path
542  END IF
543 *
544  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
545 *
546 * PP: positive definite packed matrices
547 *
548  ntypes = 9
549  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
550 *
551  IF( tstchk ) THEN
552  CALL zchkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
553  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
554  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
555  $ nout )
556  ELSE
557  WRITE( nout, fmt = 9989 )path
558  END IF
559 *
560  IF( tstdrv ) THEN
561  CALL zdrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
562  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
563  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
564  $ rwork, nout )
565  ELSE
566  WRITE( nout, fmt = 9988 )path
567  END IF
568 *
569  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
570 *
571 * PB: positive definite banded matrices
572 *
573  ntypes = 8
574  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
575 *
576  IF( tstchk ) THEN
577  CALL zchkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
578  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
579  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
580  $ work, rwork, nout )
581  ELSE
582  WRITE( nout, fmt = 9989 )path
583  END IF
584 *
585  IF( tstdrv ) THEN
586  CALL zdrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
587  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
588  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
589  $ rwork, nout )
590  ELSE
591  WRITE( nout, fmt = 9988 )path
592  END IF
593 *
594  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
595 *
596 * PT: positive definite tridiagonal matrices
597 *
598  ntypes = 12
599  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
600 *
601  IF( tstchk ) THEN
602  CALL zchkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
603  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
604  $ b( 1, 3 ), work, rwork, nout )
605  ELSE
606  WRITE( nout, fmt = 9989 )path
607  END IF
608 *
609  IF( tstdrv ) THEN
610  CALL zdrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
611  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
612  $ b( 1, 3 ), work, rwork, nout )
613  ELSE
614  WRITE( nout, fmt = 9988 )path
615  END IF
616 *
617  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
618 *
619 * HE: Hermitian indefinite matrices
620 *
621  ntypes = 10
622  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
623 *
624  IF( tstchk ) THEN
625  CALL zchkhe( dotype, nn, nval, nnb2, nbval2, nns, nsval,
626  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
627  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
628  $ work, rwork, iwork, nout )
629  ELSE
630  WRITE( nout, fmt = 9989 )path
631  END IF
632 *
633  IF( tstdrv ) THEN
634  CALL zdrvhe( dotype, nn, nval, nrhs, thresh, tsterr, lda,
635  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
636  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
637  $ nout )
638  ELSE
639  WRITE( nout, fmt = 9988 )path
640  END IF
641 *
642  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
643 *
644 * HR: Hermitian indefinite matrices,
645 * with "rook" (bounded Bunch-Kaufman) pivoting algorithm
646 *
647  ntypes = 10
648  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
649 *
650  IF( tstchk ) THEN
651  CALL zchkhe_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
652  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
653  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
654  $ work, rwork, iwork, nout )
655  ELSE
656  WRITE( nout, fmt = 9989 )path
657  END IF
658 *
659  IF( tstdrv ) THEN
660  CALL zdrvhe_rook( dotype, nn, nval, nrhs, thresh, tsterr,
661  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
662  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
663  $ rwork, iwork, nout )
664  ELSE
665  WRITE( nout, fmt = 9988 )path
666  END IF
667 *
668  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
669 *
670 * HP: Hermitian indefinite packed matrices
671 *
672  ntypes = 10
673  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
674 *
675  IF( tstchk ) THEN
676  CALL zchkhp( dotype, nn, nval, nns, nsval, thresh, tsterr,
677  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
678  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
679  $ iwork, nout )
680  ELSE
681  WRITE( nout, fmt = 9989 )path
682  END IF
683 *
684  IF( tstdrv ) THEN
685  CALL zdrvhp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
686  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
687  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
688  $ nout )
689  ELSE
690  WRITE( nout, fmt = 9988 )path
691  END IF
692 *
693  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
694 *
695 * SY: symmetric indefinite matrices,
696 * with partial (Bunch-Kaufman) pivoting algorithm
697 *
698  ntypes = 11
699  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
700 *
701  IF( tstchk ) THEN
702  CALL zchksy( dotype, nn, nval, nnb2, nbval2, nns, nsval,
703  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
704  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
705  $ work, rwork, iwork, nout )
706  ELSE
707  WRITE( nout, fmt = 9989 )path
708  END IF
709 *
710  IF( tstdrv ) THEN
711  CALL zdrvsy( dotype, nn, nval, nrhs, thresh, tsterr, lda,
712  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
713  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
714  $ nout )
715  ELSE
716  WRITE( nout, fmt = 9988 )path
717  END IF
718 *
719  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
720 *
721 * SR: symmetric indefinite matrices,
722 * with "rook" (bounded Bunch-Kaufman) pivoting algorithm
723 *
724  ntypes = 11
725  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
726 *
727  IF( tstchk ) THEN
728  CALL zchksy_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
729  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
730  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
731  $ work, rwork, iwork, nout )
732  ELSE
733  WRITE( nout, fmt = 9989 )path
734  END IF
735 *
736  IF( tstdrv ) THEN
737  CALL zdrvsy_rook( dotype, nn, nval, nrhs, thresh, tsterr,
738  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
739  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
740  $ rwork, iwork, nout )
741  ELSE
742  WRITE( nout, fmt = 9988 )path
743  END IF
744 *
745  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
746 *
747 * SP: symmetric indefinite packed matrices,
748 * with partial (Bunch-Kaufman) pivoting algorithm
749 *
750  ntypes = 11
751  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
752 *
753  IF( tstchk ) THEN
754  CALL zchksp( dotype, nn, nval, nns, nsval, thresh, tsterr,
755  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
756  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
757  $ iwork, nout )
758  ELSE
759  WRITE( nout, fmt = 9989 )path
760  END IF
761 *
762  IF( tstdrv ) THEN
763  CALL zdrvsp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
764  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
765  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
766  $ nout )
767  ELSE
768  WRITE( nout, fmt = 9988 )path
769  END IF
770 *
771  ELSE IF( lsamen( 2, c2, 'TR' ) ) THEN
772 *
773 * TR: triangular matrices
774 *
775  ntypes = 18
776  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
777 *
778  IF( tstchk ) THEN
779  CALL zchktr( dotype, nn, nval, nnb2, nbval2, nns, nsval,
780  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
781  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
782  $ nout )
783  ELSE
784  WRITE( nout, fmt = 9989 )path
785  END IF
786 *
787  ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
788 *
789 * TP: triangular packed matrices
790 *
791  ntypes = 18
792  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
793 *
794  IF( tstchk ) THEN
795  CALL zchktp( dotype, nn, nval, nns, nsval, thresh, tsterr,
796  $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
797  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
798  ELSE
799  WRITE( nout, fmt = 9989 )path
800  END IF
801 *
802  ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
803 *
804 * TB: triangular banded matrices
805 *
806  ntypes = 17
807  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
808 *
809  IF( tstchk ) THEN
810  CALL zchktb( dotype, nn, nval, nns, nsval, thresh, tsterr,
811  $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
812  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
813  ELSE
814  WRITE( nout, fmt = 9989 )path
815  END IF
816 *
817  ELSE IF( lsamen( 2, c2, 'QR' ) ) THEN
818 *
819 * QR: QR factorization
820 *
821  ntypes = 8
822  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
823 *
824  IF( tstchk ) THEN
825  CALL zchkqr( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
826  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
827  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
828  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
829  $ work, rwork, iwork, nout )
830  ELSE
831  WRITE( nout, fmt = 9989 )path
832  END IF
833 *
834  ELSE IF( lsamen( 2, c2, 'LQ' ) ) THEN
835 *
836 * LQ: LQ factorization
837 *
838  ntypes = 8
839  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
840 *
841  IF( tstchk ) THEN
842  CALL zchklq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
843  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
844  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
845  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
846  $ work, rwork, nout )
847  ELSE
848  WRITE( nout, fmt = 9989 )path
849  END IF
850 *
851  ELSE IF( lsamen( 2, c2, 'QL' ) ) THEN
852 *
853 * QL: QL factorization
854 *
855  ntypes = 8
856  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
857 *
858  IF( tstchk ) THEN
859  CALL zchkql( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
860  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
861  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
862  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
863  $ work, rwork, nout )
864  ELSE
865  WRITE( nout, fmt = 9989 )path
866  END IF
867 *
868  ELSE IF( lsamen( 2, c2, 'RQ' ) ) THEN
869 *
870 * RQ: RQ factorization
871 *
872  ntypes = 8
873  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
874 *
875  IF( tstchk ) THEN
876  CALL zchkrq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
877  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
878  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
879  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
880  $ work, rwork, iwork, nout )
881  ELSE
882  WRITE( nout, fmt = 9989 )path
883  END IF
884 *
885  ELSE IF( lsamen( 2, c2, 'EQ' ) ) THEN
886 *
887 * EQ: Equilibration routines for general and positive definite
888 * matrices (THREQ should be between 2 and 10)
889 *
890  IF( tstchk ) THEN
891  CALL zchkeq( threq, nout )
892  ELSE
893  WRITE( nout, fmt = 9989 )path
894  END IF
895 *
896  ELSE IF( lsamen( 2, c2, 'TZ' ) ) THEN
897 *
898 * TZ: Trapezoidal matrix
899 *
900  ntypes = 3
901  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
902 *
903  IF( tstchk ) THEN
904  CALL zchktz( dotype, nm, mval, nn, nval, thresh, tsterr,
905  $ a( 1, 1 ), a( 1, 2 ), s( 1 ),
906  $ b( 1, 1 ), work, rwork, nout )
907  ELSE
908  WRITE( nout, fmt = 9989 )path
909  END IF
910 *
911  ELSE IF( lsamen( 2, c2, 'QP' ) ) THEN
912 *
913 * QP: QR factorization with pivoting
914 *
915  ntypes = 6
916  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
917 *
918  IF( tstchk ) THEN
919  CALL zchkq3( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
920  $ thresh, a( 1, 1 ), a( 1, 2 ), s( 1 ),
921  $ b( 1, 1 ), work, rwork, iwork,
922  $ nout )
923  ELSE
924  WRITE( nout, fmt = 9989 )path
925  END IF
926 *
927  ELSE IF( lsamen( 2, c2, 'LS' ) ) THEN
928 *
929 * LS: Least squares drivers
930 *
931  ntypes = 6
932  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
933 *
934  IF( tstdrv ) THEN
935  CALL zdrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
936  $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
937  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
938  $ s( 1 ), s( nmax+1 ), work, rwork, iwork,
939  $ nout )
940  ELSE
941  WRITE( nout, fmt = 9989 )path
942  END IF
943 *
944 *
945  ELSE IF( lsamen( 2, c2, 'QT' ) ) THEN
946 *
947 * QT: QRT routines for general matrices
948 *
949  IF( tstchk ) THEN
950  CALL zchkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
951  $ nbval, nout )
952  ELSE
953  WRITE( nout, fmt = 9989 )path
954  END IF
955 *
956  ELSE IF( lsamen( 2, c2, 'QX' ) ) THEN
957 *
958 * QX: QRT routines for triangular-pentagonal matrices
959 *
960  IF( tstchk ) THEN
961  CALL zchkqrtp( thresh, tsterr, nm, mval, nn, nval, nnb,
962  $ nbval, nout )
963  ELSE
964  WRITE( nout, fmt = 9989 )path
965  END IF
966 *
967  ELSE
968 *
969  WRITE( nout, fmt = 9990 )path
970  END IF
971 *
972 * Go back to get another input line.
973 *
974  GO TO 80
975 *
976 * Branch to this line when the last record is read.
977 *
978  140 CONTINUE
979  CLOSE ( nin )
980  s2 = dsecnd( )
981  WRITE( nout, fmt = 9998 )
982  WRITE( nout, fmt = 9997 )s2 - s1
983 *
984  9999 FORMAT( / ' Execution not attempted due to input errors' )
985  9998 FORMAT( / ' End of tests' )
986  9997 FORMAT( ' Total time used = ', f12.2, ' seconds', / )
987  9996 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be >=',
988  $ i6 )
989  9995 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be <=',
990  $ i6 )
991  9994 FORMAT( ' Tests of the COMPLEX*16 LAPACK routines ',
992  $ / ' LAPACK VERSION ', i1, '.', i1, '.', i1,
993  $ / / ' The following parameter values will be used:' )
994  9993 FORMAT( 4x, a4, ': ', 10i6, / 11x, 10i6 )
995  9992 FORMAT( / ' Routines pass computational tests if test ratio is ',
996  $ 'less than', f8.2, / )
997  9991 FORMAT( ' Relative machine ', a, ' is taken to be', d16.6 )
998  9990 FORMAT( / 1x, a3, ': Unrecognized path name' )
999  9989 FORMAT( / 1x, a3, ' routines were not tested' )
1000  9988 FORMAT( / 1x, a3, ' driver routines were not tested' )
1001 *
1002 * End of ZCHKAA
1003 *
1004  END
subroutine zchkeq(THRESH, NOUT)
ZCHKEQ
Definition: zchkeq.f:56
subroutine zchkhe_rook(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHE_ROOK
Definition: zchkhe_rook.f:174
subroutine zchkrq(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AR, AC, B, X, XACT, TAU, WORK, RWORK, IWORK, NOUT)
ZCHKRQ
Definition: zchkrq.f:203
subroutine zchkpt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPT
Definition: zchkpt.f:149
subroutine zchkps(DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL, THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK, RWORK, NOUT)
ZCHKPS
Definition: zchkps.f:156
subroutine zchktz(DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A, COPYA, S, TAU, WORK, RWORK, NOUT)
ZCHKTZ
Definition: zchktz.f:139
subroutine zchkpo(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPO
Definition: zchkpo.f:170
subroutine zdrvge(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, IWORK, NOUT)
ZDRVGE
Definition: zdrvge.f:166
subroutine zchksy_rook(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSY_ROOK
Definition: zchksy_rook.f:174
subroutine zchkgt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKGT
Definition: zchkgt.f:149
subroutine zchkq3(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, THRESH, A, COPYA, S, TAU, WORK, RWORK, IWORK, NOUT)
ZCHKQ3
Definition: zchkq3.f:160
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine zchkhe(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHE
Definition: zchkhe.f:173
subroutine zchkql(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC, B, X, XACT, TAU, WORK, RWORK, NOUT)
ZCHKQL
Definition: zchkql.f:198
subroutine zchkqr(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AR, AC, B, X, XACT, TAU, WORK, RWORK, IWORK, NOUT)
ZCHKQR
Definition: zchkqr.f:203
subroutine zdrvhe_rook(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE_ROOK
Definition: zdrvhe_rook.f:155
subroutine zchkpb(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPB
Definition: zchkpb.f:170
subroutine zchkpp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPP
Definition: zchkpp.f:161
subroutine zchkge(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKGE
Definition: zchkge.f:188
subroutine zchktr(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKTR
Definition: zchktr.f:165
subroutine zdrvpt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
ZDRVPT
Definition: zdrvpt.f:142
subroutine zchktp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AP, AINVP, B, X, XACT, WORK, RWORK, NOUT)
ZCHKTP
Definition: zchktp.f:153
subroutine zchksp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSP
Definition: zchksp.f:166
subroutine zdrvls(DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB, NBVAL, NXVAL, THRESH, TSTERR, A, COPYA, B, COPYB, C, S, COPYS, WORK, RWORK, IWORK, NOUT)
ZDRVLS
Definition: zdrvls.f:211
subroutine zdrvgb(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, LA, AFB, LAFB, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, IWORK, NOUT)
ZDRVGB
Definition: zdrvgb.f:174
subroutine zchksy(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSY
Definition: zchksy.f:173
subroutine zchklq(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC, B, X, XACT, TAU, WORK, RWORK, NOUT)
ZCHKLQ
Definition: zchklq.f:198
program zchkaa
ZCHKAA
Definition: zchkaa.f:110
subroutine zdrvsy_rook(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY_ROOK
Definition: zdrvsy_rook.f:155
subroutine zdrvsy(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY
Definition: zdrvsy.f:155
subroutine zchktb(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AB, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKTB
Definition: zchktb.f:151
subroutine zchkqrt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKQRT
Definition: zchkqrt.f:103
subroutine zdrvgt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVGT
Definition: zdrvgt.f:141
subroutine ilaver(VERS_MAJOR, VERS_MINOR, VERS_PATCH)
ILAVER returns the LAPACK version.
Definition: ilaver.f:50
subroutine zdrvhe(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE
Definition: zdrvhe.f:155
subroutine zchkhp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHP
Definition: zchkhp.f:166
subroutine zdrvpp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
ZDRVPP
Definition: zdrvpp.f:161
subroutine zdrvpb(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
ZDRVPB
Definition: zdrvpb.f:161
subroutine zdrvpo(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
ZDRVPO
Definition: zdrvpo.f:161
subroutine zchkgb(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, A, LA, AFAC, LAFAC, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKGB
Definition: zchkgb.f:193
subroutine zchkqrtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKQRTP
Definition: zchkqrtp.f:104
subroutine zdrvsp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSP
Definition: zdrvsp.f:159
subroutine zdrvhp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHP
Definition: zdrvhp.f:159