PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
alahd.f
Go to the documentation of this file.
1  SUBROUTINE alahd( IOUNIT, PATH )
2 *
3 * -- LAPACK test routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
6 *
7 * .. Scalar Arguments ..
8  CHARACTER*3 path
9  INTEGER iounit
10 * ..
11 *
12 * Purpose
13 * =======
14 *
15 * ALAHD prints header information for the different test paths.
16 *
17 * Arguments
18 * =========
19 *
20 * IOUNIT (input) INTEGER
21 * The unit number to which the header information should be
22 * printed.
23 *
24 * PATH (input) CHARACTER*3
25 * The name of the path for which the header information is to
26 * be printed. Current paths are
27 * _GE: General matrices
28 * _GB: General band
29 * _GT: General Tridiagonal
30 * _PO: Symmetric or Hermitian positive definite
31 * _PS: Symmetric or Hermitian positive semi-definite
32 * _PP: Symmetric or Hermitian positive definite packed
33 * _PB: Symmetric or Hermitian positive definite band
34 * _PT: Symmetric or Hermitian positive definite tridiagonal
35 * _SY: Symmetric indefinite
36 * _SP: Symmetric indefinite packed
37 * _HE: (complex) Hermitian indefinite
38 * _HP: (complex) Hermitian indefinite packed
39 * _TR: Triangular
40 * _TP: Triangular packed
41 * _TB: Triangular band
42 * _QR: QR (general matrices)
43 * _LQ: LQ (general matrices)
44 * _QL: QL (general matrices)
45 * _RQ: RQ (general matrices)
46 * _QP: QR with column pivoting
47 * _TZ: Trapezoidal
48 * _LS: Least Squares driver routines
49 * _LU: LU variants
50 * _CH: Cholesky variants
51 * _QS: QR variants
52 * The first character must be one of S, D, C, or Z (C or Z only
53 * if complex).
54 *
55 * =====================================================================
56 *
57 * .. Local Scalars ..
58  LOGICAL corz, sord
59  CHARACTER c1, c3
60  CHARACTER*2 p2
61  CHARACTER*4 eigcnm
62  CHARACTER*32 subnam
63  CHARACTER*9 sym
64 * ..
65 * .. External Functions ..
66  LOGICAL lsame, lsamen
67  EXTERNAL lsame, lsamen
68 * ..
69 * .. Intrinsic Functions ..
70  INTRINSIC len_trim
71 * ..
72 * .. Executable Statements ..
73 *
74  IF( iounit.LE.0 )
75  $ return
76  c1 = path( 1: 1 )
77  c3 = path( 3: 3 )
78  p2 = path( 2: 3 )
79  sord = lsame( c1, 'S' ) .OR. lsame( c1, 'D' )
80  corz = lsame( c1, 'C' ) .OR. lsame( c1, 'Z' )
81  IF( .NOT.( sord .OR. corz ) )
82  $ return
83 *
84  IF( lsamen( 2, p2, 'GE' ) ) THEN
85 *
86 * GE: General dense
87 *
88  WRITE( iounit, fmt = 9999 )path
89  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
90  WRITE( iounit, fmt = 9979 )
91  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
92  WRITE( iounit, fmt = 9962 )1
93  WRITE( iounit, fmt = 9961 )2
94  WRITE( iounit, fmt = 9960 )3
95  WRITE( iounit, fmt = 9959 )4
96  WRITE( iounit, fmt = 9958 )5
97  WRITE( iounit, fmt = 9957 )6
98  WRITE( iounit, fmt = 9956 )7
99  WRITE( iounit, fmt = 9955 )8
100  WRITE( iounit, fmt = '( '' Messages:'' )' )
101 *
102  ELSE IF( lsamen( 2, p2, 'GB' ) ) THEN
103 *
104 * GB: General band
105 *
106  WRITE( iounit, fmt = 9998 )path
107  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
108  WRITE( iounit, fmt = 9978 )
109  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
110  WRITE( iounit, fmt = 9962 )1
111  WRITE( iounit, fmt = 9960 )2
112  WRITE( iounit, fmt = 9959 )3
113  WRITE( iounit, fmt = 9958 )4
114  WRITE( iounit, fmt = 9957 )5
115  WRITE( iounit, fmt = 9956 )6
116  WRITE( iounit, fmt = 9955 )7
117  WRITE( iounit, fmt = '( '' Messages:'' )' )
118 *
119  ELSE IF( lsamen( 2, p2, 'GT' ) ) THEN
120 *
121 * GT: General tridiagonal
122 *
123  WRITE( iounit, fmt = 9997 )path
124  WRITE( iounit, fmt = 9977 )
125  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
126  WRITE( iounit, fmt = 9962 )1
127  WRITE( iounit, fmt = 9960 )2
128  WRITE( iounit, fmt = 9959 )3
129  WRITE( iounit, fmt = 9958 )4
130  WRITE( iounit, fmt = 9957 )5
131  WRITE( iounit, fmt = 9956 )6
132  WRITE( iounit, fmt = 9955 )7
133  WRITE( iounit, fmt = '( '' Messages:'' )' )
134 *
135  ELSE IF( lsamen( 2, p2, 'PO' ) .OR. lsamen( 2, p2, 'PP' ) ) THEN
136 *
137 * PO: Positive definite full
138 * PP: Positive definite packed
139 *
140  IF( sord ) THEN
141  sym = 'Symmetric'
142  ELSE
143  sym = 'Hermitian'
144  END IF
145  IF( lsame( c3, 'O' ) ) THEN
146  WRITE( iounit, fmt = 9996 )path, sym
147  ELSE
148  WRITE( iounit, fmt = 9995 )path, sym
149  END IF
150  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
151  WRITE( iounit, fmt = 9975 )path
152  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
153  WRITE( iounit, fmt = 9954 )1
154  WRITE( iounit, fmt = 9961 )2
155  WRITE( iounit, fmt = 9960 )3
156  WRITE( iounit, fmt = 9959 )4
157  WRITE( iounit, fmt = 9958 )5
158  WRITE( iounit, fmt = 9957 )6
159  WRITE( iounit, fmt = 9956 )7
160  WRITE( iounit, fmt = 9955 )8
161  WRITE( iounit, fmt = '( '' Messages:'' )' )
162 *
163  ELSE IF( lsamen( 2, p2, 'PS' ) ) THEN
164 *
165 * PS: Positive semi-definite full
166 *
167  IF( sord ) THEN
168  sym = 'Symmetric'
169  ELSE
170  sym = 'Hermitian'
171  END IF
172  IF( lsame( c1, 'S' ) .OR. lsame( c1, 'C' ) ) THEN
173  eigcnm = '1E04'
174  ELSE
175  eigcnm = '1D12'
176  END IF
177  WRITE( iounit, fmt = 9995 )path, sym
178  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
179  WRITE( iounit, fmt = 8973 )eigcnm, eigcnm, eigcnm
180  WRITE( iounit, fmt = '( '' Difference:'' )' )
181  WRITE( iounit, fmt = 8972 )c1
182  WRITE( iounit, fmt = '( '' Test ratio:'' )' )
183  WRITE( iounit, fmt = 8950 )
184  WRITE( iounit, fmt = '( '' Messages:'' )' )
185  ELSE IF( lsamen( 2, p2, 'PB' ) ) THEN
186 *
187 * PB: Positive definite band
188 *
189  IF( sord ) THEN
190  WRITE( iounit, fmt = 9994 )path, 'Symmetric'
191  ELSE
192  WRITE( iounit, fmt = 9994 )path, 'Hermitian'
193  END IF
194  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
195  WRITE( iounit, fmt = 9973 )path
196  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
197  WRITE( iounit, fmt = 9954 )1
198  WRITE( iounit, fmt = 9960 )2
199  WRITE( iounit, fmt = 9959 )3
200  WRITE( iounit, fmt = 9958 )4
201  WRITE( iounit, fmt = 9957 )5
202  WRITE( iounit, fmt = 9956 )6
203  WRITE( iounit, fmt = 9955 )7
204  WRITE( iounit, fmt = '( '' Messages:'' )' )
205 *
206  ELSE IF( lsamen( 2, p2, 'PT' ) ) THEN
207 *
208 * PT: Positive definite tridiagonal
209 *
210  IF( sord ) THEN
211  WRITE( iounit, fmt = 9993 )path, 'Symmetric'
212  ELSE
213  WRITE( iounit, fmt = 9993 )path, 'Hermitian'
214  END IF
215  WRITE( iounit, fmt = 9976 )
216  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
217  WRITE( iounit, fmt = 9952 )1
218  WRITE( iounit, fmt = 9960 )2
219  WRITE( iounit, fmt = 9959 )3
220  WRITE( iounit, fmt = 9958 )4
221  WRITE( iounit, fmt = 9957 )5
222  WRITE( iounit, fmt = 9956 )6
223  WRITE( iounit, fmt = 9955 )7
224  WRITE( iounit, fmt = '( '' Messages:'' )' )
225 *
226  ELSE IF( lsamen( 2, p2, 'SY' ) .OR. lsamen( 2, p2, 'SP' ) ) THEN
227 *
228 * SY: Symmetric indefinite full
229 * SP: Symmetric indefinite packed
230 *
231  IF( lsame( c3, 'Y' ) ) THEN
232  WRITE( iounit, fmt = 9992 )path, 'Symmetric'
233  ELSE
234  WRITE( iounit, fmt = 9991 )path, 'Symmetric'
235  END IF
236  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
237  IF( sord ) THEN
238  WRITE( iounit, fmt = 9972 )
239  ELSE
240  WRITE( iounit, fmt = 9971 )
241  END IF
242  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
243  WRITE( iounit, fmt = 9953 )1
244  WRITE( iounit, fmt = 9961 )2
245  WRITE( iounit, fmt = 9960 )3
246  WRITE( iounit, fmt = 9959 )4
247  WRITE( iounit, fmt = 9958 )5
248  WRITE( iounit, fmt = 9956 )6
249  WRITE( iounit, fmt = 9957 )7
250  WRITE( iounit, fmt = 9955 )8
251  WRITE( iounit, fmt = '( '' Messages:'' )' )
252 *
253  ELSE IF( lsamen( 2, p2, 'HE' ) .OR. lsamen( 2, p2, 'HP' ) ) THEN
254 *
255 * HE: Hermitian indefinite full
256 * HP: Hermitian indefinite packed
257 *
258  IF( lsame( c3, 'E' ) ) THEN
259  WRITE( iounit, fmt = 9992 )path, 'Hermitian'
260  ELSE
261  WRITE( iounit, fmt = 9991 )path, 'Hermitian'
262  END IF
263  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
264  WRITE( iounit, fmt = 9972 )
265  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
266  WRITE( iounit, fmt = 9953 )1
267  WRITE( iounit, fmt = 9961 )2
268  WRITE( iounit, fmt = 9960 )3
269  WRITE( iounit, fmt = 9959 )4
270  WRITE( iounit, fmt = 9958 )5
271  WRITE( iounit, fmt = 9956 )6
272  WRITE( iounit, fmt = 9957 )7
273  WRITE( iounit, fmt = 9955 )8
274  WRITE( iounit, fmt = '( '' Messages:'' )' )
275 *
276  ELSE IF( lsamen( 2, p2, 'TR' ) .OR. lsamen( 2, p2, 'TP' ) ) THEN
277 *
278 * TR: Triangular full
279 * TP: Triangular packed
280 *
281  IF( lsame( c3, 'R' ) ) THEN
282  WRITE( iounit, fmt = 9990 )path
283  subnam = path( 1: 1 ) // 'LATRS'
284  ELSE
285  WRITE( iounit, fmt = 9989 )path
286  subnam = path( 1: 1 ) // 'LATPS'
287  END IF
288  WRITE( iounit, fmt = 9966 )path
289  WRITE( iounit, fmt = 9965 )subnam(1:len_trim( subnam ))
290  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
291  WRITE( iounit, fmt = 9961 )1
292  WRITE( iounit, fmt = 9960 )2
293  WRITE( iounit, fmt = 9959 )3
294  WRITE( iounit, fmt = 9958 )4
295  WRITE( iounit, fmt = 9957 )5
296  WRITE( iounit, fmt = 9956 )6
297  WRITE( iounit, fmt = 9955 )7
298  WRITE( iounit, fmt = 9951 )subnam(1:len_trim( subnam )), 8
299  WRITE( iounit, fmt = '( '' Messages:'' )' )
300 *
301  ELSE IF( lsamen( 2, p2, 'TB' ) ) THEN
302 *
303 * TB: Triangular band
304 *
305  WRITE( iounit, fmt = 9988 )path
306  subnam = path( 1: 1 ) // 'LATBS'
307  WRITE( iounit, fmt = 9964 )path
308  WRITE( iounit, fmt = 9963 )subnam(1:len_trim( subnam ))
309  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
310  WRITE( iounit, fmt = 9960 )1
311  WRITE( iounit, fmt = 9959 )2
312  WRITE( iounit, fmt = 9958 )3
313  WRITE( iounit, fmt = 9957 )4
314  WRITE( iounit, fmt = 9956 )5
315  WRITE( iounit, fmt = 9955 )6
316  WRITE( iounit, fmt = 9951 )subnam(1:len_trim( subnam )), 7
317  WRITE( iounit, fmt = '( '' Messages:'' )' )
318 *
319  ELSE IF( lsamen( 2, p2, 'QR' ) ) THEN
320 *
321 * QR decomposition of rectangular matrices
322 *
323  WRITE( iounit, fmt = 9987 )path, 'QR'
324  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
325  WRITE( iounit, fmt = 9970 )
326  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
327  WRITE( iounit, fmt = 9950 )1
328  WRITE( iounit, fmt = 9946 )2
329  WRITE( iounit, fmt = 9944 )3, 'M'
330  WRITE( iounit, fmt = 9943 )4, 'M'
331  WRITE( iounit, fmt = 9942 )5, 'M'
332  WRITE( iounit, fmt = 9941 )6, 'M'
333  WRITE( iounit, fmt = 9960 )7
334  WRITE( iounit, fmt = 6660 )8
335  WRITE( iounit, fmt = '( '' Messages:'' )' )
336 *
337  ELSE IF( lsamen( 2, p2, 'LQ' ) ) THEN
338 *
339 * LQ decomposition of rectangular matrices
340 *
341  WRITE( iounit, fmt = 9987 )path, 'LQ'
342  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
343  WRITE( iounit, fmt = 9970 )
344  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
345  WRITE( iounit, fmt = 9949 )1
346  WRITE( iounit, fmt = 9945 )2
347  WRITE( iounit, fmt = 9944 )3, 'N'
348  WRITE( iounit, fmt = 9943 )4, 'N'
349  WRITE( iounit, fmt = 9942 )5, 'N'
350  WRITE( iounit, fmt = 9941 )6, 'N'
351  WRITE( iounit, fmt = 9960 )7
352  WRITE( iounit, fmt = '( '' Messages:'' )' )
353 *
354  ELSE IF( lsamen( 2, p2, 'QL' ) ) THEN
355 *
356 * QL decomposition of rectangular matrices
357 *
358  WRITE( iounit, fmt = 9987 )path, 'QL'
359  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
360  WRITE( iounit, fmt = 9970 )
361  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
362  WRITE( iounit, fmt = 9948 )1
363  WRITE( iounit, fmt = 9946 )2
364  WRITE( iounit, fmt = 9944 )3, 'M'
365  WRITE( iounit, fmt = 9943 )4, 'M'
366  WRITE( iounit, fmt = 9942 )5, 'M'
367  WRITE( iounit, fmt = 9941 )6, 'M'
368  WRITE( iounit, fmt = 9960 )7
369  WRITE( iounit, fmt = '( '' Messages:'' )' )
370 *
371  ELSE IF( lsamen( 2, p2, 'RQ' ) ) THEN
372 *
373 * RQ decomposition of rectangular matrices
374 *
375  WRITE( iounit, fmt = 9987 )path, 'RQ'
376  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
377  WRITE( iounit, fmt = 9970 )
378  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
379  WRITE( iounit, fmt = 9947 )1
380  WRITE( iounit, fmt = 9945 )2
381  WRITE( iounit, fmt = 9944 )3, 'N'
382  WRITE( iounit, fmt = 9943 )4, 'N'
383  WRITE( iounit, fmt = 9942 )5, 'N'
384  WRITE( iounit, fmt = 9941 )6, 'N'
385  WRITE( iounit, fmt = 9960 )7
386  WRITE( iounit, fmt = '( '' Messages:'' )' )
387 *
388  ELSE IF( lsamen( 2, p2, 'QP' ) ) THEN
389 *
390 * QR decomposition with column pivoting
391 *
392  WRITE( iounit, fmt = 9986 )path
393  WRITE( iounit, fmt = 9969 )
394  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
395  WRITE( iounit, fmt = 9940 )1
396  WRITE( iounit, fmt = 9939 )2
397  WRITE( iounit, fmt = 9938 )3
398  WRITE( iounit, fmt = '( '' Messages:'' )' )
399 *
400  ELSE IF( lsamen( 2, p2, 'TZ' ) ) THEN
401 *
402 * TZ: Trapezoidal
403 *
404  WRITE( iounit, fmt = 9985 )path
405  WRITE( iounit, fmt = 9968 )
406  WRITE( iounit, fmt = 9929 )c1, c1
407  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
408  WRITE( iounit, fmt = 9940 )1
409  WRITE( iounit, fmt = 9937 )2
410  WRITE( iounit, fmt = 9938 )3
411  WRITE( iounit, fmt = 9940 )4
412  WRITE( iounit, fmt = 9937 )5
413  WRITE( iounit, fmt = 9938 )6
414  WRITE( iounit, fmt = '( '' Messages:'' )' )
415 *
416  ELSE IF( lsamen( 2, p2, 'LS' ) ) THEN
417 *
418 * LS: Least Squares driver routines for
419 * LS, LSD, LSS, LSX and LSY.
420 *
421  WRITE( iounit, fmt = 9984 )path
422  WRITE( iounit, fmt = 9967 )
423  WRITE( iounit, fmt = 9921 )c1, c1, c1, c1, c1
424  WRITE( iounit, fmt = 9935 )1
425  WRITE( iounit, fmt = 9931 )2
426  WRITE( iounit, fmt = 9933 )3
427  WRITE( iounit, fmt = 9935 )4
428  WRITE( iounit, fmt = 9934 )5
429  WRITE( iounit, fmt = 9932 )6
430  WRITE( iounit, fmt = 9920 )
431  WRITE( iounit, fmt = '( '' Messages:'' )' )
432 *
433  ELSE IF( lsamen( 2, p2, 'LU' ) ) THEN
434 *
435 * LU factorization variants
436 *
437  WRITE( iounit, fmt = 9983 )path
438  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
439  WRITE( iounit, fmt = 9979 )
440  WRITE( iounit, fmt = '( '' Test ratio:'' )' )
441  WRITE( iounit, fmt = 9962 )1
442  WRITE( iounit, fmt = '( '' Messages:'' )' )
443 *
444  ELSE IF( lsamen( 2, p2, 'CH' ) ) THEN
445 *
446 * Cholesky factorization variants
447 *
448  WRITE( iounit, fmt = 9982 )path
449  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
450  WRITE( iounit, fmt = 9974 )
451  WRITE( iounit, fmt = '( '' Test ratio:'' )' )
452  WRITE( iounit, fmt = 9954 )1
453  WRITE( iounit, fmt = '( '' Messages:'' )' )
454 *
455  ELSE IF( lsamen( 2, p2, 'QS' ) ) THEN
456 *
457 * QR factorization variants
458 *
459  WRITE( iounit, fmt = 9981 )path
460  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
461  WRITE( iounit, fmt = 9970 )
462  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
463 *
464  ELSE
465 *
466 * Print error message if no header is available.
467 *
468  WRITE( iounit, fmt = 9980 )path
469  END IF
470 *
471 * First line of header
472 *
473  9999 format( / 1x, a3, ': General dense matrices' )
474  9998 format( / 1x, a3, ': General band matrices' )
475  9997 format( / 1x, a3, ': General tridiagonal' )
476  9996 format( / 1x, a3, ': ', a9, ' positive definite matrices' )
477  9995 format( / 1x, a3, ': ', a9, ' positive definite packed matrices'
478  $ )
479  9994 format( / 1x, a3, ': ', a9, ' positive definite band matrices' )
480  9993 format( / 1x, a3, ': ', a9, ' positive definite tridiagonal' )
481  9992 format( / 1x, a3, ': ', a9, ' indefinite matrices' )
482  9991 format( / 1x, a3, ': ', a9, ' indefinite packed matrices' )
483  9990 format( / 1x, a3, ': Triangular matrices' )
484  9989 format( / 1x, a3, ': Triangular packed matrices' )
485  9988 format( / 1x, a3, ': Triangular band matrices' )
486  9987 format( / 1x, a3, ': ', a2, ' factorization of general matrices'
487  $ )
488  9986 format( / 1x, a3, ': QR factorization with column pivoting' )
489  9985 format( / 1x, a3, ': RQ factorization of trapezoidal matrix' )
490  9984 format( / 1x, a3, ': Least squares driver routines' )
491  9983 format( / 1x, a3, ': LU factorization variants' )
492  9982 format( / 1x, a3, ': Cholesky factorization variants' )
493  9981 format( / 1x, a3, ': QR factorization variants' )
494  9980 format( / 1x, a3, ': No header available' )
495 *
496 * GE matrix types
497 *
498  9979 format( 4x, '1. Diagonal', 24x, '7. Last n/2 columns zero', / 4x,
499  $ '2. Upper triangular', 16x,
500  $ '8. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
501  $ '3. Lower triangular', 16x, '9. Random, CNDNUM = 0.1/EPS',
502  $ / 4x, '4. Random, CNDNUM = 2', 13x,
503  $ '10. Scaled near underflow', / 4x, '5. First column zero',
504  $ 14x, '11. Scaled near overflow', / 4x,
505  $ '6. Last column zero' )
506 *
507 * GB matrix types
508 *
509  9978 format( 4x, '1. Random, CNDNUM = 2', 14x,
510  $ '5. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
511  $ '2. First column zero', 15x, '6. Random, CNDNUM = .01/EPS',
512  $ / 4x, '3. Last column zero', 16x,
513  $ '7. Scaled near underflow', / 4x,
514  $ '4. Last n/2 columns zero', 11x, '8. Scaled near overflow' )
515 *
516 * GT matrix types
517 *
518  9977 format( ' Matrix types (1-6 have specified condition numbers):',
519  $ / 4x, '1. Diagonal', 24x, '7. Random, unspecified CNDNUM',
520  $ / 4x, '2. Random, CNDNUM = 2', 14x, '8. First column zero',
521  $ / 4x, '3. Random, CNDNUM = sqrt(0.1/EPS)', 2x,
522  $ '9. Last column zero', / 4x, '4. Random, CNDNUM = 0.1/EPS',
523  $ 7x, '10. Last n/2 columns zero', / 4x,
524  $ '5. Scaled near underflow', 10x,
525  $ '11. Scaled near underflow', / 4x,
526  $ '6. Scaled near overflow', 11x, '12. Scaled near overflow' )
527 *
528 * PT matrix types
529 *
530  9976 format( ' Matrix types (1-6 have specified condition numbers):',
531  $ / 4x, '1. Diagonal', 24x, '7. Random, unspecified CNDNUM',
532  $ / 4x, '2. Random, CNDNUM = 2', 14x,
533  $ '8. First row and column zero', / 4x,
534  $ '3. Random, CNDNUM = sqrt(0.1/EPS)', 2x,
535  $ '9. Last row and column zero', / 4x,
536  $ '4. Random, CNDNUM = 0.1/EPS', 7x,
537  $ '10. Middle row and column zero', / 4x,
538  $ '5. Scaled near underflow', 10x,
539  $ '11. Scaled near underflow', / 4x,
540  $ '6. Scaled near overflow', 11x, '12. Scaled near overflow' )
541 *
542 * PO, PP matrix types
543 *
544  9975 format( 4x, '1. Diagonal', 24x,
545  $ '6. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
546  $ '2. Random, CNDNUM = 2', 14x, '7. Random, CNDNUM = 0.1/EPS',
547  $ / 3x, '*3. First row and column zero', 7x,
548  $ '8. Scaled near underflow', / 3x,
549  $ '*4. Last row and column zero', 8x,
550  $ '9. Scaled near overflow', / 3x,
551  $ '*5. Middle row and column zero', / 3x,
552  $ '(* - tests error exits from ', a3,
553  $ 'TRF, no test ratios are computed)' )
554 *
555 * CH matrix types
556 *
557  9974 format( 4x, '1. Diagonal', 24x,
558  $ '6. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
559  $ '2. Random, CNDNUM = 2', 14x, '7. Random, CNDNUM = 0.1/EPS',
560  $ / 3x, '*3. First row and column zero', 7x,
561  $ '8. Scaled near underflow', / 3x,
562  $ '*4. Last row and column zero', 8x,
563  $ '9. Scaled near overflow', / 3x,
564  $ '*5. Middle row and column zero', / 3x,
565  $ '(* - tests error exits, no test ratios are computed)' )
566 *
567 * PS matrix types
568 *
569  8973 format( 4x, '1. Diagonal', / 4x, '2. Random, CNDNUM = 2', 14x,
570  $ / 3x, '*3. Nonzero eigenvalues of: D(1:RANK-1)=1 and ',
571  $ 'D(RANK) = 1.0/', a4, / 3x,
572  $ '*4. Nonzero eigenvalues of: D(1)=1 and ',
573  $ ' D(2:RANK) = 1.0/', a4, / 3x,
574  $ '*5. Nonzero eigenvalues of: D(I) = ', a4,
575  $ '**(-(I-1)/(RANK-1)) ', ' I=1:RANK', / 4x,
576  $ '6. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
577  $ '7. Random, CNDNUM = 0.1/EPS', / 4x,
578  $ '8. Scaled near underflow', / 4x, '9. Scaled near overflow',
579  $ / 3x, '(* - Semi-definite tests )' )
580  8972 format( 3x, 'RANK minus computed rank, returned by ', a, 'PSTRF' )
581 *
582 * PB matrix types
583 *
584  9973 format( 4x, '1. Random, CNDNUM = 2', 14x,
585  $ '5. Random, CNDNUM = sqrt(0.1/EPS)', / 3x,
586  $ '*2. First row and column zero', 7x,
587  $ '6. Random, CNDNUM = 0.1/EPS', / 3x,
588  $ '*3. Last row and column zero', 8x,
589  $ '7. Scaled near underflow', / 3x,
590  $ '*4. Middle row and column zero', 6x,
591  $ '8. Scaled near overflow', / 3x,
592  $ '(* - tests error exits from ', a3,
593  $ 'TRF, no test ratios are computed)' )
594 *
595 * SSY, SSP, CHE, CHP matrix types
596 *
597  9972 format( 4x, '1. Diagonal', 24x,
598  $ '6. Last n/2 rows and columns zero', / 4x,
599  $ '2. Random, CNDNUM = 2', 14x,
600  $ '7. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
601  $ '3. First row and column zero', 7x,
602  $ '8. Random, CNDNUM = 0.1/EPS', / 4x,
603  $ '4. Last row and column zero', 8x,
604  $ '9. Scaled near underflow', / 4x,
605  $ '5. Middle row and column zero', 5x,
606  $ '10. Scaled near overflow' )
607 *
608 * CSY, CSP matrix types
609 *
610  9971 format( 4x, '1. Diagonal', 24x,
611  $ '7. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
612  $ '2. Random, CNDNUM = 2', 14x, '8. Random, CNDNUM = 0.1/EPS',
613  $ / 4x, '3. First row and column zero', 7x,
614  $ '9. Scaled near underflow', / 4x,
615  $ '4. Last row and column zero', 7x,
616  $ '10. Scaled near overflow', / 4x,
617  $ '5. Middle row and column zero', 5x,
618  $ '11. Block diagonal matrix', / 4x,
619  $ '6. Last n/2 rows and columns zero' )
620 *
621 * QR matrix types
622 *
623  9970 format( 4x, '1. Diagonal', 24x,
624  $ '5. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
625  $ '2. Upper triangular', 16x, '6. Random, CNDNUM = 0.1/EPS',
626  $ / 4x, '3. Lower triangular', 16x,
627  $ '7. Scaled near underflow', / 4x, '4. Random, CNDNUM = 2',
628  $ 14x, '8. Scaled near overflow' )
629 *
630 * QP matrix types
631 *
632  9969 format( ' Matrix types (2-6 have condition 1/EPS):', / 4x,
633  $ '1. Zero matrix', 21x, '4. First n/2 columns fixed', / 4x,
634  $ '2. One small eigenvalue', 12x, '5. Last n/2 columns fixed',
635  $ / 4x, '3. Geometric distribution', 10x,
636  $ '6. Every second column fixed' )
637 *
638 * TZ matrix types
639 *
640  9968 format( ' Matrix types (2-3 have condition 1/EPS):', / 4x,
641  $ '1. Zero matrix', / 4x, '2. One small eigenvalue', / 4x,
642  $ '3. Geometric distribution' )
643 *
644 * LS matrix types
645 *
646  9967 format( ' Matrix types (1-3: full rank, 4-6: rank deficient):',
647  $ / 4x, '1 and 4. Normal scaling', / 4x,
648  $ '2 and 5. Scaled near overflow', / 4x,
649  $ '3 and 6. Scaled near underflow' )
650 *
651 * TR, TP matrix types
652 *
653  9966 format( ' Matrix types for ', a3, ' routines:', / 4x,
654  $ '1. Diagonal', 24x, '6. Scaled near overflow', / 4x,
655  $ '2. Random, CNDNUM = 2', 14x, '7. Identity', / 4x,
656  $ '3. Random, CNDNUM = sqrt(0.1/EPS) ',
657  $ '8. Unit triangular, CNDNUM = 2', / 4x,
658  $ '4. Random, CNDNUM = 0.1/EPS', 8x,
659  $ '9. Unit, CNDNUM = sqrt(0.1/EPS)', / 4x,
660  $ '5. Scaled near underflow', 10x,
661  $ '10. Unit, CNDNUM = 0.1/EPS' )
662  9965 format( ' Special types for testing ', a, ':', / 3x,
663  $ '11. Matrix elements are O(1), large right hand side', / 3x,
664  $ '12. First diagonal causes overflow,',
665  $ ' offdiagonal column norms < 1', / 3x,
666  $ '13. First diagonal causes overflow,',
667  $ ' offdiagonal column norms > 1', / 3x,
668  $ '14. Growth factor underflows, solution does not overflow',
669  $ / 3x, '15. Small diagonal causes gradual overflow', / 3x,
670  $ '16. One zero diagonal element', / 3x,
671  $ '17. Large offdiagonals cause overflow when adding a column'
672  $ , / 3x, '18. Unit triangular with large right hand side' )
673 *
674 * TB matrix types
675 *
676  9964 format( ' Matrix types for ', a3, ' routines:', / 4x,
677  $ '1. Random, CNDNUM = 2', 14x, '6. Identity', / 4x,
678  $ '2. Random, CNDNUM = sqrt(0.1/EPS) ',
679  $ '7. Unit triangular, CNDNUM = 2', / 4x,
680  $ '3. Random, CNDNUM = 0.1/EPS', 8x,
681  $ '8. Unit, CNDNUM = sqrt(0.1/EPS)', / 4x,
682  $ '4. Scaled near underflow', 11x,
683  $ '9. Unit, CNDNUM = 0.1/EPS', / 4x,
684  $ '5. Scaled near overflow' )
685  9963 format( ' Special types for testing ', a, ':', / 3x,
686  $ '10. Matrix elements are O(1), large right hand side', / 3x,
687  $ '11. First diagonal causes overflow,',
688  $ ' offdiagonal column norms < 1', / 3x,
689  $ '12. First diagonal causes overflow,',
690  $ ' offdiagonal column norms > 1', / 3x,
691  $ '13. Growth factor underflows, solution does not overflow',
692  $ / 3x, '14. Small diagonal causes gradual overflow', / 3x,
693  $ '15. One zero diagonal element', / 3x,
694  $ '16. Large offdiagonals cause overflow when adding a column'
695  $ , / 3x, '17. Unit triangular with large right hand side' )
696 *
697 * Test ratios
698 *
699  9962 format( 3x, i2, ': norm( L * U - A ) / ( N * norm(A) * EPS )' )
700  9961 format( 3x, i2, ': norm( I - A*AINV ) / ',
701  $ '( N * norm(A) * norm(AINV) * EPS )' )
702  9960 format( 3x, i2, ': norm( B - A * X ) / ',
703  $ '( norm(A) * norm(X) * EPS )' )
704  6660 format( 3x, i2, ': diagonal is not non-negative')
705  9959 format( 3x, i2, ': norm( X - XACT ) / ',
706  $ '( norm(XACT) * CNDNUM * EPS )' )
707  9958 format( 3x, i2, ': norm( X - XACT ) / ',
708  $ '( norm(XACT) * CNDNUM * EPS ), refined' )
709  9957 format( 3x, i2, ': norm( X - XACT ) / ',
710  $ '( norm(XACT) * (error bound) )' )
711  9956 format( 3x, i2, ': (backward error) / EPS' )
712  9955 format( 3x, i2, ': RCOND * CNDNUM - 1.0' )
713  9954 format( 3x, i2, ': norm( U'' * U - A ) / ( N * norm(A) * EPS )',
714  $ ', or', / 7x, 'norm( L * L'' - A ) / ( N * norm(A) * EPS )'
715  $ )
716  8950 format( 3x,
717  $ 'norm( P * U'' * U * P'' - A ) / ( N * norm(A) * EPS )',
718  $ ', or', / 3x,
719  $ 'norm( P * L * L'' * P'' - A ) / ( N * norm(A) * EPS )' )
720  9953 format( 3x, i2, ': norm( U*D*U'' - A ) / ( N * norm(A) * EPS )',
721  $ ', or', / 7x, 'norm( L*D*L'' - A ) / ( N * norm(A) * EPS )'
722  $ )
723  9952 format( 3x, i2, ': norm( U''*D*U - A ) / ( N * norm(A) * EPS )',
724  $ ', or', / 7x, 'norm( L*D*L'' - A ) / ( N * norm(A) * EPS )'
725  $ )
726  9951 format( ' Test ratio for ', a, ':', / 3x, i2,
727  $ ': norm( s*b - A*x ) / ( norm(A) * norm(x) * EPS )' )
728  9950 format( 3x, i2, ': norm( R - Q'' * A ) / ( M * norm(A) * EPS )' )
729  9949 format( 3x, i2, ': norm( L - A * Q'' ) / ( N * norm(A) * EPS )' )
730  9948 format( 3x, i2, ': norm( L - Q'' * A ) / ( M * norm(A) * EPS )' )
731  9947 format( 3x, i2, ': norm( R - A * Q'' ) / ( N * norm(A) * EPS )' )
732  9946 format( 3x, i2, ': norm( I - Q''*Q ) / ( M * EPS )' )
733  9945 format( 3x, i2, ': norm( I - Q*Q'' ) / ( N * EPS )' )
734  9944 format( 3x, i2, ': norm( Q*C - Q*C ) / ', '( ', a1,
735  $ ' * norm(C) * EPS )' )
736  9943 format( 3x, i2, ': norm( C*Q - C*Q ) / ', '( ', a1,
737  $ ' * norm(C) * EPS )' )
738  9942 format( 3x, i2, ': norm( Q''*C - Q''*C )/ ', '( ', a1,
739  $ ' * norm(C) * EPS )' )
740  9941 format( 3x, i2, ': norm( C*Q'' - C*Q'' )/ ', '( ', a1,
741  $ ' * norm(C) * EPS )' )
742  9940 format( 3x, i2, ': norm(svd(A) - svd(R)) / ',
743  $ '( M * norm(svd(R)) * EPS )' )
744  9939 format( 3x, i2, ': norm( A*P - Q*R ) / ( M * norm(A) * EPS )'
745  $ )
746  9938 format( 3x, i2, ': norm( I - Q''*Q ) / ( M * EPS )' )
747  9937 format( 3x, i2, ': norm( A - R*Q ) / ( M * norm(A) * EPS )'
748  $ )
749  9936 format( ' Test ratios (1-2: ', a1, 'GELS, 3-6: ', a1,
750  $ 'GELSS, 7-10: ', a1, 'GELSX):' )
751  9935 format( 3x, i2, ': norm( B - A * X ) / ',
752  $ '( max(M,N) * norm(A) * norm(X) * EPS )' )
753  9934 format( 3x, i2, ': norm( (A*X-B)'' *A ) / ',
754  $ '( max(M,N,NRHS) * norm(A) * norm(B) * EPS )' )
755  9933 format( 3x, i2, ': norm(svd(A)-svd(R)) / ',
756  $ '( min(M,N) * norm(svd(R)) * EPS )' )
757  9932 format( 3x, i2, ': Check if X is in the row space of A or A''' )
758  9931 format( 3x, i2, ': norm( (A*X-B)'' *A ) / ',
759  $ '( max(M,N,NRHS) * norm(A) * norm(B) * EPS )', / 7x,
760  $ 'if TRANS=''N'.GE.' and MN or TRANS=''T'.LT.' and MN, ',
761  $ 'otherwise', / 7x,
762  $ 'check if X is in the row space of A or A'' ',
763  $ '(overdetermined case)' )
764  9930 format( 3x, ' 7-10: same as 3-6' )
765  9929 format( ' Test ratios (1-3: ', a1, 'TZRQF, 4-6: ', a1,
766  $ 'TZRZF):' )
767  9920 format( 3x, ' 7-10: same as 3-6', 3x, ' 11-14: same as 3-6',
768  $ 3x, ' 15-18: same as 3-6' )
769  9921 format( ' Test ratios:', / ' (1-2: ', a1, 'GELS, 3-6: ', a1,
770  $ 'GELSX, 7-10: ', a1, 'GELSY, 11-14: ', a1, 'GELSS, 15-18: ',
771  $ a1, 'GELSD)' )
772 *
773  return
774 *
775 * End of ALAHD
776 *
777  END