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