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