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