LAPACK  3.9.0
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 *> ZHK 10 List types on next line if 0 < NTYPES < 10
55 *> ZHA 10 List types on next line if 0 < NTYPES < 10
56 *> ZH2 10 List types on next line if 0 < NTYPES < 10
57 *> ZSA 11 List types on next line if 0 < NTYPES < 10
58 *> ZS2 11 List types on next line if 0 < NTYPES < 10
59 *> ZHP 10 List types on next line if 0 < NTYPES < 10
60 *> ZSY 11 List types on next line if 0 < NTYPES < 11
61 *> ZSR 11 List types on next line if 0 < NTYPES < 11
62 *> ZSK 11 List types on next line if 0 < NTYPES < 11
63 *> ZSP 11 List types on next line if 0 < NTYPES < 11
64 *> ZTR 18 List types on next line if 0 < NTYPES < 18
65 *> ZTP 18 List types on next line if 0 < NTYPES < 18
66 *> ZTB 17 List types on next line if 0 < NTYPES < 17
67 *> ZQR 8 List types on next line if 0 < NTYPES < 8
68 *> ZRQ 8 List types on next line if 0 < NTYPES < 8
69 *> ZLQ 8 List types on next line if 0 < NTYPES < 8
70 *> ZQL 8 List types on next line if 0 < NTYPES < 8
71 *> ZQP 6 List types on next line if 0 < NTYPES < 6
72 *> ZTZ 3 List types on next line if 0 < NTYPES < 3
73 *> ZLS 6 List types on next line if 0 < NTYPES < 6
74 *> ZEQ
75 *> ZQT
76 *> ZQX
77 *> ZTS
78 *> ZHH
79 *> \endverbatim
80 *
81 * Parameters:
82 * ==========
83 *
84 *> \verbatim
85 *> NMAX INTEGER
86 *> The maximum allowable value for M and N.
87 *>
88 *> MAXIN INTEGER
89 *> The number of different values that can be used for each of
90 *> M, N, NRHS, NB, NX and RANK
91 *>
92 *> MAXRHS INTEGER
93 *> The maximum number of right hand sides
94 *>
95 *> MATMAX INTEGER
96 *> The maximum number of matrix types to use for testing
97 *>
98 *> NIN INTEGER
99 *> The unit number for input
100 *>
101 *> NOUT INTEGER
102 *> The unit number for output
103 *> \endverbatim
104 *
105 * Authors:
106 * ========
107 *
108 *> \author Univ. of Tennessee
109 *> \author Univ. of California Berkeley
110 *> \author Univ. of Colorado Denver
111 *> \author NAG Ltd.
112 *
113 *> \date November 2019
114 *
115 *> \ingroup complex16_lin
116 *
117 * =====================================================================
118  PROGRAM zchkaa
119 *
120 * -- LAPACK test routine (version 3.9.0) --
121 * -- LAPACK is a software package provided by Univ. of Tennessee, --
122 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123 * November 2019
124 *
125 * =====================================================================
126 *
127 * .. Parameters ..
128  INTEGER nmax
129  parameter( nmax = 132 )
130  INTEGER maxin
131  parameter( maxin = 12 )
132  INTEGER maxrhs
133  parameter( maxrhs = 16 )
134  INTEGER matmax
135  parameter( matmax = 30 )
136  INTEGER nin, nout
137  parameter( nin = 5, nout = 6 )
138  INTEGER kdmax
139  parameter( kdmax = nmax+( nmax+1 ) / 4 )
140 * ..
141 * .. Local Scalars ..
142  LOGICAL fatal, tstchk, tstdrv, tsterr
143  CHARACTER c1
144  CHARACTER*2 c2
145  CHARACTER*3 path
146  CHARACTER*10 intstr
147  CHARACTER*72 aline
148  INTEGER i, ic, j, k, la, lafac, lda, nb, nm, nmats, nn,
149  $ nnb, nnb2, nns, nrhs, ntypes, nrank,
150  $ vers_major, vers_minor, vers_patch
151  DOUBLE PRECISION eps, s1, s2, threq, thresh
152 * ..
153 * .. Local Arrays ..
154  LOGICAL dotype( matmax )
155  INTEGER iwork( 25*nmax ), mval( maxin ),
156  $ nbval( maxin ), nbval2( maxin ),
157  $ nsval( maxin ), nval( maxin ), nxval( maxin ),
158  $ rankval( maxin ), piv( nmax )
159  DOUBLE PRECISION rwork( 150*nmax+2*maxrhs ), s( 2*nmax )
160  COMPLEX*16 a( ( kdmax+1 )*nmax, 7 ), b( nmax*maxrhs, 4 ),
161  $ e( nmax ), work( nmax, nmax+maxrhs+10 )
162 * ..
163 * .. External Functions ..
164  LOGICAL lsame, lsamen
165  DOUBLE PRECISION dlamch, dsecnd
166  EXTERNAL lsame, lsamen, dlamch, dsecnd
167 * ..
168 * .. External Subroutines ..
169  EXTERNAL alareq, zchkeq, zchkgb, zchkge, zchkgt, zchkhe,
181 * ..
182 * .. Scalars in Common ..
183  LOGICAL lerr, ok
184  CHARACTER*32 srnamt
185  INTEGER infot, nunit
186 * ..
187 * .. Arrays in Common ..
188  INTEGER iparms( 100 )
189 * ..
190 * .. Common blocks ..
191  COMMON / infoc / infot, nunit, ok, lerr
192  COMMON / srnamc / srnamt
193  COMMON / claenv / iparms
194 * ..
195 * .. Data statements ..
196  DATA threq / 2.0d0 / , intstr / '0123456789' /
197 * ..
198 * .. Executable Statements ..
199 *
200  s1 = dsecnd( )
201  lda = nmax
202  fatal = .false.
203 *
204 * Read a dummy line.
205 *
206  READ( nin, fmt = * )
207 *
208 * Report values of parameters.
209 *
210  CALL ilaver( vers_major, vers_minor, vers_patch )
211  WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
212 *
213 * Read the values of M
214 *
215  READ( nin, fmt = * )nm
216  IF( nm.LT.1 ) THEN
217  WRITE( nout, fmt = 9996 )' NM ', nm, 1
218  nm = 0
219  fatal = .true.
220  ELSE IF( nm.GT.maxin ) THEN
221  WRITE( nout, fmt = 9995 )' NM ', nm, maxin
222  nm = 0
223  fatal = .true.
224  END IF
225  READ( nin, fmt = * )( mval( i ), i = 1, nm )
226  DO 10 i = 1, nm
227  IF( mval( i ).LT.0 ) THEN
228  WRITE( nout, fmt = 9996 )' M ', mval( i ), 0
229  fatal = .true.
230  ELSE IF( mval( i ).GT.nmax ) THEN
231  WRITE( nout, fmt = 9995 )' M ', mval( i ), nmax
232  fatal = .true.
233  END IF
234  10 CONTINUE
235  IF( nm.GT.0 )
236  $ WRITE( nout, fmt = 9993 )'M ', ( mval( i ), i = 1, nm )
237 *
238 * Read the values of N
239 *
240  READ( nin, fmt = * )nn
241  IF( nn.LT.1 ) THEN
242  WRITE( nout, fmt = 9996 )' NN ', nn, 1
243  nn = 0
244  fatal = .true.
245  ELSE IF( nn.GT.maxin ) THEN
246  WRITE( nout, fmt = 9995 )' NN ', nn, maxin
247  nn = 0
248  fatal = .true.
249  END IF
250  READ( nin, fmt = * )( nval( i ), i = 1, nn )
251  DO 20 i = 1, nn
252  IF( nval( i ).LT.0 ) THEN
253  WRITE( nout, fmt = 9996 )' N ', nval( i ), 0
254  fatal = .true.
255  ELSE IF( nval( i ).GT.nmax ) THEN
256  WRITE( nout, fmt = 9995 )' N ', nval( i ), nmax
257  fatal = .true.
258  END IF
259  20 CONTINUE
260  IF( nn.GT.0 )
261  $ WRITE( nout, fmt = 9993 )'N ', ( nval( i ), i = 1, nn )
262 *
263 * Read the values of NRHS
264 *
265  READ( nin, fmt = * )nns
266  IF( nns.LT.1 ) THEN
267  WRITE( nout, fmt = 9996 )' NNS', nns, 1
268  nns = 0
269  fatal = .true.
270  ELSE IF( nns.GT.maxin ) THEN
271  WRITE( nout, fmt = 9995 )' NNS', nns, maxin
272  nns = 0
273  fatal = .true.
274  END IF
275  READ( nin, fmt = * )( nsval( i ), i = 1, nns )
276  DO 30 i = 1, nns
277  IF( nsval( i ).LT.0 ) THEN
278  WRITE( nout, fmt = 9996 )'NRHS', nsval( i ), 0
279  fatal = .true.
280  ELSE IF( nsval( i ).GT.maxrhs ) THEN
281  WRITE( nout, fmt = 9995 )'NRHS', nsval( i ), maxrhs
282  fatal = .true.
283  END IF
284  30 CONTINUE
285  IF( nns.GT.0 )
286  $ WRITE( nout, fmt = 9993 )'NRHS', ( nsval( i ), i = 1, nns )
287 *
288 * Read the values of NB
289 *
290  READ( nin, fmt = * )nnb
291  IF( nnb.LT.1 ) THEN
292  WRITE( nout, fmt = 9996 )'NNB ', nnb, 1
293  nnb = 0
294  fatal = .true.
295  ELSE IF( nnb.GT.maxin ) THEN
296  WRITE( nout, fmt = 9995 )'NNB ', nnb, maxin
297  nnb = 0
298  fatal = .true.
299  END IF
300  READ( nin, fmt = * )( nbval( i ), i = 1, nnb )
301  DO 40 i = 1, nnb
302  IF( nbval( i ).LT.0 ) THEN
303  WRITE( nout, fmt = 9996 )' NB ', nbval( i ), 0
304  fatal = .true.
305  END IF
306  40 CONTINUE
307  IF( nnb.GT.0 )
308  $ WRITE( nout, fmt = 9993 )'NB ', ( nbval( i ), i = 1, nnb )
309 *
310 * Set NBVAL2 to be the set of unique values of NB
311 *
312  nnb2 = 0
313  DO 60 i = 1, nnb
314  nb = nbval( i )
315  DO 50 j = 1, nnb2
316  IF( nb.EQ.nbval2( j ) )
317  $ GO TO 60
318  50 CONTINUE
319  nnb2 = nnb2 + 1
320  nbval2( nnb2 ) = nb
321  60 CONTINUE
322 *
323 * Read the values of NX
324 *
325  READ( nin, fmt = * )( nxval( i ), i = 1, nnb )
326  DO 70 i = 1, nnb
327  IF( nxval( i ).LT.0 ) THEN
328  WRITE( nout, fmt = 9996 )' NX ', nxval( i ), 0
329  fatal = .true.
330  END IF
331  70 CONTINUE
332  IF( nnb.GT.0 )
333  $ WRITE( nout, fmt = 9993 )'NX ', ( nxval( i ), i = 1, nnb )
334 *
335 * Read the values of RANKVAL
336 *
337  READ( nin, fmt = * )nrank
338  IF( nn.LT.1 ) THEN
339  WRITE( nout, fmt = 9996 )' NRANK ', nrank, 1
340  nrank = 0
341  fatal = .true.
342  ELSE IF( nn.GT.maxin ) THEN
343  WRITE( nout, fmt = 9995 )' NRANK ', nrank, maxin
344  nrank = 0
345  fatal = .true.
346  END IF
347  READ( nin, fmt = * )( rankval( i ), i = 1, nrank )
348  DO i = 1, nrank
349  IF( rankval( i ).LT.0 ) THEN
350  WRITE( nout, fmt = 9996 )' RANK ', rankval( i ), 0
351  fatal = .true.
352  ELSE IF( rankval( i ).GT.100 ) THEN
353  WRITE( nout, fmt = 9995 )' RANK ', rankval( i ), 100
354  fatal = .true.
355  END IF
356  END DO
357  IF( nrank.GT.0 )
358  $ WRITE( nout, fmt = 9993 )'RANK % OF N',
359  $ ( rankval( i ), i = 1, nrank )
360 *
361 * Read the threshold value for the test ratios.
362 *
363  READ( nin, fmt = * )thresh
364  WRITE( nout, fmt = 9992 )thresh
365 *
366 * Read the flag that indicates whether to test the LAPACK routines.
367 *
368  READ( nin, fmt = * )tstchk
369 *
370 * Read the flag that indicates whether to test the driver routines.
371 *
372  READ( nin, fmt = * )tstdrv
373 *
374 * Read the flag that indicates whether to test the error exits.
375 *
376  READ( nin, fmt = * )tsterr
377 *
378  IF( fatal ) THEN
379  WRITE( nout, fmt = 9999 )
380  stop
381  END IF
382 *
383 * Calculate and print the machine dependent constants.
384 *
385  eps = dlamch( 'Underflow threshold' )
386  WRITE( nout, fmt = 9991 )'underflow', eps
387  eps = dlamch( 'Overflow threshold' )
388  WRITE( nout, fmt = 9991 )'overflow ', eps
389  eps = dlamch( 'Epsilon' )
390  WRITE( nout, fmt = 9991 )'precision', eps
391  WRITE( nout, fmt = * )
392  nrhs = nsval( 1 )
393 *
394  80 CONTINUE
395 *
396 * Read a test path and the number of matrix types to use.
397 *
398  READ( nin, fmt = '(A72)', END = 140 )aline
399  path = aline( 1: 3 )
400  nmats = matmax
401  i = 3
402  90 CONTINUE
403  i = i + 1
404  IF( i.GT.72 )
405  $ GO TO 130
406  IF( aline( i: i ).EQ.' ' )
407  $ GO TO 90
408  nmats = 0
409  100 CONTINUE
410  c1 = aline( i: i )
411  DO 110 k = 1, 10
412  IF( c1.EQ.intstr( k: k ) ) THEN
413  ic = k - 1
414  GO TO 120
415  END IF
416  110 CONTINUE
417  GO TO 130
418  120 CONTINUE
419  nmats = nmats*10 + ic
420  i = i + 1
421  IF( i.GT.72 )
422  $ GO TO 130
423  GO TO 100
424  130 CONTINUE
425  c1 = path( 1: 1 )
426  c2 = path( 2: 3 )
427 *
428 * Check first character for correct precision.
429 *
430  IF( .NOT.lsame( c1, 'Zomplex precision' ) ) THEN
431  WRITE( nout, fmt = 9990 )path
432 *
433  ELSE IF( nmats.LE.0 ) THEN
434 *
435 * Check for a positive number of tests requested.
436 *
437  WRITE( nout, fmt = 9989 )path
438 *
439  ELSE IF( lsamen( 2, c2, 'GE' ) ) THEN
440 *
441 * GE: general matrices
442 *
443  ntypes = 11
444  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
445 *
446  IF( tstchk ) THEN
447  CALL zchkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
448  $ nsval, thresh, tsterr, lda, a( 1, 1 ),
449  $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
450  $ b( 1, 3 ), work, rwork, iwork, nout )
451  ELSE
452  WRITE( nout, fmt = 9989 )path
453  END IF
454 *
455  IF( tstdrv ) THEN
456  CALL zdrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
457  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
458  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
459  $ rwork, iwork, nout )
460  ELSE
461  WRITE( nout, fmt = 9988 )path
462  END IF
463 *
464  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
465 *
466 * GB: general banded matrices
467 *
468  la = ( 2*kdmax+1 )*nmax
469  lafac = ( 3*kdmax+1 )*nmax
470  ntypes = 8
471  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
472 *
473  IF( tstchk ) THEN
474  CALL zchkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
475  $ nsval, thresh, tsterr, a( 1, 1 ), la,
476  $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
477  $ b( 1, 3 ), work, rwork, iwork, nout )
478  ELSE
479  WRITE( nout, fmt = 9989 )path
480  END IF
481 *
482  IF( tstdrv ) THEN
483  CALL zdrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
484  $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
485  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
486  $ work, rwork, iwork, nout )
487  ELSE
488  WRITE( nout, fmt = 9988 )path
489  END IF
490 *
491  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
492 *
493 * GT: general tridiagonal matrices
494 *
495  ntypes = 12
496  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
497 *
498  IF( tstchk ) THEN
499  CALL zchkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
500  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
501  $ b( 1, 3 ), work, rwork, iwork, nout )
502  ELSE
503  WRITE( nout, fmt = 9989 )path
504  END IF
505 *
506  IF( tstdrv ) THEN
507  CALL zdrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
508  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
509  $ b( 1, 3 ), work, rwork, iwork, nout )
510  ELSE
511  WRITE( nout, fmt = 9988 )path
512  END IF
513 *
514  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
515 *
516 * PO: positive definite matrices
517 *
518  ntypes = 9
519  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
520 *
521  IF( tstchk ) THEN
522  CALL zchkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
523  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
524  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
525  $ work, rwork, nout )
526  ELSE
527  WRITE( nout, fmt = 9989 )path
528  END IF
529 *
530  IF( tstdrv ) THEN
531  CALL zdrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
532  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
533  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
534  $ rwork, nout )
535  ELSE
536  WRITE( nout, fmt = 9988 )path
537  END IF
538 *
539  ELSE IF( lsamen( 2, c2, 'PS' ) ) THEN
540 *
541 * PS: positive semi-definite matrices
542 *
543  ntypes = 9
544 *
545  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
546 *
547  IF( tstchk ) THEN
548  CALL zchkps( dotype, nn, nval, nnb2, nbval2, nrank,
549  $ rankval, thresh, tsterr, lda, a( 1, 1 ),
550  $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
551  $ nout )
552  ELSE
553  WRITE( nout, fmt = 9989 )path
554  END IF
555 *
556  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
557 *
558 * PP: positive definite packed matrices
559 *
560  ntypes = 9
561  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
562 *
563  IF( tstchk ) THEN
564  CALL zchkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
565  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
566  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
567  $ nout )
568  ELSE
569  WRITE( nout, fmt = 9989 )path
570  END IF
571 *
572  IF( tstdrv ) THEN
573  CALL zdrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
574  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
575  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
576  $ rwork, nout )
577  ELSE
578  WRITE( nout, fmt = 9988 )path
579  END IF
580 *
581  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
582 *
583 * PB: positive definite banded matrices
584 *
585  ntypes = 8
586  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
587 *
588  IF( tstchk ) THEN
589  CALL zchkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
590  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
591  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
592  $ work, rwork, nout )
593  ELSE
594  WRITE( nout, fmt = 9989 )path
595  END IF
596 *
597  IF( tstdrv ) THEN
598  CALL zdrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
599  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
600  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
601  $ rwork, nout )
602  ELSE
603  WRITE( nout, fmt = 9988 )path
604  END IF
605 *
606  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
607 *
608 * PT: positive definite tridiagonal matrices
609 *
610  ntypes = 12
611  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
612 *
613  IF( tstchk ) THEN
614  CALL zchkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
615  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
616  $ b( 1, 3 ), work, rwork, nout )
617  ELSE
618  WRITE( nout, fmt = 9989 )path
619  END IF
620 *
621  IF( tstdrv ) THEN
622  CALL zdrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
623  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
624  $ b( 1, 3 ), work, rwork, nout )
625  ELSE
626  WRITE( nout, fmt = 9988 )path
627  END IF
628 *
629  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
630 *
631 * HE: Hermitian indefinite matrices
632 *
633  ntypes = 10
634  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
635 *
636  IF( tstchk ) THEN
637  CALL zchkhe( dotype, nn, nval, nnb2, nbval2, nns, nsval,
638  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
639  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
640  $ work, rwork, iwork, nout )
641  ELSE
642  WRITE( nout, fmt = 9989 )path
643  END IF
644 *
645  IF( tstdrv ) THEN
646  CALL zdrvhe( dotype, nn, nval, nrhs, thresh, tsterr, lda,
647  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
648  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
649  $ nout )
650  ELSE
651  WRITE( nout, fmt = 9988 )path
652  END IF
653 
654  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
655 *
656 * HR: Hermitian indefinite matrices,
657 * with bounded Bunch-Kaufman (rook) pivoting algorithm,
658 *
659  ntypes = 10
660  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
661 *
662  IF( tstchk ) THEN
663  CALL zchkhe_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
664  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
665  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
666  $ work, rwork, iwork, nout )
667  ELSE
668  WRITE( nout, fmt = 9989 )path
669  END IF
670 *
671  IF( tstdrv ) THEN
672  CALL zdrvhe_rook( dotype, nn, nval, nrhs, thresh, tsterr,
673  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
674  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
675  $ rwork, iwork, nout )
676  ELSE
677  WRITE( nout, fmt = 9988 )path
678  END IF
679 *
680  ELSE IF( lsamen( 2, c2, 'HK' ) ) THEN
681 *
682 * HK: Hermitian indefinite matrices,
683 * with bounded Bunch-Kaufman (rook) pivoting algorithm,
684 * different matrix storage format than HR path version.
685 *
686  ntypes = 10
687  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
688 *
689  IF( tstchk ) THEN
690  CALL zchkhe_rk ( dotype, nn, nval, nnb2, nbval2, nns, nsval,
691  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
692  $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
693  $ b( 1, 3 ), work, rwork, iwork, nout )
694  ELSE
695  WRITE( nout, fmt = 9989 )path
696  END IF
697 *
698  IF( tstdrv ) THEN
699  CALL zdrvhe_rk( dotype, nn, nval, nrhs, thresh, tsterr,
700  $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
701  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
702  $ rwork, iwork, nout )
703  ELSE
704  WRITE( nout, fmt = 9988 )path
705  END IF
706 *
707  ELSE IF( lsamen( 2, c2, 'HA' ) ) THEN
708 *
709 * HA: Hermitian matrices,
710 * Aasen Algorithm
711 *
712  ntypes = 10
713  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
714 *
715  IF( tstchk ) THEN
716  CALL zchkhe_aa( dotype, nn, nval, nnb2, nbval2, nns,
717  $ nsval, thresh, tsterr, lda,
718  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
719  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
720  $ work, rwork, iwork, nout )
721  ELSE
722  WRITE( nout, fmt = 9989 )path
723  END IF
724 *
725  IF( tstdrv ) THEN
726  CALL zdrvhe_aa( dotype, nn, nval, nrhs, thresh, tsterr,
727  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
728  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
729  $ work, rwork, iwork, nout )
730  ELSE
731  WRITE( nout, fmt = 9988 )path
732  END IF
733 *
734  ELSE IF( lsamen( 2, c2, 'H2' ) ) THEN
735 *
736 * H2: Hermitian matrices,
737 * with partial (Aasen's) pivoting algorithm
738 *
739  ntypes = 10
740  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
741 *
742  IF( tstchk ) THEN
743  CALL zchkhe_aa_2stage( dotype, nn, nval, nnb2, nbval2,
744  $ nns, nsval, thresh, tsterr, lda,
745  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
746  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
747  $ work, rwork, iwork, nout )
748  ELSE
749  WRITE( nout, fmt = 9989 )path
750  END IF
751 *
752  IF( tstdrv ) THEN
753  CALL zdrvhe_aa_2stage(
754  $ dotype, nn, nval, nrhs, thresh, tsterr,
755  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
756  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
757  $ work, rwork, iwork, nout )
758  ELSE
759  WRITE( nout, fmt = 9988 )path
760  END IF
761 *
762 *
763  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
764 *
765 * HP: Hermitian indefinite packed matrices
766 *
767  ntypes = 10
768  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
769 *
770  IF( tstchk ) THEN
771  CALL zchkhp( dotype, nn, nval, nns, nsval, thresh, tsterr,
772  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
773  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
774  $ iwork, nout )
775  ELSE
776  WRITE( nout, fmt = 9989 )path
777  END IF
778 *
779  IF( tstdrv ) THEN
780  CALL zdrvhp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
781  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
782  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
783  $ nout )
784  ELSE
785  WRITE( nout, fmt = 9988 )path
786  END IF
787 *
788  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
789 *
790 * SY: symmetric indefinite matrices,
791 * with partial (Bunch-Kaufman) pivoting algorithm
792 *
793  ntypes = 11
794  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
795 *
796  IF( tstchk ) THEN
797  CALL zchksy( dotype, nn, nval, nnb2, nbval2, nns, nsval,
798  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
799  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
800  $ work, rwork, iwork, nout )
801  ELSE
802  WRITE( nout, fmt = 9989 )path
803  END IF
804 *
805  IF( tstdrv ) THEN
806  CALL zdrvsy( dotype, nn, nval, nrhs, thresh, tsterr, lda,
807  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
808  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
809  $ nout )
810  ELSE
811  WRITE( nout, fmt = 9988 )path
812  END IF
813 *
814  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
815 *
816 * SR: symmetric indefinite matrices,
817 * with bounded Bunch-Kaufman (rook) pivoting algorithm
818 *
819  ntypes = 11
820  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
821 *
822  IF( tstchk ) THEN
823  CALL zchksy_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
824  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
825  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
826  $ work, rwork, iwork, nout )
827  ELSE
828  WRITE( nout, fmt = 9989 )path
829  END IF
830 *
831  IF( tstdrv ) THEN
832  CALL zdrvsy_rook( dotype, nn, nval, nrhs, thresh, tsterr,
833  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
834  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
835  $ rwork, iwork, nout )
836  ELSE
837  WRITE( nout, fmt = 9988 )path
838  END IF
839 *
840  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
841 *
842 * SK: symmetric indefinite matrices,
843 * with bounded Bunch-Kaufman (rook) pivoting algorithm,
844 * different matrix storage format than SR path version.
845 *
846  ntypes = 11
847  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
848 *
849  IF( tstchk ) THEN
850  CALL zchksy_rk( dotype, nn, nval, nnb2, nbval2, nns, nsval,
851  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
852  $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
853  $ b( 1, 3 ), work, rwork, iwork, nout )
854  ELSE
855  WRITE( nout, fmt = 9989 )path
856  END IF
857 *
858  IF( tstdrv ) THEN
859  CALL zdrvsy_rk( dotype, nn, nval, nrhs, thresh, tsterr,
860  $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
861  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
862  $ rwork, iwork, nout )
863  ELSE
864  WRITE( nout, fmt = 9988 )path
865  END IF
866 *
867  ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
868 *
869 * SA: symmetric indefinite matrices with Aasen's algorithm,
870 *
871  ntypes = 11
872  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
873 *
874  IF( tstchk ) THEN
875  CALL zchksy_aa( dotype, nn, nval, nnb2, nbval2, nns, nsval,
876  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
877  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
878  $ b( 1, 3 ), work, rwork, iwork, nout )
879  ELSE
880  WRITE( nout, fmt = 9989 )path
881  END IF
882 *
883  IF( tstdrv ) THEN
884  CALL zdrvsy_aa( dotype, nn, nval, nrhs, thresh, tsterr,
885  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
886  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
887  $ rwork, iwork, nout )
888  ELSE
889  WRITE( nout, fmt = 9988 )path
890  END IF
891 *
892  ELSE IF( lsamen( 2, c2, 'S2' ) ) THEN
893 *
894 * S2: symmetric indefinite matrices with Aasen's algorithm
895 * 2 stage
896 *
897  ntypes = 11
898  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
899 *
900  IF( tstchk ) THEN
901  CALL zchksy_aa_2stage( dotype, nn, nval, nnb2, nbval2, nns,
902  $ nsval, thresh, tsterr, lda,
903  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
904  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
905  $ work, rwork, iwork, nout )
906  ELSE
907  WRITE( nout, fmt = 9989 )path
908  END IF
909 *
910  IF( tstdrv ) THEN
911  CALL zdrvsy_aa_2stage(
912  $ dotype, nn, nval, nrhs, thresh, tsterr,
913  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
914  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work,
915  $ rwork, iwork, nout )
916  ELSE
917  WRITE( nout, fmt = 9988 )path
918  END IF
919 *
920  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
921 *
922 * SP: symmetric indefinite packed matrices,
923 * with partial (Bunch-Kaufman) pivoting algorithm
924 *
925  ntypes = 11
926  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
927 *
928  IF( tstchk ) THEN
929  CALL zchksp( dotype, nn, nval, nns, nsval, thresh, tsterr,
930  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
931  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
932  $ iwork, nout )
933  ELSE
934  WRITE( nout, fmt = 9989 )path
935  END IF
936 *
937  IF( tstdrv ) THEN
938  CALL zdrvsp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
939  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
940  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
941  $ nout )
942  ELSE
943  WRITE( nout, fmt = 9988 )path
944  END IF
945 *
946  ELSE IF( lsamen( 2, c2, 'TR' ) ) THEN
947 *
948 * TR: triangular matrices
949 *
950  ntypes = 18
951  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
952 *
953  IF( tstchk ) THEN
954  CALL zchktr( dotype, nn, nval, nnb2, nbval2, nns, nsval,
955  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
956  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
957  $ nout )
958  ELSE
959  WRITE( nout, fmt = 9989 )path
960  END IF
961 *
962  ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
963 *
964 * TP: triangular packed matrices
965 *
966  ntypes = 18
967  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
968 *
969  IF( tstchk ) THEN
970  CALL zchktp( dotype, nn, nval, nns, nsval, thresh, tsterr,
971  $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
972  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
973  ELSE
974  WRITE( nout, fmt = 9989 )path
975  END IF
976 *
977  ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
978 *
979 * TB: triangular banded matrices
980 *
981  ntypes = 17
982  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
983 *
984  IF( tstchk ) THEN
985  CALL zchktb( dotype, nn, nval, nns, nsval, thresh, tsterr,
986  $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
987  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
988  ELSE
989  WRITE( nout, fmt = 9989 )path
990  END IF
991 *
992  ELSE IF( lsamen( 2, c2, 'QR' ) ) THEN
993 *
994 * QR: QR factorization
995 *
996  ntypes = 8
997  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
998 *
999  IF( tstchk ) THEN
1000  CALL zchkqr( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1001  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1002  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1003  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1004  $ work, rwork, iwork, nout )
1005  ELSE
1006  WRITE( nout, fmt = 9989 )path
1007  END IF
1008 *
1009  ELSE IF( lsamen( 2, c2, 'LQ' ) ) THEN
1010 *
1011 * LQ: LQ factorization
1012 *
1013  ntypes = 8
1014  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1015 *
1016  IF( tstchk ) THEN
1017  CALL zchklq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1018  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1019  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1020  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1021  $ work, rwork, nout )
1022  ELSE
1023  WRITE( nout, fmt = 9989 )path
1024  END IF
1025 *
1026  ELSE IF( lsamen( 2, c2, 'QL' ) ) THEN
1027 *
1028 * QL: QL factorization
1029 *
1030  ntypes = 8
1031  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1032 *
1033  IF( tstchk ) THEN
1034  CALL zchkql( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1035  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1036  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1037  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1038  $ work, rwork, nout )
1039  ELSE
1040  WRITE( nout, fmt = 9989 )path
1041  END IF
1042 *
1043  ELSE IF( lsamen( 2, c2, 'RQ' ) ) THEN
1044 *
1045 * RQ: RQ factorization
1046 *
1047  ntypes = 8
1048  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1049 *
1050  IF( tstchk ) THEN
1051  CALL zchkrq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1052  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
1053  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1054  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
1055  $ work, rwork, iwork, nout )
1056  ELSE
1057  WRITE( nout, fmt = 9989 )path
1058  END IF
1059 *
1060  ELSE IF( lsamen( 2, c2, 'EQ' ) ) THEN
1061 *
1062 * EQ: Equilibration routines for general and positive definite
1063 * matrices (THREQ should be between 2 and 10)
1064 *
1065  IF( tstchk ) THEN
1066  CALL zchkeq( threq, nout )
1067  ELSE
1068  WRITE( nout, fmt = 9989 )path
1069  END IF
1070 *
1071  ELSE IF( lsamen( 2, c2, 'TZ' ) ) THEN
1072 *
1073 * TZ: Trapezoidal matrix
1074 *
1075  ntypes = 3
1076  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1077 *
1078  IF( tstchk ) THEN
1079  CALL zchktz( dotype, nm, mval, nn, nval, thresh, tsterr,
1080  $ a( 1, 1 ), a( 1, 2 ), s( 1 ),
1081  $ b( 1, 1 ), work, rwork, nout )
1082  ELSE
1083  WRITE( nout, fmt = 9989 )path
1084  END IF
1085 *
1086  ELSE IF( lsamen( 2, c2, 'QP' ) ) THEN
1087 *
1088 * QP: QR factorization with pivoting
1089 *
1090  ntypes = 6
1091  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1092 *
1093  IF( tstchk ) THEN
1094  CALL zchkq3( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
1095  $ thresh, a( 1, 1 ), a( 1, 2 ), s( 1 ),
1096  $ b( 1, 1 ), work, rwork, iwork,
1097  $ nout )
1098  ELSE
1099  WRITE( nout, fmt = 9989 )path
1100  END IF
1101 *
1102  ELSE IF( lsamen( 2, c2, 'LS' ) ) THEN
1103 *
1104 * LS: Least squares drivers
1105 *
1106  ntypes = 6
1107  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1108 *
1109  IF( tstdrv ) THEN
1110  CALL zdrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
1111  $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
1112  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1113  $ s( 1 ), s( nmax+1 ), nout )
1114  ELSE
1115  WRITE( nout, fmt = 9989 )path
1116  END IF
1117 *
1118 *
1119  ELSE IF( lsamen( 2, c2, 'QT' ) ) THEN
1120 *
1121 * QT: QRT routines for general matrices
1122 *
1123  IF( tstchk ) THEN
1124  CALL zchkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
1125  $ nbval, nout )
1126  ELSE
1127  WRITE( nout, fmt = 9989 )path
1128  END IF
1129 *
1130  ELSE IF( lsamen( 2, c2, 'QX' ) ) THEN
1131 *
1132 * QX: QRT routines for triangular-pentagonal matrices
1133 *
1134  IF( tstchk ) THEN
1135  CALL zchkqrtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1136  $ nbval, nout )
1137  ELSE
1138  WRITE( nout, fmt = 9989 )path
1139  END IF
1140 *
1141  ELSE IF( lsamen( 2, c2, 'TQ' ) ) THEN
1142 *
1143 * TQ: LQT routines for general matrices
1144 *
1145  IF( tstchk ) THEN
1146  CALL zchklqt( thresh, tsterr, nm, mval, nn, nval, nnb,
1147  $ nbval, nout )
1148  ELSE
1149  WRITE( nout, fmt = 9989 )path
1150  END IF
1151 *
1152  ELSE IF( lsamen( 2, c2, 'XQ' ) ) THEN
1153 *
1154 * XQ: LQT routines for triangular-pentagonal matrices
1155 *
1156  IF( tstchk ) THEN
1157  CALL zchklqtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1158  $ nbval, nout )
1159  ELSE
1160  WRITE( nout, fmt = 9989 )path
1161  END IF
1162 *
1163  ELSE IF( lsamen( 2, c2, 'TS' ) ) THEN
1164 *
1165 * TS: QR routines for tall-skinny matrices
1166 *
1167  IF( tstchk ) THEN
1168  CALL zchktsqr( thresh, tsterr, nm, mval, nn, nval, nnb,
1169  $ nbval, nout )
1170  ELSE
1171  WRITE( nout, fmt = 9989 )path
1172  END IF
1173 *
1174  ELSE IF( lsamen( 2, c2, 'TQ' ) ) THEN
1175 *
1176 * TQ: LQT routines for general matrices
1177 *
1178  IF( tstchk ) THEN
1179  CALL zchklqt( thresh, tsterr, nm, mval, nn, nval, nnb,
1180  $ nbval, nout )
1181  ELSE
1182  WRITE( nout, fmt = 9989 )path
1183  END IF
1184 *
1185  ELSE IF( lsamen( 2, c2, 'XQ' ) ) THEN
1186 *
1187 * XQ: LQT routines for triangular-pentagonal matrices
1188 *
1189  IF( tstchk ) THEN
1190  CALL zchklqtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1191  $ nbval, nout )
1192  ELSE
1193  WRITE( nout, fmt = 9989 )path
1194  END IF
1195 *
1196  ELSE IF( lsamen( 2, c2, 'TS' ) ) THEN
1197 *
1198 * TS: QR routines for tall-skinny matrices
1199 *
1200  IF( tstchk ) THEN
1201  CALL zchktsqr( thresh, tsterr, nm, mval, nn, nval, nnb,
1202  $ nbval, nout )
1203  ELSE
1204  WRITE( nout, fmt = 9989 )path
1205  END IF
1206 *
1207  ELSE IF( lsamen( 2, c2, 'HH' ) ) THEN
1208 *
1209 * HH: Householder reconstruction for tall-skinny matrices
1210 *
1211  IF( tstchk ) THEN
1212  CALL zchkunhr_col( thresh, tsterr, nm, mval, nn, nval, nnb,
1213  $ nbval, nout )
1214  ELSE
1215  WRITE( nout, fmt = 9989 ) path
1216  END IF
1217 *
1218  ELSE
1219 *
1220  WRITE( nout, fmt = 9990 )path
1221  END IF
1222 *
1223 * Go back to get another input line.
1224 *
1225  GO TO 80
1226 *
1227 * Branch to this line when the last record is read.
1228 *
1229  140 CONTINUE
1230  CLOSE ( nin )
1231  s2 = dsecnd( )
1232  WRITE( nout, fmt = 9998 )
1233  WRITE( nout, fmt = 9997 )s2 - s1
1234 *
1235  9999 FORMAT( / ' Execution not attempted due to input errors' )
1236  9998 FORMAT( / ' End of tests' )
1237  9997 FORMAT( ' Total time used = ', f12.2, ' seconds', / )
1238  9996 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be >=',
1239  $ i6 )
1240  9995 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be <=',
1241  $ i6 )
1242  9994 FORMAT( ' Tests of the COMPLEX*16 LAPACK routines ',
1243  $ / ' LAPACK VERSION ', i1, '.', i1, '.', i1,
1244  $ / / ' The following parameter values will be used:' )
1245  9993 FORMAT( 4x, a4, ': ', 10i6, / 11x, 10i6 )
1246  9992 FORMAT( / ' Routines pass computational tests if test ratio is ',
1247  $ 'less than', f8.2, / )
1248  9991 FORMAT( ' Relative machine ', a, ' is taken to be', d16.6 )
1249  9990 FORMAT( / 1x, a3, ': Unrecognized path name' )
1250  9989 FORMAT( / 1x, a3, ' routines were not tested' )
1251  9988 FORMAT( / 1x, a3, ' driver routines were not tested' )
1252 *
1253 * End of ZCHKAA
1254 *
1255  END
zchklq
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
dsecnd
double precision function dsecnd()
DSECND Using ETIME
Definition: dsecnd_EXT_ETIME.f:37
zchkge
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
zdrvpt
subroutine zdrvpt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
ZDRVPT
Definition: zdrvpt.f:142
zchkhe
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
zchkhe_aa_2stage
subroutine zchkhe_aa_2stage(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHE_AA_2STAGE
Definition: zchkhe_aa_2stage.f:174
lsamen
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
zchktr
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
zchkpt
subroutine zchkpt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPT
Definition: zchkpt.f:149
zchktsqr
subroutine zchktsqr(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
DCHKQRT
Definition: zchktsqr.f:104
zchksy_aa_2stage
subroutine zchksy_aa_2stage(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSY_AA_2STAGE
Definition: zchksy_aa_2stage.f:174
zchkhe_rk
subroutine zchkhe_rk(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHE_RK
Definition: zchkhe_rk.f:179
zdrvge
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
zchktp
subroutine zchktp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AP, AINVP, B, X, XACT, WORK, RWORK, NOUT)
ZCHKTP
Definition: zchktp.f:153
zchkq3
subroutine zchkq3(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, THRESH, A, COPYA, S, TAU, WORK, RWORK, IWORK, NOUT)
ZCHKQ3
Definition: zchkq3.f:160
zchkunhr_col
subroutine zchkunhr_col(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKUNHR_COL
Definition: zchkunhr_col.f:107
zdrvls
subroutine zdrvls(DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB, NBVAL, NXVAL, THRESH, TSTERR, A, COPYA, B, COPYB, C, S, COPYS, NOUT)
ZDRVLS
Definition: zdrvls.f:194
zchkpo
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
zchksy_rook
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
zchkaa
program zchkaa
ZCHKAA
Definition: zchkaa.f:118
zchkgt
subroutine zchkgt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKGT
Definition: zchkgt.f:149
zdrvsp
subroutine zdrvsp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSP
Definition: zdrvsp.f:159
zchksp
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
zchkqrtp
subroutine zchkqrtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKQRTP
Definition: zchkqrtp.f:104
zchklqtp
subroutine zchklqtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKLQTP
Definition: zchklqtp.f:104
zdrvpo
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
zchkrq
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
zchkeq
subroutine zchkeq(THRESH, NOUT)
ZCHKEQ
Definition: zchkeq.f:56
zdrvgb
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
zdrvsy
subroutine zdrvsy(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY
Definition: zdrvsy.f:155
zdrvhe_rk
subroutine zdrvhe_rk(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE_RK
Definition: zdrvhe_rk.f:160
zchkps
subroutine zchkps(DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL, THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK, RWORK, NOUT)
ZCHKPS
Definition: zchkps.f:156
zchktz
subroutine zchktz(DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A, COPYA, S, TAU, WORK, RWORK, NOUT)
ZCHKTZ
Definition: zchktz.f:139
zchkqrt
subroutine zchkqrt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKQRT
Definition: zchkqrt.f:103
zdrvhe_aa
subroutine zdrvhe_aa(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE_AA
Definition: zdrvhe_aa.f:155
zchksy_aa
subroutine zchksy_aa(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSY_AA
Definition: zchksy_aa.f:173
zdrvhe_rook
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
zchkhe_rook
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
zdrvhe_aa_2stage
subroutine zdrvhe_aa_2stage(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE_AA_2STAGE
Definition: zdrvhe_aa_2stage.f:157
zchkhe_aa
subroutine zchkhe_aa(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKHE_AA
Definition: zchkhe_aa.f:174
zdrvpb
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
zdrvsy_aa_2stage
subroutine zdrvsy_aa_2stage(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY_AA_2STAGE
Definition: zdrvsy_aa_2stage.f:157
zchklqt
subroutine zchklqt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKLQT
Definition: zchklqt.f:104
zdrvhe
subroutine zdrvhe(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE
Definition: zdrvhe.f:155
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
zdrvsy_rk
subroutine zdrvsy_rk(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY_RK
Definition: zdrvsy_rk.f:160
zchkqr
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
zchkhp
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
zchkgb
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
alareq
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
zdrvsy_rook
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
zdrvsy_aa
subroutine zdrvsy_aa(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVSY_AA
Definition: zdrvsy_aa.f:155
zdrvgt
subroutine zdrvgt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVGT
Definition: zdrvgt.f:141
zchkql
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
zchksy
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
zchkpp
subroutine zchkpp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKPP
Definition: zchkpp.f:161
zchkpb
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
zdrvpp
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
ilaver
subroutine ilaver(VERS_MAJOR, VERS_MINOR, VERS_PATCH)
ILAVER returns the LAPACK version.
Definition: ilaver.f:53
dlamch
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:70
zchktb
subroutine zchktb(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AB, AINV, B, X, XACT, WORK, RWORK, NOUT)
ZCHKTB
Definition: zchktb.f:151
zdrvhp
subroutine zdrvhp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHP
Definition: zdrvhp.f:159
zchksy_rk
subroutine zchksy_rk(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZCHKSY_RK
Definition: zchksy_rk.f:179