LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
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 *> \date November 2019
108 *
109 *> \ingroup single_lin
110 *
111 * =====================================================================
112  PROGRAM schkaa
113 *
114 * -- LAPACK test routine (version 3.9.0) --
115 * -- LAPACK is a software package provided by Univ. of Tennessee, --
116 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117 * November 2019
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  REAL 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  REAL a( ( kdmax+1 )*nmax, 7 ), b( nmax*maxrhs, 4 ),
154  $ e( nmax ), rwork( 5*nmax+2*maxrhs ),
155  $ s( 2*nmax ), work( nmax, nmax+maxrhs+30 )
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,
171  $ schklqt, schktsqr
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 * .. Executable Statements ..
190 *
191  s1 = second( )
192  lda = nmax
193  fatal = .false.
194 *
195 * Read a dummy line.
196 *
197  READ( nin, fmt = * )
198 *
199 * Report values of parameters.
200 *
201  CALL ilaver( vers_major, vers_minor, vers_patch )
202  WRITE( nout, fmt = 9994 ) vers_major, vers_minor, vers_patch
203 *
204 * Read the values of M
205 *
206  READ( nin, fmt = * )nm
207  IF( nm.LT.1 ) THEN
208  WRITE( nout, fmt = 9996 )' NM ', nm, 1
209  nm = 0
210  fatal = .true.
211  ELSE IF( nm.GT.maxin ) THEN
212  WRITE( nout, fmt = 9995 )' NM ', nm, maxin
213  nm = 0
214  fatal = .true.
215  END IF
216  READ( nin, fmt = * )( mval( i ), i = 1, nm )
217  DO 10 i = 1, nm
218  IF( mval( i ).LT.0 ) THEN
219  WRITE( nout, fmt = 9996 )' M ', mval( i ), 0
220  fatal = .true.
221  ELSE IF( mval( i ).GT.nmax ) THEN
222  WRITE( nout, fmt = 9995 )' M ', mval( i ), nmax
223  fatal = .true.
224  END IF
225  10 CONTINUE
226  IF( nm.GT.0 )
227  $ WRITE( nout, fmt = 9993 )'M ', ( mval( i ), i = 1, nm )
228 *
229 * Read the values of N
230 *
231  READ( nin, fmt = * )nn
232  IF( nn.LT.1 ) THEN
233  WRITE( nout, fmt = 9996 )' NN ', nn, 1
234  nn = 0
235  fatal = .true.
236  ELSE IF( nn.GT.maxin ) THEN
237  WRITE( nout, fmt = 9995 )' NN ', nn, maxin
238  nn = 0
239  fatal = .true.
240  END IF
241  READ( nin, fmt = * )( nval( i ), i = 1, nn )
242  DO 20 i = 1, nn
243  IF( nval( i ).LT.0 ) THEN
244  WRITE( nout, fmt = 9996 )' N ', nval( i ), 0
245  fatal = .true.
246  ELSE IF( nval( i ).GT.nmax ) THEN
247  WRITE( nout, fmt = 9995 )' N ', nval( i ), nmax
248  fatal = .true.
249  END IF
250  20 CONTINUE
251  IF( nn.GT.0 )
252  $ WRITE( nout, fmt = 9993 )'N ', ( nval( i ), i = 1, nn )
253 *
254 * Read the values of NRHS
255 *
256  READ( nin, fmt = * )nns
257  IF( nns.LT.1 ) THEN
258  WRITE( nout, fmt = 9996 )' NNS', nns, 1
259  nns = 0
260  fatal = .true.
261  ELSE IF( nns.GT.maxin ) THEN
262  WRITE( nout, fmt = 9995 )' NNS', nns, maxin
263  nns = 0
264  fatal = .true.
265  END IF
266  READ( nin, fmt = * )( nsval( i ), i = 1, nns )
267  DO 30 i = 1, nns
268  IF( nsval( i ).LT.0 ) THEN
269  WRITE( nout, fmt = 9996 )'NRHS', nsval( i ), 0
270  fatal = .true.
271  ELSE IF( nsval( i ).GT.maxrhs ) THEN
272  WRITE( nout, fmt = 9995 )'NRHS', nsval( i ), maxrhs
273  fatal = .true.
274  END IF
275  30 CONTINUE
276  IF( nns.GT.0 )
277  $ WRITE( nout, fmt = 9993 )'NRHS', ( nsval( i ), i = 1, nns )
278 *
279 * Read the values of NB
280 *
281  READ( nin, fmt = * )nnb
282  IF( nnb.LT.1 ) THEN
283  WRITE( nout, fmt = 9996 )'NNB ', nnb, 1
284  nnb = 0
285  fatal = .true.
286  ELSE IF( nnb.GT.maxin ) THEN
287  WRITE( nout, fmt = 9995 )'NNB ', nnb, maxin
288  nnb = 0
289  fatal = .true.
290  END IF
291  READ( nin, fmt = * )( nbval( i ), i = 1, nnb )
292  DO 40 i = 1, nnb
293  IF( nbval( i ).LT.0 ) THEN
294  WRITE( nout, fmt = 9996 )' NB ', nbval( i ), 0
295  fatal = .true.
296  END IF
297  40 CONTINUE
298  IF( nnb.GT.0 )
299  $ WRITE( nout, fmt = 9993 )'NB ', ( nbval( i ), i = 1, nnb )
300 *
301 * Set NBVAL2 to be the set of unique values of NB
302 *
303  nnb2 = 0
304  DO 60 i = 1, nnb
305  nb = nbval( i )
306  DO 50 j = 1, nnb2
307  IF( nb.EQ.nbval2( j ) )
308  $ GO TO 60
309  50 CONTINUE
310  nnb2 = nnb2 + 1
311  nbval2( nnb2 ) = nb
312  60 CONTINUE
313 *
314 * Read the values of NX
315 *
316  READ( nin, fmt = * )( nxval( i ), i = 1, nnb )
317  DO 70 i = 1, nnb
318  IF( nxval( i ).LT.0 ) THEN
319  WRITE( nout, fmt = 9996 )' NX ', nxval( i ), 0
320  fatal = .true.
321  END IF
322  70 CONTINUE
323  IF( nnb.GT.0 )
324  $ WRITE( nout, fmt = 9993 )'NX ', ( nxval( i ), i = 1, nnb )
325 *
326 * Read the values of RANKVAL
327 *
328  READ( nin, fmt = * )nrank
329  IF( nn.LT.1 ) THEN
330  WRITE( nout, fmt = 9996 )' NRANK ', nrank, 1
331  nrank = 0
332  fatal = .true.
333  ELSE IF( nn.GT.maxin ) THEN
334  WRITE( nout, fmt = 9995 )' NRANK ', nrank, maxin
335  nrank = 0
336  fatal = .true.
337  END IF
338  READ( nin, fmt = * )( rankval( i ), i = 1, nrank )
339  DO i = 1, nrank
340  IF( rankval( i ).LT.0 ) THEN
341  WRITE( nout, fmt = 9996 )' RANK ', rankval( i ), 0
342  fatal = .true.
343  ELSE IF( rankval( i ).GT.100 ) THEN
344  WRITE( nout, fmt = 9995 )' RANK ', rankval( i ), 100
345  fatal = .true.
346  END IF
347  END DO
348  IF( nrank.GT.0 )
349  $ WRITE( nout, fmt = 9993 )'RANK % OF N',
350  $ ( rankval( i ), i = 1, nrank )
351 *
352 * Read the threshold value for the test ratios.
353 *
354  READ( nin, fmt = * )thresh
355  WRITE( nout, fmt = 9992 )thresh
356 *
357 * Read the flag that indicates whether to test the LAPACK routines.
358 *
359  READ( nin, fmt = * )tstchk
360 *
361 * Read the flag that indicates whether to test the driver routines.
362 *
363  READ( nin, fmt = * )tstdrv
364 *
365 * Read the flag that indicates whether to test the error exits.
366 *
367  READ( nin, fmt = * )tsterr
368 *
369  IF( fatal ) THEN
370  WRITE( nout, fmt = 9999 )
371  stop
372  END IF
373 *
374 * Calculate and print the machine dependent constants.
375 *
376  eps = slamch( 'Underflow threshold' )
377  WRITE( nout, fmt = 9991 )'underflow', eps
378  eps = slamch( 'Overflow threshold' )
379  WRITE( nout, fmt = 9991 )'overflow ', eps
380  eps = slamch( 'Epsilon' )
381  WRITE( nout, fmt = 9991 )'precision', eps
382  WRITE( nout, fmt = * )
383 *
384  80 CONTINUE
385 *
386 * Read a test path and the number of matrix types to use.
387 *
388  READ( nin, fmt = '(A72)', END = 140 )aline
389  path = aline( 1: 3 )
390  nmats = matmax
391  i = 3
392  90 CONTINUE
393  i = i + 1
394  IF( i.GT.72 ) THEN
395  nmats = matmax
396  GO TO 130
397  END IF
398  IF( aline( i: i ).EQ.' ' )
399  $ GO TO 90
400  nmats = 0
401  100 CONTINUE
402  c1 = aline( i: i )
403  DO 110 k = 1, 10
404  IF( c1.EQ.intstr( k: k ) ) THEN
405  ic = k - 1
406  GO TO 120
407  END IF
408  110 CONTINUE
409  GO TO 130
410  120 CONTINUE
411  nmats = nmats*10 + ic
412  i = i + 1
413  IF( i.GT.72 )
414  $ GO TO 130
415  GO TO 100
416  130 CONTINUE
417  c1 = path( 1: 1 )
418  c2 = path( 2: 3 )
419  nrhs = nsval( 1 )
420 *
421 * Check first character for correct precision.
422 *
423  IF( .NOT.lsame( c1, 'Single precision' ) ) THEN
424  WRITE( nout, fmt = 9990 )path
425 *
426  ELSE IF( nmats.LE.0 ) THEN
427 *
428 * Check for a positive number of tests requested.
429 *
430  WRITE( nout, fmt = 9989 )path
431 *
432  ELSE IF( lsamen( 2, c2, 'GE' ) ) THEN
433 *
434 * GE: general matrices
435 *
436  ntypes = 11
437  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
438 *
439  IF( tstchk ) THEN
440  CALL schkge( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
441  $ nsval, thresh, tsterr, lda, a( 1, 1 ),
442  $ a( 1, 2 ), a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
443  $ b( 1, 3 ), work, rwork, iwork, nout )
444  ELSE
445  WRITE( nout, fmt = 9989 )path
446  END IF
447 *
448  IF( tstdrv ) THEN
449  CALL sdrvge( dotype, nn, nval, nrhs, thresh, tsterr, lda,
450  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
451  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
452  $ rwork, iwork, nout )
453  ELSE
454  WRITE( nout, fmt = 9988 )path
455  END IF
456 *
457  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
458 *
459 * GB: general banded matrices
460 *
461  la = ( 2*kdmax+1 )*nmax
462  lafac = ( 3*kdmax+1 )*nmax
463  ntypes = 8
464  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
465 *
466  IF( tstchk ) THEN
467  CALL schkgb( dotype, nm, mval, nn, nval, nnb2, nbval2, nns,
468  $ nsval, thresh, tsterr, a( 1, 1 ), la,
469  $ a( 1, 3 ), lafac, b( 1, 1 ), b( 1, 2 ),
470  $ b( 1, 3 ), work, rwork, iwork, nout )
471  ELSE
472  WRITE( nout, fmt = 9989 )path
473  END IF
474 *
475  IF( tstdrv ) THEN
476  CALL sdrvgb( dotype, nn, nval, nrhs, thresh, tsterr,
477  $ a( 1, 1 ), la, a( 1, 3 ), lafac, a( 1, 6 ),
478  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s,
479  $ work, rwork, iwork, nout )
480  ELSE
481  WRITE( nout, fmt = 9988 )path
482  END IF
483 *
484  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
485 *
486 * GT: general tridiagonal matrices
487 *
488  ntypes = 12
489  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
490 *
491  IF( tstchk ) THEN
492  CALL schkgt( dotype, nn, nval, nns, nsval, thresh, tsterr,
493  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
494  $ b( 1, 3 ), work, rwork, iwork, nout )
495  ELSE
496  WRITE( nout, fmt = 9989 )path
497  END IF
498 *
499  IF( tstdrv ) THEN
500  CALL sdrvgt( dotype, nn, nval, nrhs, thresh, tsterr,
501  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ), b( 1, 2 ),
502  $ b( 1, 3 ), work, rwork, iwork, nout )
503  ELSE
504  WRITE( nout, fmt = 9988 )path
505  END IF
506 *
507  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
508 *
509 * PO: positive definite matrices
510 *
511  ntypes = 9
512  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
513 *
514  IF( tstchk ) THEN
515  CALL schkpo( dotype, nn, nval, nnb2, nbval2, nns, nsval,
516  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
517  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
518  $ work, rwork, iwork, nout )
519  ELSE
520  WRITE( nout, fmt = 9989 )path
521  END IF
522 *
523  IF( tstdrv ) THEN
524  CALL sdrvpo( dotype, nn, nval, nrhs, thresh, tsterr, lda,
525  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
526  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
527  $ rwork, iwork, nout )
528  ELSE
529  WRITE( nout, fmt = 9988 )path
530  END IF
531 *
532  ELSE IF( lsamen( 2, c2, 'PS' ) ) THEN
533 *
534 * PS: positive semi-definite matrices
535 *
536  ntypes = 9
537 *
538  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
539 *
540  IF( tstchk ) THEN
541  CALL schkps( dotype, nn, nval, nnb2, nbval2, nrank,
542  $ rankval, thresh, tsterr, lda, a( 1, 1 ),
543  $ a( 1, 2 ), a( 1, 3 ), piv, work, rwork,
544  $ nout )
545  ELSE
546  WRITE( nout, fmt = 9989 )path
547  END IF
548 *
549  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
550 *
551 * PP: positive definite packed matrices
552 *
553  ntypes = 9
554  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
555 *
556  IF( tstchk ) THEN
557  CALL schkpp( dotype, nn, nval, nns, nsval, thresh, tsterr,
558  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
559  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
560  $ iwork, nout )
561  ELSE
562  WRITE( nout, fmt = 9989 )path
563  END IF
564 *
565  IF( tstdrv ) THEN
566  CALL sdrvpp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
567  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
568  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
569  $ rwork, iwork, nout )
570  ELSE
571  WRITE( nout, fmt = 9988 )path
572  END IF
573 *
574  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
575 *
576 * PB: positive definite banded matrices
577 *
578  ntypes = 8
579  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
580 *
581  IF( tstchk ) THEN
582  CALL schkpb( dotype, nn, nval, nnb2, nbval2, nns, nsval,
583  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
584  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
585  $ work, rwork, iwork, nout )
586  ELSE
587  WRITE( nout, fmt = 9989 )path
588  END IF
589 *
590  IF( tstdrv ) THEN
591  CALL sdrvpb( dotype, nn, nval, nrhs, thresh, tsterr, lda,
592  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
593  $ b( 1, 2 ), b( 1, 3 ), b( 1, 4 ), s, work,
594  $ rwork, iwork, nout )
595  ELSE
596  WRITE( nout, fmt = 9988 )path
597  END IF
598 *
599  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
600 *
601 * PT: positive definite tridiagonal matrices
602 *
603  ntypes = 12
604  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
605 *
606  IF( tstchk ) THEN
607  CALL schkpt( dotype, nn, nval, nns, nsval, thresh, tsterr,
608  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
609  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
610  ELSE
611  WRITE( nout, fmt = 9989 )path
612  END IF
613 *
614  IF( tstdrv ) THEN
615  CALL sdrvpt( dotype, nn, nval, nrhs, thresh, tsterr,
616  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
617  $ b( 1, 2 ), b( 1, 3 ), work, rwork, nout )
618  ELSE
619  WRITE( nout, fmt = 9988 )path
620  END IF
621 *
622  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
623 *
624 * SY: symmetric indefinite matrices,
625 * with partial (Bunch-Kaufman) pivoting algorithm
626 *
627  ntypes = 10
628  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
629 *
630  IF( tstchk ) THEN
631  CALL schksy( dotype, nn, nval, nnb2, nbval2, nns, nsval,
632  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
633  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
634  $ work, rwork, iwork, nout )
635  ELSE
636  WRITE( nout, fmt = 9989 )path
637  END IF
638 *
639  IF( tstdrv ) THEN
640  CALL sdrvsy( dotype, nn, nval, nrhs, thresh, tsterr, lda,
641  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
642  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
643  $ nout )
644  ELSE
645  WRITE( nout, fmt = 9988 )path
646  END IF
647 *
648  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
649 *
650 * SR: symmetric indefinite matrices,
651 * with bounded Bunch-Kaufman (rook) pivoting algorithm
652 *
653  ntypes = 10
654  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
655 *
656  IF( tstchk ) THEN
657  CALL schksy_rook(dotype, nn, nval, nnb2, nbval2, nns, nsval,
658  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
659  $ a( 1, 3 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
660  $ work, rwork, iwork, nout )
661  ELSE
662  WRITE( nout, fmt = 9989 )path
663  END IF
664 *
665  IF( tstdrv ) THEN
666  CALL sdrvsy_rook( dotype, nn, nval, nrhs, thresh, tsterr,
667  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
668  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
669  $ work, rwork, iwork, nout )
670  ELSE
671  WRITE( nout, fmt = 9988 )path
672  END IF
673 *
674  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
675 *
676 * SK: symmetric indefinite matrices,
677 * with bounded Bunch-Kaufman (rook) pivoting algorithm,
678 * different matrix storage format than SR path version.
679 *
680  ntypes = 10
681  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
682 *
683  IF( tstchk ) THEN
684  CALL schksy_rk( dotype, nn, nval, nnb2, nbval2, nns, nsval,
685  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
686  $ e, a( 1, 3 ), b( 1, 1 ), b( 1, 2 ),
687  $ b( 1, 3 ), work, rwork, iwork, nout )
688  ELSE
689  WRITE( nout, fmt = 9989 )path
690  END IF
691 *
692  IF( tstdrv ) THEN
693  CALL sdrvsy_rk( dotype, nn, nval, nrhs, thresh, tsterr,
694  $ lda, a( 1, 1 ), a( 1, 2 ), e, a( 1, 3 ),
695  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
696  $ work, rwork, iwork, nout )
697  ELSE
698  WRITE( nout, fmt = 9988 )path
699  END IF
700 *
701  ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
702 *
703 * SA: symmetric indefinite matrices,
704 * with partial (Aasen's) pivoting algorithm
705 *
706  ntypes = 10
707  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
708 *
709  IF( tstchk ) THEN
710  CALL schksy_aa( dotype, nn, nval, nnb2, nbval2, nns,
711  $ nsval, thresh, tsterr, lda,
712  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
713  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
714  $ work, rwork, iwork, nout )
715  ELSE
716  WRITE( nout, fmt = 9989 )path
717  END IF
718 *
719  IF( tstdrv ) THEN
720  CALL sdrvsy_aa( dotype, nn, nval, nrhs, thresh, tsterr,
721  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
722  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
723  $ work, rwork, iwork, nout )
724  ELSE
725  WRITE( nout, fmt = 9988 )path
726  END IF
727 *
728  ELSE IF( lsamen( 2, c2, 'S2' ) ) THEN
729 *
730 * SA: symmetric indefinite matrices,
731 * with partial (Aasen's) pivoting algorithm
732 *
733  ntypes = 10
734  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
735 *
736  IF( tstchk ) THEN
737  CALL schksy_aa_2stage( dotype, nn, nval, nnb2, nbval2,
738  $ nns, nsval, thresh, tsterr, lda,
739  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
740  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
741  $ work, rwork, iwork, nout )
742  ELSE
743  WRITE( nout, fmt = 9989 )path
744  END IF
745 *
746  IF( tstdrv ) THEN
747  CALL sdrvsy_aa_2stage(
748  $ dotype, nn, nval, nrhs, thresh, tsterr,
749  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
750  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
751  $ work, rwork, iwork, nout )
752  ELSE
753  WRITE( nout, fmt = 9988 )path
754  END IF
755 *
756  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
757 *
758 * SP: symmetric indefinite packed matrices,
759 * with partial (Bunch-Kaufman) pivoting algorithm
760 *
761  ntypes = 10
762  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
763 *
764  IF( tstchk ) THEN
765  CALL schksp( dotype, nn, nval, nns, nsval, thresh, tsterr,
766  $ lda, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
767  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
768  $ iwork, nout )
769  ELSE
770  WRITE( nout, fmt = 9989 )path
771  END IF
772 *
773  IF( tstdrv ) THEN
774  CALL sdrvsp( dotype, nn, nval, nrhs, thresh, tsterr, lda,
775  $ a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b( 1, 1 ),
776  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
777  $ nout )
778  ELSE
779  WRITE( nout, fmt = 9988 )path
780  END IF
781 *
782  ELSE IF( lsamen( 2, c2, 'TR' ) ) THEN
783 *
784 * TR: triangular matrices
785 *
786  ntypes = 18
787  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
788 *
789  IF( tstchk ) THEN
790  CALL schktr( dotype, nn, nval, nnb2, nbval2, nns, nsval,
791  $ thresh, tsterr, lda, a( 1, 1 ), a( 1, 2 ),
792  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), work, rwork,
793  $ iwork, nout )
794  ELSE
795  WRITE( nout, fmt = 9989 )path
796  END IF
797 *
798  ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
799 *
800 * TP: triangular packed matrices
801 *
802  ntypes = 18
803  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
804 *
805  IF( tstchk ) THEN
806  CALL schktp( dotype, nn, nval, nns, nsval, thresh, tsterr,
807  $ lda, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
808  $ b( 1, 2 ), b( 1, 3 ), work, rwork, iwork,
809  $ nout )
810  ELSE
811  WRITE( nout, fmt = 9989 )path
812  END IF
813 *
814  ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
815 *
816 * TB: triangular banded matrices
817 *
818  ntypes = 17
819  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
820 *
821  IF( tstchk ) THEN
822  CALL schktb( 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, 'QR' ) ) THEN
831 *
832 * QR: QR factorization
833 *
834  ntypes = 8
835  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
836 *
837  IF( tstchk ) THEN
838  CALL schkqr( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
839  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
840  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
841  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
842  $ work, rwork, iwork, nout )
843  ELSE
844  WRITE( nout, fmt = 9989 )path
845  END IF
846 *
847  ELSE IF( lsamen( 2, c2, 'LQ' ) ) THEN
848 *
849 * LQ: LQ factorization
850 *
851  ntypes = 8
852  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
853 *
854  IF( tstchk ) THEN
855  CALL schklq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
856  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
857  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
858  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
859  $ work, rwork, nout )
860  ELSE
861  WRITE( nout, fmt = 9989 )path
862  END IF
863 *
864  ELSE IF( lsamen( 2, c2, 'QL' ) ) THEN
865 *
866 * QL: QL factorization
867 *
868  ntypes = 8
869  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
870 *
871  IF( tstchk ) THEN
872  CALL schkql( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
873  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
874  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
875  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
876  $ work, rwork, nout )
877  ELSE
878  WRITE( nout, fmt = 9989 )path
879  END IF
880 *
881  ELSE IF( lsamen( 2, c2, 'RQ' ) ) THEN
882 *
883 * RQ: RQ factorization
884 *
885  ntypes = 8
886  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
887 *
888  IF( tstchk ) THEN
889  CALL schkrq( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
890  $ nrhs, thresh, tsterr, nmax, a( 1, 1 ),
891  $ a( 1, 2 ), a( 1, 3 ), a( 1, 4 ), a( 1, 5 ),
892  $ b( 1, 1 ), b( 1, 2 ), b( 1, 3 ), b( 1, 4 ),
893  $ work, rwork, iwork, nout )
894  ELSE
895  WRITE( nout, fmt = 9989 )path
896  END IF
897 *
898  ELSE IF( lsamen( 2, c2, 'QP' ) ) THEN
899 *
900 * QP: QR factorization with pivoting
901 *
902  ntypes = 6
903  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
904 *
905  IF( tstchk ) THEN
906  CALL schkq3( dotype, nm, mval, nn, nval, nnb, nbval, nxval,
907  $ thresh, a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
908  $ b( 1, 3 ), work, iwork, nout )
909  ELSE
910  WRITE( nout, fmt = 9989 )path
911  END IF
912 *
913  ELSE IF( lsamen( 2, c2, 'TZ' ) ) THEN
914 *
915 * TZ: Trapezoidal matrix
916 *
917  ntypes = 3
918  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
919 *
920  IF( tstchk ) THEN
921  CALL schktz( dotype, nm, mval, nn, nval, thresh, tsterr,
922  $ a( 1, 1 ), a( 1, 2 ), b( 1, 1 ),
923  $ b( 1, 3 ), work, nout )
924  ELSE
925  WRITE( nout, fmt = 9989 )path
926  END IF
927 *
928  ELSE IF( lsamen( 2, c2, 'LS' ) ) THEN
929 *
930 * LS: Least squares drivers
931 *
932  ntypes = 6
933  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
934 *
935  IF( tstdrv ) THEN
936  CALL sdrvls( dotype, nm, mval, nn, nval, nns, nsval, nnb,
937  $ nbval, nxval, thresh, tsterr, a( 1, 1 ),
938  $ a( 1, 2 ), b( 1, 1 ), b( 1, 2 ), b( 1, 3 ),
939  $ rwork, rwork( nmax+1 ), nout )
940  ELSE
941  WRITE( nout, fmt = 9988 )path
942  END IF
943 *
944  ELSE IF( lsamen( 2, c2, 'EQ' ) ) THEN
945 *
946 * EQ: Equilibration routines for general and positive definite
947 * matrices (THREQ should be between 2 and 10)
948 *
949  IF( tstchk ) THEN
950  CALL schkeq( threq, nout )
951  ELSE
952  WRITE( nout, fmt = 9989 )path
953  END IF
954 *
955  ELSE IF( lsamen( 2, c2, 'QT' ) ) THEN
956 *
957 * QT: QRT routines for general matrices
958 *
959  IF( tstchk ) THEN
960  CALL schkqrt( thresh, tsterr, nm, mval, nn, nval, nnb,
961  $ nbval, nout )
962  ELSE
963  WRITE( nout, fmt = 9989 )path
964  END IF
965 *
966  ELSE IF( lsamen( 2, c2, 'QX' ) ) THEN
967 *
968 * QX: QRT routines for triangular-pentagonal matrices
969 *
970  IF( tstchk ) THEN
971  CALL schkqrtp( 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, 'TQ' ) ) THEN
978 *
979 * TQ: LQT routines for general matrices
980 *
981  IF( tstchk ) THEN
982  CALL schklqt( 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, 'XQ' ) ) THEN
989 *
990 * XQ: LQT routines for triangular-pentagonal matrices
991 *
992  IF( tstchk ) THEN
993  CALL schklqtp( 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, 'TS' ) ) THEN
1000 *
1001 * TS: QR routines for tall-skinny matrices
1002 *
1003  IF( tstchk ) THEN
1004  CALL schktsqr( 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, 'HH' ) ) THEN
1011 *
1012 * HH: Householder reconstruction for tall-skinny matrices
1013 *
1014  IF( tstchk ) THEN
1015  CALL schkorhr_col( thresh, tsterr, nm, mval, nn, nval, nnb,
1016  $ nbval, nout )
1017  ELSE
1018  WRITE( nout, fmt = 9989 ) path
1019  END IF
1020 *
1021  ELSE
1022 *
1023  WRITE( nout, fmt = 9990 )path
1024  END IF
1025 *
1026 * Go back to get another input line.
1027 *
1028  GO TO 80
1029 *
1030 * Branch to this line when the last record is read.
1031 *
1032  140 CONTINUE
1033  CLOSE ( nin )
1034  s2 = second( )
1035  WRITE( nout, fmt = 9998 )
1036  WRITE( nout, fmt = 9997 )s2 - s1
1037 *
1038  9999 FORMAT( / ' Execution not attempted due to input errors' )
1039  9998 FORMAT( / ' End of tests' )
1040  9997 FORMAT( ' Total time used = ', f12.2, ' seconds', / )
1041  9996 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be >=',
1042  $ i6 )
1043  9995 FORMAT( ' Invalid input value: ', a4, '=', i6, '; must be <=',
1044  $ i6 )
1045  9994 FORMAT( ' Tests of the REAL LAPACK routines ',
1046  $ / ' LAPACK VERSION ', i1, '.', i1, '.', i1,
1047  $ / / ' The following parameter values will be used:' )
1048  9993 FORMAT( 4x, a4, ': ', 10i6, / 11x, 10i6 )
1049  9992 FORMAT( / ' Routines pass computational tests if test ratio is ',
1050  $ 'less than', f8.2, / )
1051  9991 FORMAT( ' Relative machine ', a, ' is taken to be', e16.6 )
1052  9990 FORMAT( / 1x, a3, ': Unrecognized path name' )
1053  9989 FORMAT( / 1x, a3, ' routines were not tested' )
1054  9988 FORMAT( / 1x, a3, ' driver routines were not tested' )
1055 *
1056 * End of SCHKAA
1057 *
1058  END
schkeq
subroutine schkeq(THRESH, NOUT)
SCHKEQ
Definition: schkeq.f:56
schkgb
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:193
schkqrtp
subroutine schkqrtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKQRTP
Definition: schkqrtp.f:104
lsamen
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
schktsqr
subroutine schktsqr(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKQRT
Definition: schktsqr.f:104
schksy
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:172
schksp
subroutine schksp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKSP
Definition: schksp.f:165
schklqtp
subroutine schklqtp(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKLQTP
Definition: schklqtp.f:104
schklqt
subroutine schklqt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKLQT
Definition: schklqt.f:104
sdrvge
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:166
second
real function second()
SECOND Using ETIME
Definition: second_EXT_ETIME.f:37
schklq
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:198
schkpb
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:174
schktz
subroutine schktz(DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A, COPYA, S, TAU, WORK, NOUT)
SCHKTZ
Definition: schktz.f:134
schkqrt
subroutine schkqrt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKQRT
Definition: schkqrt.f:102
schktb
subroutine schktb(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AB, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKTB
Definition: schktb.f:157
sdrvsy_aa
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:154
schksy_rk
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:178
schkorhr_col
subroutine schkorhr_col(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKORHR_COL
Definition: schkorhr_col.f:107
schksy_aa
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:172
schkpo
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:174
sdrvsy_aa_2stage
subroutine sdrvsy_aa_2stage(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SDRVSY_AA_2STAGE
Definition: sdrvsy_aa_2stage.f:157
sdrvls
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:194
sdrvpb
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:166
schktr
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:169
schkql
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:198
sdrvsy_rook
subroutine sdrvsy_rook(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SDRVSY_ROOK
Definition: sdrvsy_rook.f:155
schkps
subroutine schkps(DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL, THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK, RWORK, NOUT)
SCHKPS
Definition: schkps.f:156
sdrvgt
subroutine sdrvgt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SDRVGT
Definition: sdrvgt.f:141
sdrvsy_rk
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:158
sdrvpo
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:166
schkaa
program schkaa
SCHKAA
Definition: schkaa.f:112
schkge
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:187
lsame
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
schkgt
subroutine schkgt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, AF, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKGT
Definition: schkgt.f:148
schksy_rook
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
Definition: schksy_rook.f:173
schkrq
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:203
slamch
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:70
sdrvsy
subroutine sdrvsy(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SDRVSY
Definition: sdrvsy.f:154
schksy_aa_2stage
subroutine schksy_aa_2stage(DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKSY_AA_2STAGE
Definition: schksy_aa_2stage.f:173
sdrvpp
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:169
alareq
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
schkpt
subroutine schkpt(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
SCHKPT
Definition: schkpt.f:148
schktp
subroutine schktp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, AP, AINVP, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKTP
Definition: schktp.f:159
sdrvsp
subroutine sdrvsp(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SDRVSP
Definition: sdrvsp.f:158
sdrvpt
subroutine sdrvpt(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, A, D, E, B, X, XACT, WORK, RWORK, NOUT)
SDRVPT
Definition: sdrvpt.f:142
schkq3
subroutine schkq3(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, THRESH, A, COPYA, S, TAU, WORK, IWORK, NOUT)
SCHKQ3
Definition: schkq3.f:155
schkpp
subroutine schkpp(DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
SCHKPP
Definition: schkpp.f:165
schkqr
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:203
ilaver
subroutine ilaver(VERS_MAJOR, VERS_MINOR, VERS_PATCH)
ILAVER returns the LAPACK version.
Definition: ilaver.f:53
sdrvgb
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:174