LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
cchkaa.f
Go to the documentation of this file.
1 *> \brief \b CCHKAA
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 CCHKAA
12 *
13 *
14 *> \par Purpose:
15 * =============
16 *>
17 *> \verbatim
18 *>
19 *> CCHKAA is the main test program for the COMPLEX 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 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 *> CGE 11 List types on next line if 0 < NTYPES < 11
45 *> CGB 8 List types on next line if 0 < NTYPES < 8
46 *> CGT 12 List types on next line if 0 < NTYPES < 12
47 *> CPO 9 List types on next line if 0 < NTYPES < 9
48 *> CPO 9 List types on next line if 0 < NTYPES < 9
49 *> CPP 9 List types on next line if 0 < NTYPES < 9
50 *> CPB 8 List types on next line if 0 < NTYPES < 8
51 *> CPT 12 List types on next line if 0 < NTYPES < 12
52 *> CHE 10 List types on next line if 0 < NTYPES < 10
53 *> CHR 10 List types on next line if 0 < NTYPES < 10
54 *> CHK 10 List types on next line if 0 < NTYPES < 10
55 *> CHA 10 List types on next line if 0 < NTYPES < 10
56 *> CH2 10 List types on next line if 0 < NTYPES < 10
57 *> CSA 11 List types on next line if 0 < NTYPES < 10
58 *> CS2 11 List types on next line if 0 < NTYPES < 10
59 *> CHP 10 List types on next line if 0 < NTYPES < 10
60 *> CSY 11 List types on next line if 0 < NTYPES < 11
61 *> CSK 11 List types on next line if 0 < NTYPES < 11
62 *> CSR 11 List types on next line if 0 < NTYPES < 11
63 *> CSP 11 List types on next line if 0 < NTYPES < 11
64 *> CTR 18 List types on next line if 0 < NTYPES < 18
65 *> CTP 18 List types on next line if 0 < NTYPES < 18
66 *> CTB 17 List types on next line if 0 < NTYPES < 17
67 *> CQR 8 List types on next line if 0 < NTYPES < 8
68 *> CRQ 8 List types on next line if 0 < NTYPES < 8
69 *> CLQ 8 List types on next line if 0 < NTYPES < 8
70 *> CQL 8 List types on next line if 0 < NTYPES < 8
71 *> CQP 6 List types on next line if 0 < NTYPES < 6
72 *> CTZ 3 List types on next line if 0 < NTYPES < 3
73 *> CLS 6 List types on next line if 0 < NTYPES < 6
74 *> CEQ
75 *> CQT
76 *> CQX
77 *> CTS
78 *> CHH
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 complex_lin
116 *
117 * =====================================================================
118  PROGRAM cchkaa
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 2017
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  REAL 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  REAL rwork( 150*nmax+2*maxrhs ), s( 2*nmax )
160  COMPLEX 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  REAL second, slamch
166  EXTERNAL lsame, lsamen, second, slamch
167 * ..
168 * .. External Subroutines ..
169  EXTERNAL alareq, cchkeq, cchkgb, cchkge, cchkgt, cchkhe,
179  $ cchkqrt, cchkqrtp
180 * ..
181 * .. Scalars in Common ..
182  LOGICAL lerr, ok
183  CHARACTER*32 srnamt
184  INTEGER infot, nunit
185 * ..
186 * .. Arrays in Common ..
187  INTEGER iparms( 100 )
188 * ..
189 * .. Common blocks ..
190  COMMON / claenv / iparms
191  COMMON / infoc / infot, nunit, ok, lerr
192  COMMON / srnamc / srnamt
193 * ..
194 * .. Data statements ..
195  DATA threq / 2.0 / , intstr / '0123456789' /
196 * ..
197 * .. Executable Statements ..
198 *
199  s1 = second( )
200  lda = nmax
201  fatal = .false.
202 *
203 * Read a dummy line.
204 *
205  READ( nin, fmt = * )
206 *
207 * Report values of parameters.
208 *
209  CALL ilaver( vers_major, vers_minor, vers_patch )
210  WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
211 *
212 * Read the values of M
213 *
214  READ( nin, fmt = * )nm
215  IF( nm.LT.1 ) THEN
216  WRITE( nout, fmt = 9996 )' NM ', nm, 1
217  nm = 0
218  fatal = .true.
219  ELSE IF( nm.GT.maxin ) THEN
220  WRITE( nout, fmt = 9995 )' NM ', nm, maxin
221  nm = 0
222  fatal = .true.
223  END IF
224  READ( nin, fmt = * )( mval( i ), i = 1, nm )
225  DO 10 i = 1, nm
226  IF( mval( i ).LT.0 ) THEN
227  WRITE( nout, fmt = 9996 )' M ', mval( i ), 0
228  fatal = .true.
229  ELSE IF( mval( i ).GT.nmax ) THEN
230  WRITE( nout, fmt = 9995 )' M ', mval( i ), nmax
231  fatal = .true.
232  END IF
233  10 CONTINUE
234  IF( nm.GT.0 )
235  $ WRITE( nout, fmt = 9993 )'M ', ( mval( i ), i = 1, nm )
236 *
237 * Read the values of N
238 *
239  READ( nin, fmt = * )nn
240  IF( nn.LT.1 ) THEN
241  WRITE( nout, fmt = 9996 )' NN ', nn, 1
242  nn = 0
243  fatal = .true.
244  ELSE IF( nn.GT.maxin ) THEN
245  WRITE( nout, fmt = 9995 )' NN ', nn, maxin
246  nn = 0
247  fatal = .true.
248  END IF
249  READ( nin, fmt = * )( nval( i ), i = 1, nn )
250  DO 20 i = 1, nn
251  IF( nval( i ).LT.0 ) THEN
252  WRITE( nout, fmt = 9996 )' N ', nval( i ), 0
253  fatal = .true.
254  ELSE IF( nval( i ).GT.nmax ) THEN
255  WRITE( nout, fmt = 9995 )' N ', nval( i ), nmax
256  fatal = .true.
257  END IF
258  20 CONTINUE
259  IF( nn.GT.0 )
260  $ WRITE( nout, fmt = 9993 )'N ', ( nval( i ), i = 1, nn )
261 *
262 * Read the values of NRHS
263 *
264  READ( nin, fmt = * )nns
265  IF( nns.LT.1 ) THEN
266  WRITE( nout, fmt = 9996 )' NNS', nns, 1
267  nns = 0
268  fatal = .true.
269  ELSE IF( nns.GT.maxin ) THEN
270  WRITE( nout, fmt = 9995 )' NNS', nns, maxin
271  nns = 0
272  fatal = .true.
273  END IF
274  READ( nin, fmt = * )( nsval( i ), i = 1, nns )
275  DO 30 i = 1, nns
276  IF( nsval( i ).LT.0 ) THEN
277  WRITE( nout, fmt = 9996 )'NRHS', nsval( i ), 0
278  fatal = .true.
279  ELSE IF( nsval( i ).GT.maxrhs ) THEN
280  WRITE( nout, fmt = 9995 )'NRHS', nsval( i ), maxrhs
281  fatal = .true.
282  END IF
283  30 CONTINUE
284  IF( nns.GT.0 )
285  $ WRITE( nout, fmt = 9993 )'NRHS', ( nsval( i ), i = 1, nns )
286 *
287 * Read the values of NB
288 *
289  READ( nin, fmt = * )nnb
290  IF( nnb.LT.1 ) THEN
291  WRITE( nout, fmt = 9996 )'NNB ', nnb, 1
292  nnb = 0
293  fatal = .true.
294  ELSE IF( nnb.GT.maxin ) THEN
295  WRITE( nout, fmt = 9995 )'NNB ', nnb, maxin
296  nnb = 0
297  fatal = .true.
298  END IF
299  READ( nin, fmt = * )( nbval( i ), i = 1, nnb )
300  DO 40 i = 1, nnb
301  IF( nbval( i ).LT.0 ) THEN
302  WRITE( nout, fmt = 9996 )' NB ', nbval( i ), 0
303  fatal = .true.
304  END IF
305  40 CONTINUE
306  IF( nnb.GT.0 )
307  $ WRITE( nout, fmt = 9993 )'NB ', ( nbval( i ), i = 1, nnb )
308 *
309 * Set NBVAL2 to be the set of unique values of NB
310 *
311  nnb2 = 0
312  DO 60 i = 1, nnb
313  nb = nbval( i )
314  DO 50 j = 1, nnb2
315  IF( nb.EQ.nbval2( j ) )
316  $ GO TO 60
317  50 CONTINUE
318  nnb2 = nnb2 + 1
319  nbval2( nnb2 ) = nb
320  60 CONTINUE
321 *
322 * Read the values of NX
323 *
324  READ( nin, fmt = * )( nxval( i ), i = 1, nnb )
325  DO 70 i = 1, nnb
326  IF( nxval( i ).LT.0 ) THEN
327  WRITE( nout, fmt = 9996 )' NX ', nxval( i ), 0
328  fatal = .true.
329  END IF
330  70 CONTINUE
331  IF( nnb.GT.0 )
332  $ WRITE( nout, fmt = 9993 )'NX ', ( nxval( i ), i = 1, nnb )
333 *
334 * Read the values of RANKVAL
335 *
336  READ( nin, fmt = * )nrank
337  IF( nn.LT.1 ) THEN
338  WRITE( nout, fmt = 9996 )' NRANK ', nrank, 1
339  nrank = 0
340  fatal = .true.
341  ELSE IF( nn.GT.maxin ) THEN
342  WRITE( nout, fmt = 9995 )' NRANK ', nrank, maxin
343  nrank = 0
344  fatal = .true.
345  END IF
346  READ( nin, fmt = * )( rankval( i ), i = 1, nrank )
347  DO i = 1, nrank
348  IF( rankval( i ).LT.0 ) THEN
349  WRITE( nout, fmt = 9996 )' RANK ', rankval( i ), 0
350  fatal = .true.
351  ELSE IF( rankval( i ).GT.100 ) THEN
352  WRITE( nout, fmt = 9995 )' RANK ', rankval( i ), 100
353  fatal = .true.
354  END IF
355  END DO
356  IF( nrank.GT.0 )
357  $ WRITE( nout, fmt = 9993 )'RANK % OF N',
358  $ ( rankval( i ), i = 1, nrank )
359 *
360 * Read the threshold value for the test ratios.
361 *
362  READ( nin, fmt = * )thresh
363  WRITE( nout, fmt = 9992 )thresh
364 *
365 * Read the flag that indicates whether to test the LAPACK routines.
366 *
367  READ( nin, fmt = * )tstchk
368 *
369 * Read the flag that indicates whether to test the driver routines.
370 *
371  READ( nin, fmt = * )tstdrv
372 *
373 * Read the flag that indicates whether to test the error exits.
374 *
375  READ( nin, fmt = * )tsterr
376 *
377  IF( fatal ) THEN
378  WRITE( nout, fmt = 9999 )
379  stop
380  END IF
381 *
382 * Calculate and print the machine dependent constants.
383 *
384  eps = slamch( 'Underflow threshold' )
385  WRITE( nout, fmt = 9991 )'underflow', eps
386  eps = slamch( 'Overflow threshold' )
387  WRITE( nout, fmt = 9991 )'overflow ', eps
388  eps = slamch( 'Epsilon' )
389  WRITE( nout, fmt = 9991 )'precision', eps
390  WRITE( nout, fmt = * )
391  nrhs = nsval( 1 )
392 *
393  80 CONTINUE
394 *
395 * Read a test path and the number of matrix types to use.
396 *
397  READ( nin, fmt = '(A72)', END = 140 )aline
398  path = aline( 1: 3 )
399  nmats = matmax
400  i = 3
401  90 CONTINUE
402  i = i + 1
403  IF( i.GT.72 )
404  $ GO TO 130
405  IF( aline( i: i ).EQ.' ' )
406  $ GO TO 90
407  nmats = 0
408  100 CONTINUE
409  c1 = aline( i: i )
410  DO 110 k = 1, 10
411  IF( c1.EQ.intstr( k: k ) ) THEN
412  ic = k - 1
413  GO TO 120
414  END IF
415  110 CONTINUE
416  GO TO 130
417  120 CONTINUE
418  nmats = nmats*10 + ic
419  i = i + 1
420  IF( i.GT.72 )
421  $ GO TO 130
422  GO TO 100
423  130 CONTINUE
424  c1 = path( 1: 1 )
425  c2 = path( 2: 3 )
426 *
427 * Check first character for correct precision.
428 *
429  IF( .NOT.lsame( c1, 'Complex precision' ) ) THEN
430  WRITE( nout, fmt = 9990 )path
431 *
432  ELSE IF( nmats.LE.0 ) THEN
433 *
434 * Check for a positive number of tests requested.
435 *
436  WRITE( nout, fmt = 9989 )path
437 *
438  ELSE IF( lsamen( 2, c2, 'GE' ) ) THEN
439 *
440 * GE: general matrices
441 *
442  ntypes = 11
443  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
444 *
445  IF( tstchk ) THEN
446  CALL cchkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
447  $ nsval, thresh, tsterr, lda, a( 1, 1 ),
448  $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
449  $ b( 1, 3 ), work, rwork, iwork, nout )
450  ELSE
451  WRITE( nout, fmt = 9989 )path
452  END IF
453 *
454  IF( tstdrv ) THEN
455  CALL cdrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
456  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
457  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
458  $ rwork, iwork, nout )
459  ELSE
460  WRITE( nout, fmt = 9988 )path
461  END IF
462 *
463  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
464 *
465 * GB: general banded matrices
466 *
467  la = ( 2*kdmax+1 )*nmax
468  lafac = ( 3*kdmax+1 )*nmax
469  ntypes = 8
470  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
471 *
472  IF( tstchk ) THEN
473  CALL cchkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
474  $ nsval, thresh, tsterr, a( 1, 1 ), la,
475  $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
476  $ b( 1, 3 ), work, rwork, iwork, nout )
477  ELSE
478  WRITE( nout, fmt = 9989 )path
479  END IF
480 *
481  IF( tstdrv ) THEN
482  CALL cdrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
483  $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
484  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
485  $ work, rwork, iwork, nout )
486  ELSE
487  WRITE( nout, fmt = 9988 )path
488  END IF
489 *
490  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
491 *
492 * GT: general tridiagonal matrices
493 *
494  ntypes = 12
495  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
496 *
497  IF( tstchk ) THEN
498  CALL cchkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
499  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
500  $ b( 1, 3 ), work, rwork, iwork, nout )
501  ELSE
502  WRITE( nout, fmt = 9989 )path
503  END IF
504 *
505  IF( tstdrv ) THEN
506  CALL cdrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
507  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
508  $ b( 1, 3 ), work, rwork, iwork, nout )
509  ELSE
510  WRITE( nout, fmt = 9988 )path
511  END IF
512 *
513  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
514 *
515 * PO: positive definite matrices
516 *
517  ntypes = 9
518  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
519 *
520  IF( tstchk ) THEN
521  CALL cchkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
522  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
523  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
524  $ work, rwork, nout )
525  ELSE
526  WRITE( nout, fmt = 9989 )path
527  END IF
528 *
529  IF( tstdrv ) THEN
530  CALL cdrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
531  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
532  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
533  $ rwork, nout )
534  ELSE
535  WRITE( nout, fmt = 9988 )path
536  END IF
537 *
538  ELSE IF( lsamen( 2, c2, 'PS' ) ) THEN
539 *
540 * PS: positive semi-definite matrices
541 *
542  ntypes = 9
543 *
544  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
545 *
546  IF( tstchk ) THEN
547  CALL cchkps( dotype, nn, nval, nnb2, nbval2, nrank,
548  $ rankval, thresh, tsterr, lda, a( 1, 1 ),
549  $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
550  $ nout )
551  ELSE
552  WRITE( nout, fmt = 9989 )path
553  END IF
554 *
555  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
556 *
557 * PP: positive definite packed matrices
558 *
559  ntypes = 9
560  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
561 *
562  IF( tstchk ) THEN
563  CALL cchkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
564  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
565  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
566  $ nout )
567  ELSE
568  WRITE( nout, fmt = 9989 )path
569  END IF
570 *
571  IF( tstdrv ) THEN
572  CALL cdrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
573  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
574  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
575  $ rwork, nout )
576  ELSE
577  WRITE( nout, fmt = 9988 )path
578  END IF
579 *
580  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
581 *
582 * PB: positive definite banded matrices
583 *
584  ntypes = 8
585  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
586 *
587  IF( tstchk ) THEN
588  CALL cchkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
589  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
590  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
591  $ work, rwork, nout )
592  ELSE
593  WRITE( nout, fmt = 9989 )path
594  END IF
595 *
596  IF( tstdrv ) THEN
597  CALL cdrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
598  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
599  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
600  $ rwork, nout )
601  ELSE
602  WRITE( nout, fmt = 9988 )path
603  END IF
604 *
605  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
606 *
607 * PT: positive definite tridiagonal matrices
608 *
609  ntypes = 12
610  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
611 *
612  IF( tstchk ) THEN
613  CALL cchkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
614  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
615  $ b( 1, 3 ), work, rwork, nout )
616  ELSE
617  WRITE( nout, fmt = 9989 )path
618  END IF
619 *
620  IF( tstdrv ) THEN
621  CALL cdrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
622  $ a( 1, 1 ), s, a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
623  $ b( 1, 3 ), work, rwork, nout )
624  ELSE
625  WRITE( nout, fmt = 9988 )path
626  END IF
627 *
628  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
629 *
630 * HE: Hermitian indefinite matrices,
631 * with partial (Bunch-Kaufman) pivoting algorithm
632 *
633  ntypes = 10
634  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
635 *
636  IF( tstchk ) THEN
637  CALL cchkhe( 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 cdrvhe( 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 cchkhe_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 cdrvhe_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 cchkhe_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 cdrvhe_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 cchkhe_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 cdrvhe_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 cchkhe_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 cdrvhe_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  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
763 *
764 * HP: Hermitian indefinite packed matrices,
765 * with partial (Bunch-Kaufman) pivoting algorithm
766 *
767  ntypes = 10
768  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
769 *
770  IF( tstchk ) THEN
771  CALL cchkhp( 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 cdrvhp( 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 cchksy( 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 cdrvsy( 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 cchksy_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 cdrvsy_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 cchksy_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 cdrvsy_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 cchksy_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 cdrvsy_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 cchksy_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 cdrvsy_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 cchksp( 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 cdrvsp( 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 cchktr( 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 cchktp( 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 cchktb( 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 cchkqr( 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 cchklq( 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 cchkql( 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 cchkrq( 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 cchkeq( 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 cchktz( 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 cchkq3( 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, nout )
1097  ELSE
1098  WRITE( nout, fmt = 9989 )path
1099  END IF
1100 *
1101  ELSE IF( lsamen( 2, c2, 'LS' ) ) THEN
1102 *
1103 * LS: Least squares drivers
1104 *
1105  ntypes = 6
1106  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
1107 *
1108  IF( tstdrv ) THEN
1109  CALL cdrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
1110  $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
1111  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
1112  $ s( 1 ), s( nmax+1 ), nout )
1113  ELSE
1114  WRITE( nout, fmt = 9989 )path
1115  END IF
1116 *
1117  ELSE IF( lsamen( 2, c2, 'QT' ) ) THEN
1118 *
1119 * QT: QRT routines for general matrices
1120 *
1121  IF( tstchk ) THEN
1122  CALL cchkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
1123  $ nbval, nout )
1124  ELSE
1125  WRITE( nout, fmt = 9989 )path
1126  END IF
1127 *
1128  ELSE IF( lsamen( 2, c2, 'QX' ) ) THEN
1129 *
1130 * QX: QRT routines for triangular-pentagonal matrices
1131 *
1132  IF( tstchk ) THEN
1133  CALL cchkqrtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1134  $ nbval, nout )
1135  ELSE
1136  WRITE( nout, fmt = 9989 )path
1137  END IF
1138 *
1139  ELSE IF( lsamen( 2, c2, 'TQ' ) ) THEN
1140 *
1141 * TQ: LQT routines for general matrices
1142 *
1143  IF( tstchk ) THEN
1144  CALL cchklqt( thresh, tsterr, nm, mval, nn, nval, nnb,
1145  $ nbval, nout )
1146  ELSE
1147  WRITE( nout, fmt = 9989 )path
1148  END IF
1149 *
1150  ELSE IF( lsamen( 2, c2, 'XQ' ) ) THEN
1151 *
1152 * XQ: LQT routines for triangular-pentagonal matrices
1153 *
1154  IF( tstchk ) THEN
1155  CALL cchklqtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1156  $ nbval, nout )
1157  ELSE
1158  WRITE( nout, fmt = 9989 )path
1159  END IF
1160 *
1161  ELSE IF( lsamen( 2, c2, 'TS' ) ) THEN
1162 *
1163 * TS: QR routines for tall-skinny matrices
1164 *
1165  IF( tstchk ) THEN
1166  CALL cchktsqr( thresh, tsterr, nm, mval, nn, nval, nnb,
1167  $ nbval, nout )
1168  ELSE
1169  WRITE( nout, fmt = 9989 )path
1170  END IF
1171 *
1172  ELSE IF( lsamen( 2, c2, 'HH' ) ) THEN
1173 *
1174 * HH: Householder reconstruction for tall-skinny matrices
1175 *
1176  IF( tstchk ) THEN
1177  CALL cchkunhr_col( thresh, tsterr, nm, mval, nn, nval, nnb,
1178  $ nbval, nout )
1179  ELSE
1180  WRITE( nout, fmt = 9989 ) path
1181  END IF
1182 *
1183  ELSE
1184 *
1185  WRITE( nout, fmt = 9990 )path
1186  END IF
1187 *
1188 * Go back to get another input line.
1189 *
1190  GO TO 80
1191 *
1192 * Branch to this line when the last record is read.
1193 *
1194  140 CONTINUE
1195  CLOSE ( nin )
1196  s2 = second( )
1197  WRITE( nout, fmt = 9998 )
1198  WRITE( nout, fmt = 9997 )s2 - s1
1199 *
1200  9999 FORMAT( / ' Execution not attempted due to input errors' )
1201  9998 FORMAT( / ' End of tests' )
1202  9997 FORMAT( ' Total time used = ', f12.2, ' seconds', / )
1203  9996 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be >=',
1204  $ i6 )
1205  9995 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be <=',
1206  $ i6 )
1207  9994 FORMAT( ' Tests of the COMPLEX LAPACK routines ',
1208  $ / ' LAPACK VERSION ', i1, '.', i1, '.', i1,
1209  $ / / ' The following parameter values will be used:' )
1210  9993 FORMAT( 4x, a4, ': ', 10i6, / 11x, 10i6 )
1211  9992 FORMAT( / ' Routines pass computational tests if test ratio is ',
1212  $ 'less than', f8.2, / )
1213  9991 FORMAT( ' Relative machine ', a, ' is taken to be', e16.6 )
1214  9990 FORMAT( / 1x, a3, ': Unrecognized path name' )
1215  9989 FORMAT( / 1x, a3, ' routines were not tested' )
1216  9988 FORMAT( / 1x, a3, ' driver routines were not tested' )
1217 *
1218 * End of CCHKAA
1219 *
1220  END
cchklq
subroutine cchklq(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC, B, X, XACT, TAU, WORK, RWORK, NOUT)
CCHKLQ
Definition: cchklq.f:198
cdrvpb
subroutine cdrvpb(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
CDRVPB
Definition: cdrvpb.f:161
lsamen
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
cchkunhr_col
subroutine cchkunhr_col(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKUNHR_COL
Definition: cchkunhr_col.f:107
cdrvsy_rook
subroutine cdrvsy_rook(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSY_ROOK
Definition: cdrvsy_rook.f:154
cchkhe_rook
subroutine cchkhe_rook(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHE_ROOK
Definition: cchkhe_rook.f:174
cchkpp
subroutine cchkpp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
CCHKPP
Definition: cchkpp.f:161
cchkps
subroutine cchkps(DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL, THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK, RWORK, NOUT)
CCHKPS
Definition: cchkps.f:156
cchkhe_aa_2stage
subroutine cchkhe_aa_2stage(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHE_AA_2STAGE
Definition: cchkhe_aa_2stage.f:175
cchklqt
subroutine cchklqt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKLQT
Definition: cchklqt.f:104
cdrvhe_aa_2stage
subroutine cdrvhe_aa_2stage(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHE_AA_2STAGE
Definition: cdrvhe_aa_2stage.f:157
cchkpt
subroutine cchkpt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
CCHKPT
Definition: cchkpt.f:149
cchktr
subroutine cchktr(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AINV, B, X, XACT, WORK, RWORK, NOUT)
CCHKTR
Definition: cchktr.f:165
cchkpo
subroutine cchkpo(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
CCHKPO
Definition: cchkpo.f:170
cdrvsp
subroutine cdrvsp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSP
Definition: cdrvsp.f:159
cchksy_rook
subroutine cchksy_rook(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSY_ROOK
Definition: cchksy_rook.f:174
cdrvsy_aa
subroutine cdrvsy_aa(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSY_AA
Definition: cdrvsy_aa.f:157
cdrvge
subroutine cdrvge(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, IWORK, NOUT)
CDRVGE
Definition: cdrvge.f:166
cdrvpp
subroutine cdrvpp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
CDRVPP
Definition: cdrvpp.f:161
cchksy_aa
subroutine cchksy_aa(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSY_AA
Definition: cchksy_aa.f:174
cdrvsy_rk
subroutine cdrvsy_rk(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSY_RK
Definition: cdrvsy_rk.f:159
cchkhp
subroutine cchkhp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHP
Definition: cchkhp.f:166
cchkhe_rk
subroutine cchkhe_rk(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHE_RK
Definition: cchkhe_rk.f:179
second
real function second()
SECOND Using ETIME
Definition: second_EXT_ETIME.f:37
cchktsqr
subroutine cchktsqr(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKQRT
Definition: cchktsqr.f:104
cchkgt
subroutine cchkgt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKGT
Definition: cchkgt.f:149
cdrvpo
subroutine cdrvpo(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, NOUT)
CDRVPO
Definition: cdrvpo.f:161
cchktb
subroutine cchktb(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AB, AINV, B, X, XACT, WORK, RWORK, NOUT)
CCHKTB
Definition: cchktb.f:151
cchklqtp
subroutine cchklqtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKLQTP
Definition: cchklqtp.f:104
cchkpb
subroutine cchkpb(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, NOUT)
CCHKPB
Definition: cchkpb.f:170
cchksy_rk
subroutine cchksy_rk(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSY_RK
Definition: cchksy_rk.f:179
cchkeq
subroutine cchkeq(THRESH, NOUT)
CCHKEQ
Definition: cchkeq.f:56
cchkge
subroutine cchkge(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKGE
Definition: cchkge.f:188
cchkrq
subroutine cchkrq(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)
CCHKRQ
Definition: cchkrq.f:203
cchkgb
subroutine cchkgb(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, A, LA, AFAC, LAFAC, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKGB
Definition: cchkgb.f:193
cchktz
subroutine cchktz(DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A, COPYA, S, TAU, WORK, RWORK, NOUT)
CCHKTZ
Definition: cchktz.f:139
cdrvhe
subroutine cdrvhe(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHE
Definition: cdrvhe.f:155
cchkqr
subroutine cchkqr(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)
CCHKQR
Definition: cchkqr.f:203
cchkhe_aa
subroutine cchkhe_aa(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHE_AA
Definition: cchkhe_aa.f:174
cdrvhe_rk
subroutine cdrvhe_rk(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, E, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHE_RK
Definition: cdrvhe_rk.f:160
cchkqrtp
subroutine cchkqrtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKQRTP
Definition: cchkqrtp.f:104
cdrvhe_aa
subroutine cdrvhe_aa(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHE_AA
Definition: cdrvhe_aa.f:155
cdrvhp
subroutine cdrvhp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHP
Definition: cdrvhp.f:159
cchkaa
program cchkaa
CCHKAA
Definition: cchkaa.f:118
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
cchksy_aa_2stage
subroutine cchksy_aa_2stage(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSY_AA_2STAGE
Definition: cchksy_aa_2stage.f:174
slamch
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:70
alareq
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
cdrvgt
subroutine cdrvgt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVGT
Definition: cdrvgt.f:141
cchkq3
subroutine cchkq3(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, THRESH, A, COPYA, S, TAU, WORK, RWORK, IWORK, NOUT)
CCHKQ3
Definition: cchkq3.f:160
cchkhe
subroutine cchkhe(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKHE
Definition: cchkhe.f:173
cchksy
subroutine cchksy(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSY
Definition: cchksy.f:173
cdrvls
subroutine cdrvls(DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB, NBVAL, NXVAL, THRESH, TSTERR, A, COPYA, B, COPYB, C, S, COPYS, NOUT)
CDRVLS
Definition: cdrvls.f:194
cchkqrt
subroutine cchkqrt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
CCHKQRT
Definition: cchkqrt.f:104
cchksp
subroutine cchksp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CCHKSP
Definition: cchksp.f:166
cchkql
subroutine cchkql(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC, B, X, XACT, TAU, WORK, RWORK, NOUT)
CCHKQL
Definition: cchkql.f:198
cdrvpt
subroutine cdrvpt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
CDRVPT
Definition: cdrvpt.f:142
cdrvsy
subroutine cdrvsy(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSY
Definition: cdrvsy.f:155
cdrvsy_aa_2stage
subroutine cdrvsy_aa_2stage(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVSY_AA_2STAGE
Definition: cdrvsy_aa_2stage.f:157
cdrvgb
subroutine cdrvgb(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, LA, AFB, LAFB, ASAV, B, BSAV, X, XACT, S, WORK, RWORK, IWORK, NOUT)
CDRVGB
Definition: cdrvgb.f:174
ilaver
subroutine ilaver(VERS_MAJOR, VERS_MINOR, VERS_PATCH)
ILAVER returns the LAPACK version.
Definition: ilaver.f:53
cchktp
subroutine cchktp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AP, AINVP, B, X, XACT, WORK, RWORK, NOUT)
CCHKTP
Definition: cchktp.f:153
cdrvhe_rook
subroutine cdrvhe_rook(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
CDRVHE_ROOK
Definition: cdrvhe_rook.f:155