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