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