LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
aladhd.f
Go to the documentation of this file.
1 *> \brief \b ALADHD
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ALADHD( IOUNIT, PATH )
12 *
13 * .. Scalar Arguments ..
14 * CHARACTER*3 PATH
15 * INTEGER IOUNIT
16 * ..
17 *
18 *
19 *> \par Purpose:
20 * =============
21 *>
22 *> \verbatim
23 *>
24 *> ALADHD prints header information for the driver routines test paths.
25 *> \endverbatim
26 *
27 * Arguments:
28 * ==========
29 *
30 *> \param[in] IOUNIT
31 *> \verbatim
32 *> IOUNIT is INTEGER
33 *> The unit number to which the header information should be
34 *> printed.
35 *> \endverbatim
36 *>
37 *> \param[in] PATH
38 *> \verbatim
39 *> PATH is CHARACTER*3
40 *> The name of the path for which the header information is to
41 *> be printed. Current paths are
42 *> _GE: General matrices
43 *> _GB: General band
44 *> _GT: General Tridiagonal
45 *> _PO: Symmetric or Hermitian positive definite
46 *> _PS: Symmetric or Hermitian positive semi-definite
47 *> _PP: Symmetric or Hermitian positive definite packed
48 *> _PB: Symmetric or Hermitian positive definite band
49 *> _PT: Symmetric or Hermitian positive definite tridiagonal
50 *> _SY: Symmetric indefinite,
51 *> with partial (Bunch-Kaufman) pivoting
52 *> _SR: Symmetric indefinite,
53 *> with "rook" (bounded Bunch-Kaufman) pivoting
54 *> _SP: Symmetric indefinite packed,
55 *> with partial (Bunch-Kaufman) pivoting
56 *> _HE: (complex) Hermitian indefinite,
57 *> with partial (Bunch-Kaufman) pivoting
58 *> _HR: (complex) Hermitian indefinite,
59 *> with "rook" (bounded Bunch-Kaufman) pivoting
60 *> _HP: (complex) Hermitian indefinite packed,
61 *> with partial (Bunch-Kaufman) pivoting
62 *> The first character must be one of S, D, C, or Z (C or Z only
63 *> if complex).
64 *> \endverbatim
65 *
66 * Authors:
67 * ========
68 *
69 *> \author Univ. of Tennessee
70 *> \author Univ. of California Berkeley
71 *> \author Univ. of Colorado Denver
72 *> \author NAG Ltd.
73 *
74 *> \date November 2013
75 *
76 *> \ingroup aux_lin
77 *
78 * =====================================================================
79  SUBROUTINE aladhd( IOUNIT, PATH )
80 *
81 * -- LAPACK test routine (version 3.5.0) --
82 * -- LAPACK is a software package provided by Univ. of Tennessee, --
83 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
84 * November 2013
85 *
86 * .. Scalar Arguments ..
87  CHARACTER*3 PATH
88  INTEGER IOUNIT
89 * ..
90 *
91 * =====================================================================
92 *
93 * .. Local Scalars ..
94  LOGICAL CORZ, SORD
95  CHARACTER C1, C3
96  CHARACTER*2 P2
97  CHARACTER*9 SYM
98 * ..
99 * .. External Functions ..
100  LOGICAL LSAME, LSAMEN
101  EXTERNAL lsame, lsamen
102 * ..
103 * .. Executable Statements ..
104 *
105  IF( iounit.LE.0 )
106  $ RETURN
107  c1 = path( 1: 1 )
108  c3 = path( 3: 3 )
109  p2 = path( 2: 3 )
110  sord = lsame( c1, 'S' ) .OR. lsame( c1, 'D' )
111  corz = lsame( c1, 'C' ) .OR. lsame( c1, 'Z' )
112  IF( .NOT.( sord .OR. corz ) )
113  $ RETURN
114 *
115  IF( lsamen( 2, p2, 'GE' ) ) THEN
116 *
117 * GE: General dense
118 *
119  WRITE( iounit, fmt = 9999 )path
120  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
121  WRITE( iounit, fmt = 9989 )
122  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
123  WRITE( iounit, fmt = 9981 )1
124  WRITE( iounit, fmt = 9980 )2
125  WRITE( iounit, fmt = 9979 )3
126  WRITE( iounit, fmt = 9978 )4
127  WRITE( iounit, fmt = 9977 )5
128  WRITE( iounit, fmt = 9976 )6
129  WRITE( iounit, fmt = 9972 )7
130  WRITE( iounit, fmt = '( '' Messages:'' )' )
131 *
132  ELSE IF( lsamen( 2, p2, 'GB' ) ) THEN
133 *
134 * GB: General band
135 *
136  WRITE( iounit, fmt = 9998 )path
137  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
138  WRITE( iounit, fmt = 9988 )
139  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
140  WRITE( iounit, fmt = 9981 )1
141  WRITE( iounit, fmt = 9980 )2
142  WRITE( iounit, fmt = 9979 )3
143  WRITE( iounit, fmt = 9978 )4
144  WRITE( iounit, fmt = 9977 )5
145  WRITE( iounit, fmt = 9976 )6
146  WRITE( iounit, fmt = 9972 )7
147  WRITE( iounit, fmt = '( '' Messages:'' )' )
148 *
149  ELSE IF( lsamen( 2, p2, 'GT' ) ) THEN
150 *
151 * GT: General tridiagonal
152 *
153  WRITE( iounit, fmt = 9997 )path
154  WRITE( iounit, fmt = 9987 )
155  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
156  WRITE( iounit, fmt = 9981 )1
157  WRITE( iounit, fmt = 9980 )2
158  WRITE( iounit, fmt = 9979 )3
159  WRITE( iounit, fmt = 9978 )4
160  WRITE( iounit, fmt = 9977 )5
161  WRITE( iounit, fmt = 9976 )6
162  WRITE( iounit, fmt = '( '' Messages:'' )' )
163 *
164  ELSE IF( lsamen( 2, p2, 'PO' ) .OR. lsamen( 2, p2, 'PP' )
165  $ .OR. lsamen( 2, p2, 'PS' ) ) THEN
166 *
167 * PO: Positive definite full
168 * PS: Positive definite full
169 * PP: Positive definite packed
170 *
171  IF( sord ) THEN
172  sym = 'Symmetric'
173  ELSE
174  sym = 'Hermitian'
175  END IF
176  IF( lsame( c3, 'O' ) ) THEN
177  WRITE( iounit, fmt = 9996 )path, sym
178  ELSE
179  WRITE( iounit, fmt = 9995 )path, sym
180  END IF
181  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
182  WRITE( iounit, fmt = 9985 )path
183  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
184  WRITE( iounit, fmt = 9975 )1
185  WRITE( iounit, fmt = 9980 )2
186  WRITE( iounit, fmt = 9979 )3
187  WRITE( iounit, fmt = 9978 )4
188  WRITE( iounit, fmt = 9977 )5
189  WRITE( iounit, fmt = 9976 )6
190  WRITE( iounit, fmt = '( '' Messages:'' )' )
191 *
192  ELSE IF( lsamen( 2, p2, 'PB' ) ) THEN
193 *
194 * PB: Positive definite band
195 *
196  IF( sord ) THEN
197  WRITE( iounit, fmt = 9994 )path, 'Symmetric'
198  ELSE
199  WRITE( iounit, fmt = 9994 )path, 'Hermitian'
200  END IF
201  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
202  WRITE( iounit, fmt = 9984 )path
203  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
204  WRITE( iounit, fmt = 9975 )1
205  WRITE( iounit, fmt = 9980 )2
206  WRITE( iounit, fmt = 9979 )3
207  WRITE( iounit, fmt = 9978 )4
208  WRITE( iounit, fmt = 9977 )5
209  WRITE( iounit, fmt = 9976 )6
210  WRITE( iounit, fmt = '( '' Messages:'' )' )
211 *
212  ELSE IF( lsamen( 2, p2, 'PT' ) ) THEN
213 *
214 * PT: Positive definite tridiagonal
215 *
216  IF( sord ) THEN
217  WRITE( iounit, fmt = 9993 )path, 'Symmetric'
218  ELSE
219  WRITE( iounit, fmt = 9993 )path, 'Hermitian'
220  END IF
221  WRITE( iounit, fmt = 9986 )
222  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
223  WRITE( iounit, fmt = 9973 )1
224  WRITE( iounit, fmt = 9980 )2
225  WRITE( iounit, fmt = 9979 )3
226  WRITE( iounit, fmt = 9978 )4
227  WRITE( iounit, fmt = 9977 )5
228  WRITE( iounit, fmt = 9976 )6
229  WRITE( iounit, fmt = '( '' Messages:'' )' )
230 *
231  ELSE IF( lsamen( 2, p2, 'SY' ) .OR. lsamen( 2, p2, 'SP' ) ) THEN
232 *
233 * SY: Symmetric indefinite full
234 * with partial (Bunch-Kaufman) pivoting algorithm
235 * SP: Symmetric indefinite packed
236 * with partial (Bunch-Kaufman) pivoting algorithm
237 *
238  IF( lsame( c3, 'Y' ) ) THEN
239  WRITE( iounit, fmt = 9992 )path, 'Symmetric'
240  ELSE
241  WRITE( iounit, fmt = 9991 )path, 'Symmetric'
242  END IF
243  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
244  IF( sord ) THEN
245  WRITE( iounit, fmt = 9983 )
246  ELSE
247  WRITE( iounit, fmt = 9982 )
248  END IF
249  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
250  WRITE( iounit, fmt = 9974 )1
251  WRITE( iounit, fmt = 9980 )2
252  WRITE( iounit, fmt = 9979 )3
253  WRITE( iounit, fmt = 9977 )4
254  WRITE( iounit, fmt = 9978 )5
255  WRITE( iounit, fmt = 9976 )6
256  WRITE( iounit, fmt = '( '' Messages:'' )' )
257 *
258  ELSE IF( lsamen( 2, p2, 'SR' ) ) THEN
259 *
260 * SR: Symmetric indefinite full,
261 * with "rook" (bounded Bunch-Kaufman) pivoting algorithm
262 *
263  WRITE( iounit, fmt = 9992 )path, 'Symmetric'
264 *
265  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
266  IF( sord ) THEN
267  WRITE( iounit, fmt = 9983 )
268  ELSE
269  WRITE( iounit, fmt = 9982 )
270  END IF
271 *
272  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
273  WRITE( iounit, fmt = 9974 )1
274  WRITE( iounit, fmt = 9980 )2
275  WRITE( iounit, fmt = 9979 )3
276  WRITE( iounit, fmt = '( '' Messages:'' )' )
277 *
278  ELSE IF( lsamen( 2, p2, 'HE' ) .OR. lsamen( 2, p2, 'HP' ) ) THEN
279 *
280 * HE: Hermitian indefinite full
281 * with partial (Bunch-Kaufman) pivoting algorithm
282 * HP: Hermitian indefinite packed
283 * with partial (Bunch-Kaufman) pivoting algorithm
284 *
285  IF( lsame( c3, 'E' ) ) THEN
286  WRITE( iounit, fmt = 9992 )path, 'Hermitian'
287  ELSE
288  WRITE( iounit, fmt = 9991 )path, 'Hermitian'
289  END IF
290 *
291  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
292  WRITE( iounit, fmt = 9983 )
293 *
294  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
295  WRITE( iounit, fmt = 9974 )1
296  WRITE( iounit, fmt = 9980 )2
297  WRITE( iounit, fmt = 9979 )3
298  WRITE( iounit, fmt = 9977 )4
299  WRITE( iounit, fmt = 9978 )5
300  WRITE( iounit, fmt = 9976 )6
301  WRITE( iounit, fmt = '( '' Messages:'' )' )
302 *
303  ELSE IF( lsamen( 2, p2, 'HR' ) ) THEN
304 *
305 * HR: Hermitian indefinite full,
306 * with "rook" (bounded Bunch-Kaufman) pivoting algorithm
307 *
308  WRITE( iounit, fmt = 9992 )path, 'Hermitian'
309 *
310  WRITE( iounit, fmt = '( '' Matrix types:'' )' )
311  WRITE( iounit, fmt = 9983 )
312 *
313  WRITE( iounit, fmt = '( '' Test ratios:'' )' )
314  WRITE( iounit, fmt = 9974 )1
315  WRITE( iounit, fmt = 9980 )2
316  WRITE( iounit, fmt = 9979 )3
317  WRITE( iounit, fmt = '( '' Messages:'' )' )
318 *
319  ELSE
320 *
321 * Print error message if no header is available.
322 *
323  WRITE( iounit, fmt = 9990 )path
324  END IF
325 *
326 * First line of header
327 *
328  9999 FORMAT( / 1x, a3, ' drivers: General dense matrices' )
329  9998 FORMAT( / 1x, a3, ' drivers: General band matrices' )
330  9997 FORMAT( / 1x, a3, ' drivers: General tridiagonal' )
331  9996 FORMAT( / 1x, a3, ' drivers: ', a9,
332  $ ' positive definite matrices' )
333  9995 FORMAT( / 1x, a3, ' drivers: ', a9,
334  $ ' positive definite packed matrices' )
335  9994 FORMAT( / 1x, a3, ' drivers: ', a9,
336  $ ' positive definite band matrices' )
337  9993 FORMAT( / 1x, a3, ' drivers: ', a9,
338  $ ' positive definite tridiagonal' )
339  9992 FORMAT( / 1x, a3, ' drivers: ', a9, ' indefinite matrices',
340  $ ', "rook" (bounded Bunch-Kaufman) pivoting' )
341  9991 FORMAT( / 1x, a3, ' drivers: ', a9,
342  $ ' indefinite packed matrices',
343  $ ', partial (Bunch-Kaufman) pivoting' )
344  9891 FORMAT( / 1x, a3, ' drivers: ', a9,
345  $ ' indefinite packed matrices',
346  $ ', "rook" (bounded Bunch-Kaufman) pivoting' )
347  9990 FORMAT( / 1x, a3, ': No header available' )
348 *
349 * GE matrix types
350 *
351  9989 FORMAT( 4x, '1. Diagonal', 24x, '7. Last n/2 columns zero', / 4x,
352  $ '2. Upper triangular', 16x,
353  $ '8. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
354  $ '3. Lower triangular', 16x, '9. Random, CNDNUM = 0.1/EPS',
355  $ / 4x, '4. Random, CNDNUM = 2', 13x,
356  $ '10. Scaled near underflow', / 4x, '5. First column zero',
357  $ 14x, '11. Scaled near overflow', / 4x,
358  $ '6. Last column zero' )
359 *
360 * GB matrix types
361 *
362  9988 FORMAT( 4x, '1. Random, CNDNUM = 2', 14x,
363  $ '5. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
364  $ '2. First column zero', 15x, '6. Random, CNDNUM = 0.1/EPS',
365  $ / 4x, '3. Last column zero', 16x,
366  $ '7. Scaled near underflow', / 4x,
367  $ '4. Last n/2 columns zero', 11x, '8. Scaled near overflow' )
368 *
369 * GT matrix types
370 *
371  9987 FORMAT( ' Matrix types (1-6 have specified condition numbers):',
372  $ / 4x, '1. Diagonal', 24x, '7. Random, unspecified CNDNUM',
373  $ / 4x, '2. Random, CNDNUM = 2', 14x, '8. First column zero',
374  $ / 4x, '3. Random, CNDNUM = sqrt(0.1/EPS)', 2x,
375  $ '9. Last column zero', / 4x, '4. Random, CNDNUM = 0.1/EPS',
376  $ 7x, '10. Last n/2 columns zero', / 4x,
377  $ '5. Scaled near underflow', 10x,
378  $ '11. Scaled near underflow', / 4x,
379  $ '6. Scaled near overflow', 11x, '12. Scaled near overflow' )
380 *
381 * PT matrix types
382 *
383  9986 FORMAT( ' Matrix types (1-6 have specified condition numbers):',
384  $ / 4x, '1. Diagonal', 24x, '7. Random, unspecified CNDNUM',
385  $ / 4x, '2. Random, CNDNUM = 2', 14x,
386  $ '8. First row and column zero', / 4x,
387  $ '3. Random, CNDNUM = sqrt(0.1/EPS)', 2x,
388  $ '9. Last row and column zero', / 4x,
389  $ '4. Random, CNDNUM = 0.1/EPS', 7x,
390  $ '10. Middle row and column zero', / 4x,
391  $ '5. Scaled near underflow', 10x,
392  $ '11. Scaled near underflow', / 4x,
393  $ '6. Scaled near overflow', 11x, '12. Scaled near overflow' )
394 *
395 * PO, PP matrix types
396 *
397  9985 FORMAT( 4x, '1. Diagonal', 24x,
398  $ '6. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
399  $ '2. Random, CNDNUM = 2', 14x, '7. Random, CNDNUM = 0.1/EPS',
400  $ / 3x, '*3. First row and column zero', 7x,
401  $ '8. Scaled near underflow', / 3x,
402  $ '*4. Last row and column zero', 8x,
403  $ '9. Scaled near overflow', / 3x,
404  $ '*5. Middle row and column zero', / 3x,
405  $ '(* - tests error exits from ', a3,
406  $ 'TRF, no test ratios are computed)' )
407 *
408 * PB matrix types
409 *
410  9984 FORMAT( 4x, '1. Random, CNDNUM = 2', 14x,
411  $ '5. Random, CNDNUM = sqrt(0.1/EPS)', / 3x,
412  $ '*2. First row and column zero', 7x,
413  $ '6. Random, CNDNUM = 0.1/EPS', / 3x,
414  $ '*3. Last row and column zero', 8x,
415  $ '7. Scaled near underflow', / 3x,
416  $ '*4. Middle row and column zero', 6x,
417  $ '8. Scaled near overflow', / 3x,
418  $ '(* - tests error exits from ', a3,
419  $ 'TRF, no test ratios are computed)' )
420 *
421 * SSY, SSP, CHE, CHP matrix types
422 *
423  9983 FORMAT( 4x, '1. Diagonal', 24x,
424  $ '6. Last n/2 rows and columns zero', / 4x,
425  $ '2. Random, CNDNUM = 2', 14x,
426  $ '7. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
427  $ '3. First row and column zero', 7x,
428  $ '8. Random, CNDNUM = 0.1/EPS', / 4x,
429  $ '4. Last row and column zero', 8x,
430  $ '9. Scaled near underflow', / 4x,
431  $ '5. Middle row and column zero', 5x,
432  $ '10. Scaled near overflow' )
433 *
434 * CSY, CSP matrix types
435 *
436  9982 FORMAT( 4x, '1. Diagonal', 24x,
437  $ '7. Random, CNDNUM = sqrt(0.1/EPS)', / 4x,
438  $ '2. Random, CNDNUM = 2', 14x, '8. Random, CNDNUM = 0.1/EPS',
439  $ / 4x, '3. First row and column zero', 7x,
440  $ '9. Scaled near underflow', / 4x,
441  $ '4. Last row and column zero', 7x,
442  $ '10. Scaled near overflow', / 4x,
443  $ '5. Middle row and column zero', 5x,
444  $ '11. Block diagonal matrix', / 4x,
445  $ '6. Last n/2 rows and columns zero' )
446 *
447 * Test ratios
448 *
449  9981 FORMAT( 3x, i2, ': norm( L * U - A ) / ( N * norm(A) * EPS )' )
450  9980 FORMAT( 3x, i2, ': norm( B - A * X ) / ',
451  $ '( norm(A) * norm(X) * EPS )' )
452  9979 FORMAT( 3x, i2, ': norm( X - XACT ) / ',
453  $ '( norm(XACT) * CNDNUM * EPS )' )
454  9978 FORMAT( 3x, i2, ': norm( X - XACT ) / ',
455  $ '( norm(XACT) * (error bound) )' )
456  9977 FORMAT( 3x, i2, ': (backward error) / EPS' )
457  9976 FORMAT( 3x, i2, ': RCOND * CNDNUM - 1.0' )
458  9975 FORMAT( 3x, i2, ': norm( U'' * U - A ) / ( N * norm(A) * EPS )',
459  $ ', or', / 7x, 'norm( L * L'' - A ) / ( N * norm(A) * EPS )'
460  $ )
461  9974 FORMAT( 3x, i2, ': norm( U*D*U'' - A ) / ( N * norm(A) * EPS )',
462  $ ', or', / 7x, 'norm( L*D*L'' - A ) / ( N * norm(A) * EPS )'
463  $ )
464  9973 FORMAT( 3x, i2, ': norm( U''*D*U - A ) / ( N * norm(A) * EPS )',
465  $ ', or', / 7x, 'norm( L*D*L'' - A ) / ( N * norm(A) * EPS )'
466  $ )
467  9972 FORMAT( 3x, i2, ': abs( WORK(1) - RPVGRW ) /',
468  $ ' ( max( WORK(1), RPVGRW ) * EPS )' )
469 *
470  RETURN
471 *
472 * End of ALADHD
473 *
474  END
subroutine aladhd(IOUNIT, PATH)
ALADHD
Definition: aladhd.f:80