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