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