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