LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dchkaa.F
Go to the documentation of this file.
1*> \brief \b DCHKAA
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 DCHKAA
12*
13*
14*> \par Purpose:
15* =============
16*>
17*> \verbatim
18*>
19*> DCHKAA is the main test program for the DOUBLE PRECISION LAPACK
20*> linear equation 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 40 lines:
28*> Data file for testing DOUBLE PRECISION LAPACK linear eqn. 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*> 20.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*> DGE 11 List types on next line if 0 < NTYPES < 11
45*> DGB 8 List types on next line if 0 < NTYPES < 8
46*> DGT 12 List types on next line if 0 < NTYPES < 12
47*> DPO 9 List types on next line if 0 < NTYPES < 9
48*> DPS 9 List types on next line if 0 < NTYPES < 9
49*> DPP 9 List types on next line if 0 < NTYPES < 9
50*> DPB 8 List types on next line if 0 < NTYPES < 8
51*> DPT 12 List types on next line if 0 < NTYPES < 12
52*> DSY 10 List types on next line if 0 < NTYPES < 10
53*> DSR 10 List types on next line if 0 < NTYPES < 10
54*> DSK 10 List types on next line if 0 < NTYPES < 10
55*> DSA 10 List types on next line if 0 < NTYPES < 10
56*> DS2 10 List types on next line if 0 < NTYPES < 10
57*> DSP 10 List types on next line if 0 < NTYPES < 10
58*> DTR 18 List types on next line if 0 < NTYPES < 18
59*> DTP 18 List types on next line if 0 < NTYPES < 18
60*> DTB 17 List types on next line if 0 < NTYPES < 17
61*> DQR 8 List types on next line if 0 < NTYPES < 8
62*> DRQ 8 List types on next line if 0 < NTYPES < 8
63*> DLQ 8 List types on next line if 0 < NTYPES < 8
64*> DQL 8 List types on next line if 0 < NTYPES < 8
65*> DQP 6 List types on next line if 0 < NTYPES < 6
66*> DQK 19 List types on next line if 0 < NTYPES < 19
67*> DTZ 3 List types on next line if 0 < NTYPES < 3
68*> DLS 6 List types on next line if 0 < NTYPES < 6
69*> DEQ
70*> DQT
71*> DQX
72*> DTQ
73*> DXQ
74*> DTS
75*> DHH
76*> \endverbatim
77*
78* Parameters:
79* ==========
80*
81*> \verbatim
82*> NMAX INTEGER
83*> The maximum allowable value for M and N.
84*>
85*> MAXIN INTEGER
86*> The number of different values that can be used for each of
87*> M, N, NRHS, NB, NX and RANK
88*>
89*> MAXRHS INTEGER
90*> The maximum number of right hand sides
91*>
92*> MATMAX INTEGER
93*> The maximum number of matrix types to use for testing
94*>
95*> NIN INTEGER
96*> The unit number for input
97*>
98*> NOUT INTEGER
99*> The unit number for output
100*> \endverbatim
101*
102* Authors:
103* ========
104*
105*> \author Univ. of Tennessee
106*> \author Univ. of California Berkeley
107*> \author Univ. of Colorado Denver
108*> \author NAG Ltd.
109*
110*> \ingroup double_lin
111*
112* =====================================================================
113 PROGRAM dchkaa
114*
115* -- LAPACK test routine --
116* -- LAPACK is a software package provided by Univ. of Tennessee, --
117* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118*
119* =====================================================================
120*
121* .. Parameters ..
122 INTEGER nmax
123 parameter( nmax = 132 )
124 INTEGER maxin
125 parameter( maxin = 12 )
126 INTEGER maxrhs
127 parameter( maxrhs = 16 )
128 INTEGER matmax
129 parameter( matmax = 30 )
130 INTEGER nin, nout
131 parameter( nin = 5, nout = 6 )
132 INTEGER kdmax
133 parameter( kdmax = nmax+( nmax+1 ) / 4 )
134* ..
135* .. Local Scalars ..
136 LOGICAL fatal, tstchk, tstdrv, tsterr
137 CHARACTER c1
138 CHARACTER*2 c2
139 CHARACTER*3 path
140 CHARACTER*10 intstr
141 CHARACTER*72 aline
142 INTEGER i, ic, j, k, la, lafac, lda, nb, nm, nmats, nn,
143 $ nnb, nnb2, nns, nrhs, ntypes, nrank,
144 $ vers_major, vers_minor, vers_patch
145 DOUBLE PRECISION eps, s1, s2, threq, thresh
146* ..
147* .. Local Arrays ..
148 LOGICAL dotype( matmax )
149 INTEGER iwork( 25*nmax ), mval( maxin ),
150 $ nbval( maxin ), nbval2( maxin ),
151 $ nsval( maxin ), nval( maxin ), nxval( maxin ),
152 $ rankval( maxin ), piv( nmax )
153* ..
154* .. Allocatable Arrays ..
155 INTEGER allocatestatus
156 DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: rwork, s
157 DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: e
158 DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: a, b, work
159* ..
160* .. External Functions ..
161 LOGICAL lsame, lsamen
162 DOUBLE PRECISION dlamch, dsecnd
163 EXTERNAL lsame, lsamen, dlamch, dsecnd
164* ..
165* .. External Subroutines ..
166 EXTERNAL alareq, dchkeq, dchkgb, dchkge, dchkgt, dchklq,
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* ..
193* .. Allocate memory dynamically ..
194*
195 ALLOCATE ( a( ( kdmax+1 )*nmax, 7 ), stat = allocatestatus )
196 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
197 ALLOCATE ( b( nmax*maxrhs, 4 ), stat = allocatestatus )
198 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
199 ALLOCATE ( work( nmax, 3*nmax+maxrhs+30 ), stat = allocatestatus )
200 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
201 ALLOCATE ( e( nmax ), stat = allocatestatus )
202 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
203 ALLOCATE ( s( 2*nmax ), stat = allocatestatus )
204 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
205 ALLOCATE ( rwork( 5*nmax+2*maxrhs ), stat = allocatestatus )
206 IF (allocatestatus /= 0) stop "*** Not enough memory ***"
207*
208* .. Executable Statements ..
209*
210 s1 = dsecnd( )
211 lda = nmax
212 fatal = .false.
213*
214* Read a dummy line.
215*
216 READ( nin, fmt = * )
217*
218* Report values of parameters.
219*
220 CALL ilaver( vers_major, vers_minor, vers_patch )
221 WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
222*
223* Read the values of M
224*
225 READ( nin, fmt = * )nm
226 IF( nm.LT.1 ) THEN
227 WRITE( nout, fmt = 9996 )' NM ', nm, 1
228 nm = 0
229 fatal = .true.
230 ELSE IF( nm.GT.maxin ) THEN
231 WRITE( nout, fmt = 9995 )' NM ', nm, maxin
232 nm = 0
233 fatal = .true.
234 END IF
235 READ( nin, fmt = * )( mval( i ), i = 1, nm )
236 DO 10 i = 1, nm
237 IF( mval( i ).LT.0 ) THEN
238 WRITE( nout, fmt = 9996 )' M ', mval( i ), 0
239 fatal = .true.
240 ELSE IF( mval( i ).GT.nmax ) THEN
241 WRITE( nout, fmt = 9995 )' M ', mval( i ), nmax
242 fatal = .true.
243 END IF
244 10 CONTINUE
245 IF( nm.GT.0 )
246 $ WRITE( nout, fmt = 9993 )'M ', ( mval( i ), i = 1, nm )
247*
248* Read the values of N
249*
250 READ( nin, fmt = * )nn
251 IF( nn.LT.1 ) THEN
252 WRITE( nout, fmt = 9996 )' NN ', nn, 1
253 nn = 0
254 fatal = .true.
255 ELSE IF( nn.GT.maxin ) THEN
256 WRITE( nout, fmt = 9995 )' NN ', nn, maxin
257 nn = 0
258 fatal = .true.
259 END IF
260 READ( nin, fmt = * )( nval( i ), i = 1, nn )
261 DO 20 i = 1, nn
262 IF( nval( i ).LT.0 ) THEN
263 WRITE( nout, fmt = 9996 )' N ', nval( i ), 0
264 fatal = .true.
265 ELSE IF( nval( i ).GT.nmax ) THEN
266 WRITE( nout, fmt = 9995 )' N ', nval( i ), nmax
267 fatal = .true.
268 END IF
269 20 CONTINUE
270 IF( nn.GT.0 )
271 $ WRITE( nout, fmt = 9993 )'N ', ( nval( i ), i = 1, nn )
272*
273* Read the values of NRHS
274*
275 READ( nin, fmt = * )nns
276 IF( nns.LT.1 ) THEN
277 WRITE( nout, fmt = 9996 )' NNS', nns, 1
278 nns = 0
279 fatal = .true.
280 ELSE IF( nns.GT.maxin ) THEN
281 WRITE( nout, fmt = 9995 )' NNS', nns, maxin
282 nns = 0
283 fatal = .true.
284 END IF
285 READ( nin, fmt = * )( nsval( i ), i = 1, nns )
286 DO 30 i = 1, nns
287 IF( nsval( i ).LT.0 ) THEN
288 WRITE( nout, fmt = 9996 )'NRHS', nsval( i ), 0
289 fatal = .true.
290 ELSE IF( nsval( i ).GT.maxrhs ) THEN
291 WRITE( nout, fmt = 9995 )'NRHS', nsval( i ), maxrhs
292 fatal = .true.
293 END IF
294 30 CONTINUE
295 IF( nns.GT.0 )
296 $ WRITE( nout, fmt = 9993 )'NRHS', ( nsval( i ), i = 1, nns )
297*
298* Read the values of NB
299*
300 READ( nin, fmt = * )nnb
301 IF( nnb.LT.1 ) THEN
302 WRITE( nout, fmt = 9996 )'NNB ', nnb, 1
303 nnb = 0
304 fatal = .true.
305 ELSE IF( nnb.GT.maxin ) THEN
306 WRITE( nout, fmt = 9995 )'NNB ', nnb, maxin
307 nnb = 0
308 fatal = .true.
309 END IF
310 READ( nin, fmt = * )( nbval( i ), i = 1, nnb )
311 DO 40 i = 1, nnb
312 IF( nbval( i ).LT.0 ) THEN
313 WRITE( nout, fmt = 9996 )' NB ', nbval( i ), 0
314 fatal = .true.
315 END IF
316 40 CONTINUE
317 IF( nnb.GT.0 )
318 $ WRITE( nout, fmt = 9993 )'NB ', ( nbval( i ), i = 1, nnb )
319*
320* Set NBVAL2 to be the set of unique values of NB
321*
322 nnb2 = 0
323 DO 60 i = 1, nnb
324 nb = nbval( i )
325 DO 50 j = 1, nnb2
326 IF( nb.EQ.nbval2( j ) )
327 $ GO TO 60
328 50 CONTINUE
329 nnb2 = nnb2 + 1
330 nbval2( nnb2 ) = nb
331 60 CONTINUE
332*
333* Read the values of NX
334*
335 READ( nin, fmt = * )( nxval( i ), i = 1, nnb )
336 DO 70 i = 1, nnb
337 IF( nxval( i ).LT.0 ) THEN
338 WRITE( nout, fmt = 9996 )' NX ', nxval( i ), 0
339 fatal = .true.
340 END IF
341 70 CONTINUE
342 IF( nnb.GT.0 )
343 $ WRITE( nout, fmt = 9993 )'NX ', ( nxval( i ), i = 1, nnb )
344*
345* Read the values of RANKVAL
346*
347 READ( nin, fmt = * )nrank
348 IF( nn.LT.1 ) THEN
349 WRITE( nout, fmt = 9996 )' NRANK ', nrank, 1
350 nrank = 0
351 fatal = .true.
352 ELSE IF( nn.GT.maxin ) THEN
353 WRITE( nout, fmt = 9995 )' NRANK ', nrank, maxin
354 nrank = 0
355 fatal = .true.
356 END IF
357 READ( nin, fmt = * )( rankval( i ), i = 1, nrank )
358 DO i = 1, nrank
359 IF( rankval( i ).LT.0 ) THEN
360 WRITE( nout, fmt = 9996 )' RANK ', rankval( i ), 0
361 fatal = .true.
362 ELSE IF( rankval( i ).GT.100 ) THEN
363 WRITE( nout, fmt = 9995 )' RANK ', rankval( i ), 100
364 fatal = .true.
365 END IF
366 END DO
367 IF( nrank.GT.0 )
368 $ WRITE( nout, fmt = 9993 )'RANK % OF N',
369 $ ( rankval( i ), i = 1, nrank )
370*
371* Read the threshold value for the test ratios.
372*
373 READ( nin, fmt = * )thresh
374 WRITE( nout, fmt = 9992 )thresh
375*
376* Read the flag that indicates whether to test the LAPACK routines.
377*
378 READ( nin, fmt = * )tstchk
379*
380* Read the flag that indicates whether to test the driver routines.
381*
382 READ( nin, fmt = * )tstdrv
383*
384* Read the flag that indicates whether to test the error exits.
385*
386 READ( nin, fmt = * )tsterr
387*
388 IF( fatal ) THEN
389 WRITE( nout, fmt = 9999 )
390 stop
391 END IF
392*
393* Calculate and print the machine dependent constants.
394*
395 eps = dlamch( 'Underflow threshold' )
396 WRITE( nout, fmt = 9991 )'underflow', eps
397 eps = dlamch( 'Overflow threshold' )
398 WRITE( nout, fmt = 9991 )'overflow ', eps
399 eps = dlamch( 'Epsilon' )
400 WRITE( nout, fmt = 9991 )'precision', eps
401 WRITE( nout, fmt = * )
402*
403 80 CONTINUE
404*
405* Read a test path and the number of matrix types to use.
406*
407 READ( nin, fmt = '(A72)', END = 140 )aline
408 path = aline( 1: 3 )
409 nmats = matmax
410 i = 3
411 90 CONTINUE
412 i = i + 1
413 IF( i.GT.72 ) THEN
414 nmats = matmax
415 GO TO 130
416 END IF
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 nrhs = nsval( 1 )
439*
440* Check first character for correct precision.
441*
442 IF( .NOT.lsame( c1, 'Double precision' ) ) THEN
443 WRITE( nout, fmt = 9990 )path
444*
445 ELSE IF( nmats.LE.0 ) THEN
446*
447* Check for a positive number of tests requested.
448*
449 WRITE( nout, fmt = 9989 )path
450*
451 ELSE IF( lsamen( 2, c2, 'GE' ) ) THEN
452*
453* GE: general matrices
454*
455 ntypes = 11
456 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
457*
458 IF( tstchk ) THEN
459 CALL dchkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
460 $ nsval, thresh, tsterr, lda, a( 1, 1 ),
461 $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
462 $ b( 1, 3 ), work, rwork, iwork, nout )
463 ELSE
464 WRITE( nout, fmt = 9989 )path
465 END IF
466*
467 IF( tstdrv ) THEN
468 CALL ddrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
469 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
470 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
471 $ rwork, iwork, nout )
472 ELSE
473 WRITE( nout, fmt = 9988 )path
474 END IF
475*
476 ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
477*
478* GB: general banded matrices
479*
480 la = ( 2*kdmax+1 )*nmax
481 lafac = ( 3*kdmax+1 )*nmax
482 ntypes = 8
483 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
484*
485 IF( tstchk ) THEN
486 CALL dchkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
487 $ nsval, thresh, tsterr, a( 1, 1 ), la,
488 $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
489 $ b( 1, 3 ), work, rwork, iwork, nout )
490 ELSE
491 WRITE( nout, fmt = 9989 )path
492 END IF
493*
494 IF( tstdrv ) THEN
495 CALL ddrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
496 $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
497 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
498 $ work, rwork, iwork, nout )
499 ELSE
500 WRITE( nout, fmt = 9988 )path
501 END IF
502*
503 ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
504*
505* GT: general tridiagonal matrices
506*
507 ntypes = 12
508 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
509*
510 IF( tstchk ) THEN
511 CALL dchkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
512 $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
513 $ b( 1, 3 ), work, rwork, iwork, nout )
514 ELSE
515 WRITE( nout, fmt = 9989 )path
516 END IF
517*
518 IF( tstdrv ) THEN
519 CALL ddrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
520 $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
521 $ b( 1, 3 ), work, rwork, iwork, nout )
522 ELSE
523 WRITE( nout, fmt = 9988 )path
524 END IF
525*
526 ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
527*
528* PO: positive definite matrices
529*
530 ntypes = 9
531 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
532*
533 IF( tstchk ) THEN
534 CALL dchkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
535 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
536 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
537 $ work, rwork, iwork, nout )
538 ELSE
539 WRITE( nout, fmt = 9989 )path
540 END IF
541*
542 IF( tstdrv ) THEN
543 CALL ddrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
544 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
545 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
546 $ rwork, iwork, nout )
547 ELSE
548 WRITE( nout, fmt = 9988 )path
549 END IF
550*
551 ELSE IF( lsamen( 2, c2, 'PS' ) ) THEN
552*
553* PS: positive semi-definite matrices
554*
555 ntypes = 9
556*
557 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
558*
559 IF( tstchk ) THEN
560 CALL dchkps( dotype, nn, nval, nnb2, nbval2, nrank,
561 $ rankval, thresh, tsterr, lda, a( 1, 1 ),
562 $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
563 $ nout )
564 ELSE
565 WRITE( nout, fmt = 9989 )path
566 END IF
567*
568 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
569*
570* PP: positive definite packed matrices
571*
572 ntypes = 9
573 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
574*
575 IF( tstchk ) THEN
576 CALL dchkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
577 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
578 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
579 $ iwork, nout )
580 ELSE
581 WRITE( nout, fmt = 9989 )path
582 END IF
583*
584 IF( tstdrv ) THEN
585 CALL ddrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
586 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
587 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
588 $ rwork, iwork, nout )
589 ELSE
590 WRITE( nout, fmt = 9988 )path
591 END IF
592*
593 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
594*
595* PB: positive definite banded matrices
596*
597 ntypes = 8
598 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
599*
600 IF( tstchk ) THEN
601 CALL dchkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
602 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
603 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
604 $ work, rwork, iwork, nout )
605 ELSE
606 WRITE( nout, fmt = 9989 )path
607 END IF
608*
609 IF( tstdrv ) THEN
610 CALL ddrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
611 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
612 $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
613 $ rwork, iwork, nout )
614 ELSE
615 WRITE( nout, fmt = 9988 )path
616 END IF
617*
618 ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
619*
620* PT: positive definite tridiagonal matrices
621*
622 ntypes = 12
623 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
624*
625 IF( tstchk ) THEN
626 CALL dchkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
627 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
628 $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
629 ELSE
630 WRITE( nout, fmt = 9989 )path
631 END IF
632*
633 IF( tstdrv ) THEN
634 CALL ddrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
635 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
636 $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
637 ELSE
638 WRITE( nout, fmt = 9988 )path
639 END IF
640*
641 ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
642*
643* SY: symmetric indefinite matrices,
644* with partial (Bunch-Kaufman) pivoting algorithm
645*
646 ntypes = 10
647 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
648*
649 IF( tstchk ) THEN
650 CALL dchksy( dotype, nn, nval, nnb2, nbval2, nns, nsval,
651 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
652 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
653 $ work, rwork, iwork, nout )
654 ELSE
655 WRITE( nout, fmt = 9989 )path
656 END IF
657*
658 IF( tstdrv ) THEN
659 CALL ddrvsy( dotype, nn, nval, nrhs, thresh, tsterr, lda,
660 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
661 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
662 $ nout )
663 ELSE
664 WRITE( nout, fmt = 9988 )path
665 END IF
666*
667 ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
668*
669* SR: symmetric indefinite matrices,
670* with bounded Bunch-Kaufman (rook) pivoting algorithm
671*
672 ntypes = 10
673 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
674*
675 IF( tstchk ) THEN
676 CALL dchksy_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
677 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
678 $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
679 $ work, rwork, iwork, nout )
680 ELSE
681 WRITE( nout, fmt = 9989 )path
682 END IF
683*
684 IF( tstdrv ) THEN
685 CALL ddrvsy_rook( dotype, nn, nval, nrhs, thresh, tsterr,
686 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
687 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
688 $ work, rwork, iwork, nout )
689 ELSE
690 WRITE( nout, fmt = 9988 )path
691 END IF
692*
693 ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
694*
695* SK: symmetric indefinite matrices,
696* with bounded Bunch-Kaufman (rook) pivoting algorithm,
697* different matrix storage format than SR path version.
698*
699 ntypes = 10
700 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
701*
702 IF( tstchk ) THEN
703 CALL dchksy_rk( dotype, nn, nval, nnb2, nbval2, nns, nsval,
704 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
705 $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
706 $ b( 1, 3 ), work, rwork, iwork, nout )
707 ELSE
708 WRITE( nout, fmt = 9989 )path
709 END IF
710*
711 IF( tstdrv ) THEN
712 CALL ddrvsy_rk( dotype, nn, nval, nrhs, thresh, tsterr,
713 $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
714 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
715 $ work, rwork, iwork, nout )
716 ELSE
717 WRITE( nout, fmt = 9988 )path
718 END IF
719*
720 ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
721*
722* SA: symmetric indefinite matrices,
723* with partial (Aasen's) pivoting algorithm
724*
725 ntypes = 10
726 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
727*
728 IF( tstchk ) THEN
729 CALL dchksy_aa( dotype, nn, nval, nnb2, nbval2, nns,
730 $ nsval, thresh, tsterr, lda,
731 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
732 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
733 $ work, rwork, iwork, nout )
734 ELSE
735 WRITE( nout, fmt = 9989 )path
736 END IF
737*
738 IF( tstdrv ) THEN
739 CALL ddrvsy_aa( dotype, nn, nval, nrhs, thresh, tsterr,
740 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
741 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
742 $ work, rwork, iwork, nout )
743 ELSE
744 WRITE( nout, fmt = 9988 )path
745 END IF
746*
747*
748 ELSE IF( lsamen( 2, c2, 'S2' ) ) THEN
749*
750* SA: symmetric indefinite matrices,
751* with partial (Aasen's) pivoting algorithm
752*
753 ntypes = 10
754 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
755*
756 IF( tstchk ) THEN
757 CALL dchksy_aa_2stage( dotype, nn, nval, nnb2, nbval2,
758 $ nns, nsval, thresh, tsterr, lda,
759 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
760 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
761 $ work, rwork, iwork, nout )
762 ELSE
763 WRITE( nout, fmt = 9989 )path
764 END IF
765*
766 IF( tstdrv ) THEN
767 CALL ddrvsy_aa_2stage(
768 $ dotype, nn, nval, nrhs, thresh, tsterr,
769 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
770 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
771 $ work, rwork, iwork, nout )
772 ELSE
773 WRITE( nout, fmt = 9988 )path
774 END IF
775*
776*
777 ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
778*
779* SP: symmetric indefinite packed matrices,
780* with partial (Bunch-Kaufman) pivoting algorithm
781*
782 ntypes = 10
783 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
784*
785 IF( tstchk ) THEN
786 CALL dchksp( dotype, nn, nval, nns, nsval, thresh, tsterr,
787 $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
788 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
789 $ iwork, nout )
790 ELSE
791 WRITE( nout, fmt = 9989 )path
792 END IF
793*
794 IF( tstdrv ) THEN
795 CALL ddrvsp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
796 $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
797 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
798 $ nout )
799 ELSE
800 WRITE( nout, fmt = 9988 )path
801 END IF
802*
803 ELSE IF( lsamen( 2, c2, 'TR' ) ) THEN
804*
805* TR: triangular matrices
806*
807 ntypes = 18
808 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
809*
810 IF( tstchk ) THEN
811 CALL dchktr( dotype, nn, nval, nnb2, nbval2, nns, nsval,
812 $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
813 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
814 $ iwork, nout )
815 ELSE
816 WRITE( nout, fmt = 9989 )path
817 END IF
818*
819 ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
820*
821* TP: triangular packed matrices
822*
823 ntypes = 18
824 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
825*
826 IF( tstchk ) THEN
827 CALL dchktp( dotype, nn, nval, nns, nsval, thresh, tsterr,
828 $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
829 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
830 $ nout )
831 ELSE
832 WRITE( nout, fmt = 9989 )path
833 END IF
834*
835 ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
836*
837* TB: triangular banded matrices
838*
839 ntypes = 17
840 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
841*
842 IF( tstchk ) THEN
843 CALL dchktb( dotype, nn, nval, nns, nsval, thresh, tsterr,
844 $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
845 $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
846 $ nout )
847 ELSE
848 WRITE( nout, fmt = 9989 )path
849 END IF
850*
851 ELSE IF( lsamen( 2, c2, 'QR' ) ) THEN
852*
853* QR: QR factorization
854*
855 ntypes = 8
856 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
857*
858 IF( tstchk ) THEN
859 CALL dchkqr( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
860 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
861 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
862 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
863 $ work, rwork, iwork, nout )
864 ELSE
865 WRITE( nout, fmt = 9989 )path
866 END IF
867*
868 ELSE IF( lsamen( 2, c2, 'LQ' ) ) THEN
869*
870* LQ: LQ factorization
871*
872 ntypes = 8
873 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
874*
875 IF( tstchk ) THEN
876 CALL dchklq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
877 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
878 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
879 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
880 $ work, rwork, nout )
881 ELSE
882 WRITE( nout, fmt = 9989 )path
883 END IF
884*
885 ELSE IF( lsamen( 2, c2, 'QL' ) ) THEN
886*
887* QL: QL factorization
888*
889 ntypes = 8
890 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
891*
892 IF( tstchk ) THEN
893 CALL dchkql( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
894 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
895 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
896 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
897 $ work, rwork, nout )
898 ELSE
899 WRITE( nout, fmt = 9989 )path
900 END IF
901*
902 ELSE IF( lsamen( 2, c2, 'RQ' ) ) THEN
903*
904* RQ: RQ factorization
905*
906 ntypes = 8
907 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
908*
909 IF( tstchk ) THEN
910 CALL dchkrq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
911 $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
912 $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
913 $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
914 $ work, rwork, iwork, nout )
915 ELSE
916 WRITE( nout, fmt = 9989 )path
917 END IF
918*
919 ELSE IF( lsamen( 2, c2, 'QP' ) ) THEN
920*
921* QP: QR factorization with pivoting
922*
923 ntypes = 6
924 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
925*
926 IF( tstchk ) THEN
927 CALL dchkq3( dotype, nm, mval, nn, nval, nnb, nbval,
928 $ nxval, thresh, a( 1, 1 ), a( 1, 2 ),
929 $ b( 1, 1 ), b( 1, 3 ), work, iwork, nout )
930 ELSE
931 WRITE( nout, fmt = 9989 )path
932 END IF
933*
934 ELSE IF( lsamen( 2, c2, 'QK' ) ) THEN
935*
936* QK: truncated QR factorization with pivoting
937*
938 ntypes = 19
939 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
940*
941 IF( tstchk ) THEN
942 CALL dchkqp3rk( dotype, nm, mval, nn, nval, nns, nsval,
943 $ nnb, nbval, nxval, thresh, a( 1, 1 ),
944 $ a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
945 $ b( 1, 3 ), b( 1, 4 ),
946 $ work, iwork, nout )
947 ELSE
948 WRITE( nout, fmt = 9989 )path
949 END IF
950*
951 ELSE IF( lsamen( 2, c2, 'TZ' ) ) THEN
952*
953* TZ: Trapezoidal matrix
954*
955 ntypes = 3
956 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
957*
958 IF( tstchk ) THEN
959 CALL dchktz( dotype, nm, mval, nn, nval, thresh, tsterr,
960 $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
961 $ b( 1, 3 ), work, nout )
962 ELSE
963 WRITE( nout, fmt = 9989 )path
964 END IF
965*
966 ELSE IF( lsamen( 2, c2, 'LS' ) ) THEN
967*
968* LS: Least squares drivers
969*
970 ntypes = 6
971 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
972*
973 IF( tstdrv ) THEN
974 CALL ddrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
975 $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
976 $ a( 1, 2 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
977 $ rwork, rwork( nmax+1 ), nout )
978 ELSE
979 WRITE( nout, fmt = 9988 )path
980 END IF
981*
982 ELSE IF( lsamen( 2, c2, 'EQ' ) ) THEN
983*
984* EQ: Equilibration routines for general and positive definite
985* matrices (THREQ should be between 2 and 10)
986*
987 IF( tstchk ) THEN
988 CALL dchkeq( threq, nout )
989 ELSE
990 WRITE( nout, fmt = 9989 )path
991 END IF
992*
993 ELSE IF( lsamen( 2, c2, 'QT' ) ) THEN
994*
995* QT: QRT routines for general matrices
996*
997 IF( tstchk ) THEN
998 CALL dchkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
999 $ nbval, nout )
1000 ELSE
1001 WRITE( nout, fmt = 9989 )path
1002 END IF
1003*
1004 ELSE IF( lsamen( 2, c2, 'QX' ) ) THEN
1005*
1006* QX: QRT routines for triangular-pentagonal matrices
1007*
1008 IF( tstchk ) THEN
1009 CALL dchkqrtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1010 $ nbval, nout )
1011 ELSE
1012 WRITE( nout, fmt = 9989 )path
1013 END IF
1014*
1015 ELSE IF( lsamen( 2, c2, 'TQ' ) ) THEN
1016*
1017* TQ: LQT routines for general matrices
1018*
1019 IF( tstchk ) THEN
1020 CALL dchklqt( thresh, tsterr, nm, mval, nn, nval, nnb,
1021 $ nbval, nout )
1022 ELSE
1023 WRITE( nout, fmt = 9989 )path
1024 END IF
1025*
1026 ELSE IF( lsamen( 2, c2, 'XQ' ) ) THEN
1027*
1028* XQ: LQT routines for triangular-pentagonal matrices
1029*
1030 IF( tstchk ) THEN
1031 CALL dchklqtp( thresh, tsterr, nm, mval, nn, nval, nnb,
1032 $ nbval, nout )
1033 ELSE
1034 WRITE( nout, fmt = 9989 )path
1035 END IF
1036*
1037 ELSE IF( lsamen( 2, c2, 'TS' ) ) THEN
1038*
1039* TS: QR routines for tall-skinny matrices
1040*
1041 IF( tstchk ) THEN
1042 CALL dchktsqr( thresh, tsterr, nm, mval, nn, nval, nnb,
1043 $ nbval, nout )
1044 ELSE
1045 WRITE( nout, fmt = 9989 )path
1046 END IF
1047*
1048 ELSE IF( lsamen( 2, c2, 'HH' ) ) THEN
1049*
1050* HH: Householder reconstruction for tall-skinny matrices
1051*
1052 IF( tstchk ) THEN
1053 CALL dchkorhr_col( thresh, tsterr, nm, mval, nn, nval, nnb,
1054 $ nbval, nout )
1055 ELSE
1056 WRITE( nout, fmt = 9989 ) path
1057 END IF
1058*
1059 ELSE
1060
1061*
1062 WRITE( nout, fmt = 9990 )path
1063 END IF
1064*
1065* Go back to get another input line.
1066*
1067 GO TO 80
1068*
1069* Branch to this line when the last record is read.
1070*
1071 140 CONTINUE
1072 CLOSE ( nin )
1073 s2 = dsecnd( )
1074 WRITE( nout, fmt = 9998 )
1075 WRITE( nout, fmt = 9997 )s2 - s1
1076*
1077 DEALLOCATE (a, stat = allocatestatus)
1078 DEALLOCATE (b, stat = allocatestatus)
1079 DEALLOCATE (work, stat = allocatestatus)
1080 DEALLOCATE (rwork, stat = allocatestatus)
1081*
1082 9999 FORMAT( / ' Execution not attempted due to input errors' )
1083 9998 FORMAT( / ' End of tests' )
1084 9997 FORMAT( ' Total time used = ', f12.2, ' seconds', / )
1085 9996 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be >=',
1086 $ i6 )
1087 9995 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be <=',
1088 $ i6 )
1089 9994 FORMAT( ' Tests of the DOUBLE PRECISION LAPACK routines ',
1090 $ / ' LAPACK VERSION ', i1, '.', i1, '.', i1,
1091 $ / / ' The following parameter values will be used:' )
1092 9993 FORMAT( 4x, a4, ': ', 10i6, / 11x, 10i6 )
1093 9992 FORMAT( / ' Routines pass computational tests if test ratio is ',
1094 $ 'less than', f8.2, / )
1095 9991 FORMAT( ' Relative machine ', a, ' is taken to be', d16.6 )
1096 9990 FORMAT( / 1x, a3, ': Unrecognized path name' )
1097 9989 FORMAT( / 1x, a3, ' routines were not tested' )
1098 9988 FORMAT( / 1x, a3, ' driver routines were not tested' )
1099*
1100* End of DCHKAA
1101*
1102 END
subroutine alareq(path, nmats, dotype, ntypes, nin, nout)
ALAREQ
Definition alareq.f:90
program dchkaa
DCHKAA
Definition dchkaa.F:113
subroutine dchkeq(thresh, nout)
DCHKEQ
Definition dchkeq.f:54
subroutine dchkgb(dotype, nm, mval, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, a, la, afac, lafac, b, x, xact, work, rwork, iwork, nout)
DCHKGB
Definition dchkgb.f:191
subroutine dchkge(dotype, nm, mval, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKGE
Definition dchkge.f:185
subroutine dchkgt(dotype, nn, nval, nns, nsval, thresh, tsterr, a, af, b, x, xact, work, rwork, iwork, nout)
DCHKGT
Definition dchkgt.f:146
subroutine dchklq(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, al, ac, b, x, xact, tau, work, rwork, nout)
DCHKLQ
Definition dchklq.f:196
subroutine dchklqt(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKLQT
Definition dchklqt.f:102
subroutine dchklqtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKLQTP
Definition dchklqtp.f:102
subroutine dchkorhr_col(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKORHR_COL
subroutine dchkpb(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKPB
Definition dchkpb.f:172
subroutine dchkpo(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKPO
Definition dchkpo.f:172
subroutine dchkpp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKPP
Definition dchkpp.f:163
subroutine dchkps(dotype, nn, nval, nnb, nbval, nrank, rankval, thresh, tsterr, nmax, a, afac, perm, piv, work, rwork, nout)
DCHKPS
Definition dchkps.f:154
subroutine dchkpt(dotype, nn, nval, nns, nsval, thresh, tsterr, a, d, e, b, x, xact, work, rwork, nout)
DCHKPT
Definition dchkpt.f:146
subroutine dchkq3(dotype, nm, mval, nn, nval, nnb, nbval, nxval, thresh, a, copya, s, tau, work, iwork, nout)
DCHKQ3
Definition dchkq3.f:153
subroutine dchkql(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, al, ac, b, x, xact, tau, work, rwork, nout)
DCHKQL
Definition dchkql.f:196
subroutine dchkqp3rk(dotype, nm, mval, nn, nval, nns, nsval, nnb, nbval, nxval, thresh, a, copya, b, copyb, s, tau, work, iwork, nout)
DCHKQP3RK
Definition dchkqp3rk.f:184
subroutine dchkqr(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)
DCHKQR
Definition dchkqr.f:201
subroutine dchkqrt(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKQRT
Definition dchkqrt.f:102
subroutine dchkqrtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKQRTP
Definition dchkqrtp.f:102
subroutine dchkrq(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)
DCHKRQ
Definition dchkrq.f:201
subroutine dchksp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSP
Definition dchksp.f:163
subroutine dchksy(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSY
Definition dchksy.f:170
subroutine dchksy_aa(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSY_AA
Definition dchksy_aa.f:170
subroutine dchksy_aa_2stage(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSY_AA_2STAGE
subroutine dchksy_rk(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSY_RK
Definition dchksy_rk.f:176
subroutine dchksy_rook(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKSY_ROOK
subroutine dchktb(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, ab, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKTB
Definition dchktb.f:155
subroutine dchktp(dotype, nn, nval, nns, nsval, thresh, tsterr, nmax, ap, ainvp, b, x, xact, work, rwork, iwork, nout)
DCHKTP
Definition dchktp.f:157
subroutine dchktr(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, ainv, b, x, xact, work, rwork, iwork, nout)
DCHKTR
Definition dchktr.f:167
subroutine dchktsqr(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
DCHKQRT
Definition dchktsqr.f:102
subroutine dchktz(dotype, nm, mval, nn, nval, thresh, tsterr, a, copya, s, tau, work, nout)
DCHKTZ
Definition dchktz.f:132
subroutine ddrvgb(dotype, nn, nval, nrhs, thresh, tsterr, a, la, afb, lafb, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
DDRVGB
Definition ddrvgb.f:172
subroutine ddrvge(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
DDRVGE
Definition ddrvge.f:164
subroutine ddrvgt(dotype, nn, nval, nrhs, thresh, tsterr, a, af, b, x, xact, work, rwork, iwork, nout)
DDRVGT
Definition ddrvgt.f:139
subroutine ddrvls(dotype, nm, mval, nn, nval, nns, nsval, nnb, nbval, nxval, thresh, tsterr, a, copya, b, copyb, c, s, copys, nout)
DDRVLS
Definition ddrvls.f:192
subroutine ddrvpb(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
DDRVPB
Definition ddrvpb.f:164
subroutine ddrvpo(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
DDRVPO
Definition ddrvpo.f:164
subroutine ddrvpp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, asav, b, bsav, x, xact, s, work, rwork, iwork, nout)
DDRVPP
Definition ddrvpp.f:167
subroutine ddrvpt(dotype, nn, nval, nrhs, thresh, tsterr, a, d, e, b, x, xact, work, rwork, nout)
DDRVPT
Definition ddrvpt.f:140
subroutine ddrvsp(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSP
Definition ddrvsp.f:156
subroutine ddrvsy(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY
Definition ddrvsy.f:152
subroutine ddrvsy_aa(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY_AA
Definition ddrvsy_aa.f:152
subroutine ddrvsy_aa_2stage(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY_AA_2STAGE
subroutine ddrvsy_rk(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, e, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY_RK
Definition ddrvsy_rk.f:156
subroutine ddrvsy_rook(dotype, nn, nval, nrhs, thresh, tsterr, nmax, a, afac, ainv, b, x, xact, work, rwork, iwork, nout)
DDRVSY_ROOK
subroutine ilaver(vers_major, vers_minor, vers_patch)
ILAVER returns the LAPACK version.
Definition ilaver.f:51
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
logical function lsamen(n, ca, cb)
LSAMEN
Definition lsamen.f:74
double precision function dsecnd()
DSECND Using ETIME