1 SUBROUTINE DLAHD2( IOUNIT, PATH )
2 *
3 * -- LAPACK auxiliary test routine (version 2.0) --
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 * DLAHD2 prints header information for the different test paths.
16 *
17 * Arguments
18 * =========
19 *
20 * IOUNIT (input) INTEGER.
21 * On entry, IOUNIT specifies the unit number to which the
22 * header information should be printed.
23 *
24 * PATH (input) CHARACTER*3.
25 * On entry, PATH contains the name of the path for which the
26 * header information is to be printed. Current paths are
27 *
28 * DHS, ZHS: Non-symmetric eigenproblem.
29 * DST, ZST: Symmetric eigenproblem.
30 * DSG, ZSG: Symmetric Generalized eigenproblem.
31 * DBD, ZBD: Singular Value Decomposition (SVD)
32 * DBB, ZBB: General Banded reduction to bidiagonal form
33 *
34 * These paths also are supplied in double precision (replace
35 * leading S by D and leading C by Z in path names).
36 *
37 * =====================================================================
38 *
39 * .. Local Scalars ..
40 LOGICAL CORZ, SORD
41 CHARACTER*2 C2
42 INTEGER J
43 * ..
44 * .. External Functions ..
45 LOGICAL LSAME, LSAMEN
46 EXTERNAL LSAME, LSAMEN
47 * ..
48 * .. Executable Statements ..
49 *
50 IF( IOUNIT.LE.0 )
51 $ RETURN
52 SORD = LSAME( PATH, 'S' ) .OR. LSAME( PATH, 'D' )
53 CORZ = LSAME( PATH, 'C' ) .OR. LSAME( PATH, 'Z' )
54 IF( .NOT.SORD .AND. .NOT.CORZ ) THEN
55 WRITE( IOUNIT, FMT = 9999 )PATH
56 END IF
57 C2 = PATH( 2: 3 )
58 *
59 IF( LSAMEN( 2, C2, 'HS' ) ) THEN
60 IF( SORD ) THEN
61 *
62 * Real Non-symmetric Eigenvalue Problem:
63 *
64 WRITE( IOUNIT, FMT = 9998 )PATH
65 *
66 * Matrix types
67 *
68 WRITE( IOUNIT, FMT = 9988 )
69 WRITE( IOUNIT, FMT = 9987 )
70 WRITE( IOUNIT, FMT = 9986 )'pairs ', 'pairs ', 'prs.',
71 $ 'prs.'
72 WRITE( IOUNIT, FMT = 9985 )
73 *
74 * Tests performed
75 *
76 WRITE( IOUNIT, FMT = 9984 )'orthogonal', '''=transpose',
77 $ ( '''', J = 1, 6 )
78 *
79 ELSE
80 *
81 * Complex Non-symmetric Eigenvalue Problem:
82 *
83 WRITE( IOUNIT, FMT = 9997 )PATH
84 *
85 * Matrix types
86 *
87 WRITE( IOUNIT, FMT = 9988 )
88 WRITE( IOUNIT, FMT = 9987 )
89 WRITE( IOUNIT, FMT = 9986 )'e.vals', 'e.vals', 'e.vs',
90 $ 'e.vs'
91 WRITE( IOUNIT, FMT = 9985 )
92 *
93 * Tests performed
94 *
95 WRITE( IOUNIT, FMT = 9984 )'unitary', '*=conj.transp.',
96 $ ( '*', J = 1, 6 )
97 END IF
98 *
99 ELSE IF( LSAMEN( 2, C2, 'ST' ) ) THEN
100 *
101 IF( SORD ) THEN
102 *
103 * Real Symmetric Eigenvalue Problem:
104 *
105 WRITE( IOUNIT, FMT = 9996 )PATH
106 *
107 * Matrix types
108 *
109 WRITE( IOUNIT, FMT = 9983 )
110 WRITE( IOUNIT, FMT = 9982 )
111 WRITE( IOUNIT, FMT = 9981 )'Symmetric'
112 *
113 * Tests performed
114 *
115 WRITE( IOUNIT, FMT = 9968 )
116 *
117 ELSE
118 *
119 * Complex Hermitian Eigenvalue Problem:
120 *
121 WRITE( IOUNIT, FMT = 9995 )PATH
122 *
123 * Matrix types
124 *
125 WRITE( IOUNIT, FMT = 9983 )
126 WRITE( IOUNIT, FMT = 9982 )
127 WRITE( IOUNIT, FMT = 9981 )'Hermitian'
128 *
129 * Tests performed
130 *
131 WRITE( IOUNIT, FMT = 9967 )
132 END IF
133 *
134 ELSE IF( LSAMEN( 2, C2, 'SG' ) ) THEN
135 *
136 IF( SORD ) THEN
137 *
138 * Real Symmetric Generalized Eigenvalue Problem:
139 *
140 WRITE( IOUNIT, FMT = 9992 )PATH
141 *
142 * Matrix types
143 *
144 WRITE( IOUNIT, FMT = 9980 )
145 WRITE( IOUNIT, FMT = 9979 )
146 WRITE( IOUNIT, FMT = 9978 )'Symmetric'
147 *
148 * Tests performed
149 *
150 WRITE( IOUNIT, FMT = 9977 )
151 WRITE( IOUNIT, FMT = 9976 )
152 *
153 ELSE
154 *
155 * Complex Hermitian Generalized Eigenvalue Problem:
156 *
157 WRITE( IOUNIT, FMT = 9991 )PATH
158 *
159 * Matrix types
160 *
161 WRITE( IOUNIT, FMT = 9980 )
162 WRITE( IOUNIT, FMT = 9979 )
163 WRITE( IOUNIT, FMT = 9978 )'Hermitian'
164 *
165 * Tests performed
166 *
167 WRITE( IOUNIT, FMT = 9975 )
168 WRITE( IOUNIT, FMT = 9974 )
169 *
170 END IF
171 *
172 ELSE IF( LSAMEN( 2, C2, 'BD' ) ) THEN
173 *
174 IF( SORD ) THEN
175 *
176 * Real Singular Value Decomposition:
177 *
178 WRITE( IOUNIT, FMT = 9994 )PATH
179 *
180 * Matrix types
181 *
182 WRITE( IOUNIT, FMT = 9973 )
183 *
184 * Tests performed
185 *
186 WRITE( IOUNIT, FMT = 9972 )'orthogonal'
187 WRITE( IOUNIT, FMT = 9971 )
188 ELSE
189 *
190 * Complex Singular Value Decomposition:
191 *
192 WRITE( IOUNIT, FMT = 9993 )PATH
193 *
194 * Matrix types
195 *
196 WRITE( IOUNIT, FMT = 9973 )
197 *
198 * Tests performed
199 *
200 WRITE( IOUNIT, FMT = 9972 )'unitary '
201 WRITE( IOUNIT, FMT = 9971 )
202 END IF
203 *
204 ELSE IF( LSAMEN( 2, C2, 'BB' ) ) THEN
205 *
206 IF( SORD ) THEN
207 *
208 * Real General Band reduction to bidiagonal form:
209 *
210 WRITE( IOUNIT, FMT = 9990 )PATH
211 *
212 * Matrix types
213 *
214 WRITE( IOUNIT, FMT = 9970 )
215 *
216 * Tests performed
217 *
218 WRITE( IOUNIT, FMT = 9969 )'orthogonal'
219 ELSE
220 *
221 * Complex Band reduction to bidiagonal form:
222 *
223 WRITE( IOUNIT, FMT = 9989 )PATH
224 *
225 * Matrix types
226 *
227 WRITE( IOUNIT, FMT = 9970 )
228 *
229 * Tests performed
230 *
231 WRITE( IOUNIT, FMT = 9969 )'unitary '
232 END IF
233 *
234 ELSE
235 *
236 WRITE( IOUNIT, FMT = 9999 )PATH
237 RETURN
238 END IF
239 *
240 RETURN
241 *
242 9999 FORMAT( 1X, A3, ': no header available' )
243 9998 FORMAT( / 1X, A3, ' -- Real Non-symmetric eigenvalue problem' )
244 9997 FORMAT( / 1X, A3, ' -- Complex Non-symmetric eigenvalue problem' )
245 9996 FORMAT( / 1X, A3, ' -- Real Symmetric eigenvalue problem' )
246 9995 FORMAT( / 1X, A3, ' -- Complex Hermitian eigenvalue problem' )
247 9994 FORMAT( / 1X, A3, ' -- Real Singular Value Decomposition' )
248 9993 FORMAT( / 1X, A3, ' -- Complex Singular Value Decomposition' )
249 9992 FORMAT( / 1X, A3, ' -- Real Symmetric Generalized eigenvalue ',
250 $ 'problem' )
251 9991 FORMAT( / 1X, A3, ' -- Complex Hermitian Generalized eigenvalue ',
252 $ 'problem' )
253 9990 FORMAT( / 1X, A3, ' -- Real Band reduc. to bidiagonal form' )
254 9989 FORMAT( / 1X, A3, ' -- Complex Band reduc. to bidiagonal form' )
255 *
256 9988 FORMAT( ' Matrix types (see xCHKHS for details): ' )
257 *
258 9987 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
259 $ ' ', ' 5=Diagonal: geometr. spaced entries.',
260 $ / ' 2=Identity matrix. ', ' 6=Diagona',
261 $ 'l: clustered entries.', / ' 3=Transposed Jordan block. ',
262 $ ' ', ' 7=Diagonal: large, evenly spaced.', / ' ',
263 $ '4=Diagonal: evenly spaced entries. ', ' 8=Diagonal: s',
264 $ 'mall, evenly spaced.' )
265 9986 FORMAT( ' Dense, Non-Symmetric Matrices:', / ' 9=Well-cond., ev',
266 $ 'enly spaced eigenvals.', ' 14=Ill-cond., geomet. spaced e',
267 $ 'igenals.', / ' 10=Well-cond., geom. spaced eigenvals. ',
268 $ ' 15=Ill-conditioned, clustered e.vals.', / ' 11=Well-cond',
269 $ 'itioned, clustered e.vals. ', ' 16=Ill-cond., random comp',
270 $ 'lex ', A6, / ' 12=Well-cond., random complex ', A6, ' ',
271 $ ' 17=Ill-cond., large rand. complx ', A4, / ' 13=Ill-condi',
272 $ 'tioned, evenly spaced. ', ' 18=Ill-cond., small rand.',
273 $ ' complx ', A4 )
274 9985 FORMAT( ' 19=Matrix with random O(1) entries. ', ' 21=Matrix ',
275 $ 'with small random entries.', / ' 20=Matrix with large ran',
276 $ 'dom entries. ' )
277 9984 FORMAT( / ' Tests performed: ', '(H is Hessenberg, T is Schur,',
278 $ ' U and Z are ', A, ',', / 20X, A, ', W is a diagonal matr',
279 $ 'ix of eigenvalues,', / 20X, 'L and R are the left and rig',
280 $ 'ht eigenvector matrices)', / ' 1 = | A - U H U', A1, ' |',
281 $ ' / ( |A| n ulp ) ', ' 2 = | I - U U', A1, ' | / ',
282 $ '( n ulp )', / ' 3 = | H - Z T Z', A1, ' | / ( |H| n ulp ',
283 $ ') ', ' 4 = | I - Z Z', A1, ' | / ( n ulp )',
284 $ / ' 5 = | A - UZ T (UZ)', A1, ' | / ( |A| n ulp ) ',
285 $ ' 6 = | I - UZ (UZ)', A1, ' | / ( n ulp )', / ' 7 = | T(',
286 $ 'e.vects.) - T(no e.vects.) | / ( |T| ulp )', / ' 8 = | W',
287 $ '(e.vects.) - W(no e.vects.) | / ( |W| ulp )', / ' 9 = | ',
288 $ 'TR - RW | / ( |T| |R| ulp ) ', ' 10 = | LT - WL | / (',
289 $ ' |T| |L| ulp )', / ' 11= |HX - XW| / (|H| |X| ulp) (inv.',
290 $ 'it)', ' 12= |YH - WY| / (|H| |Y| ulp) (inv.it)' )
291 *
292 * Symmetric/Hermitian eigenproblem
293 *
294 9983 FORMAT( ' Matrix types (see xDRVST for details): ' )
295 *
296 9982 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
297 $ ' ', ' 5=Diagonal: clustered entries.', / ' 2=',
298 $ 'Identity matrix. ', ' 6=Diagonal: lar',
299 $ 'ge, evenly spaced.', / ' 3=Diagonal: evenly spaced entri',
300 $ 'es. ', ' 7=Diagonal: small, evenly spaced.', / ' 4=D',
301 $ 'iagonal: geometr. spaced entries.' )
302 9981 FORMAT( ' Dense ', A, ' Matrices:', / ' 8=Evenly spaced eigen',
303 $ 'vals. ', ' 12=Small, evenly spaced eigenvals.',
304 $ / ' 9=Geometrically spaced eigenvals. ', ' 13=Matrix ',
305 $ 'with random O(1) entries.', / ' 10=Clustered eigenvalues.',
306 $ ' ', ' 14=Matrix with large random entries.',
307 $ / ' 11=Large, evenly spaced eigenvals. ', ' 15=Matrix ',
308 $ 'with small random entries.' )
309 *
310 * Symmetric/Hermitian Generalized eigenproblem
311 *
312 9980 FORMAT( ' Matrix types (see xDRVSG for details): ' )
313 *
314 9979 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
315 $ ' ', ' 5=Diagonal: clustered entries.', / ' 2=',
316 $ 'Identity matrix. ', ' 6=Diagonal: lar',
317 $ 'ge, evenly spaced.', / ' 3=Diagonal: evenly spaced entri',
318 $ 'es. ', ' 7=Diagonal: small, evenly spaced.', / ' 4=D',
319 $ 'iagonal: geometr. spaced entries.' )
320 9978 FORMAT( ' Dense or Banded ', A, ' Matrices: ',
321 $ / ' 8=Evenly spaced eigenvals. ',
322 $ ' 15=Matrix with small random entries.',
323 $ / ' 9=Geometrically spaced eigenvals. ',
324 $ ' 16=Evenly spaced eigenvals, KA=1, KB=1.',
325 $ / ' 10=Clustered eigenvalues. ',
326 $ ' 17=Evenly spaced eigenvals, KA=2, KB=1.',
327 $ / ' 11=Large, evenly spaced eigenvals. ',
328 $ ' 18=Evenly spaced eigenvals, KA=2, KB=2.',
329 $ / ' 12=Small, evenly spaced eigenvals. ',
330 $ ' 19=Evenly spaced eigenvals, KA=3, KB=1.',
331 $ / ' 13=Matrix with random O(1) entries. ',
332 $ ' 20=Evenly spaced eigenvals, KA=3, KB=2.',
333 $ / ' 14=Matrix with large random entries.',
334 $ ' 21=Evenly spaced eigenvals, KA=3, KB=3.' )
335 9977 FORMAT( / ' Tests performed: ',
336 $ / '( For each pair (A,B), where A is of the given type ',
337 $ / ' and B is a random well-conditioned matrix. D is ',
338 $ / ' diagonal, and Z is orthogonal. )',
339 $ / ' 1 = DSYGV, with ITYPE=1 and UPLO=''U'':',
340 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
341 $ / ' 2 = DSPGV, with ITYPE=1 and UPLO=''U'':',
342 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
343 $ / ' 3 = DSBGV, with ITYPE=1 and UPLO=''U'':',
344 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
345 $ / ' 4 = DSYGV, with ITYPE=1 and UPLO=''L'':',
346 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
347 $ / ' 5 = DSPGV, with ITYPE=1 and UPLO=''L'':',
348 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
349 $ / ' 6 = DSBGV, with ITYPE=1 and UPLO=''L'':',
350 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ' )
351 9976 FORMAT( ' 7 = DSYGV, with ITYPE=2 and UPLO=''U'':',
352 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
353 $ / ' 8 = DSPGV, with ITYPE=2 and UPLO=''U'':',
354 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
355 $ / ' 9 = DSPGV, with ITYPE=2 and UPLO=''L'':',
356 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
357 $ / '10 = DSPGV, with ITYPE=2 and UPLO=''L'':',
358 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
359 $ / '11 = DSYGV, with ITYPE=3 and UPLO=''U'':',
360 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
361 $ / '12 = DSPGV, with ITYPE=3 and UPLO=''U'':',
362 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
363 $ / '13 = DSYGV, with ITYPE=3 and UPLO=''L'':',
364 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
365 $ / '14 = DSPGV, with ITYPE=3 and UPLO=''L'':',
366 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ' )
367 9975 FORMAT( / ' Tests performed: ',
368 $ / '( For each pair (A,B), where A is of the given type ',
369 $ / ' and B is a random well-conditioned matrix. D is ',
370 $ / ' diagonal, and Z is unitary. )',
371 $ / ' 1 = ZHEGV, with ITYPE=1 and UPLO=''U'':',
372 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
373 $ / ' 2 = ZHPGV, with ITYPE=1 and UPLO=''U'':',
374 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
375 $ / ' 3 = ZHBGV, with ITYPE=1 and UPLO=''U'':',
376 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
377 $ / ' 4 = ZHEGV, with ITYPE=1 and UPLO=''L'':',
378 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
379 $ / ' 5 = ZHPGV, with ITYPE=1 and UPLO=''L'':',
380 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
381 $ / ' 6 = ZHBGV, with ITYPE=1 and UPLO=''L'':',
382 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ' )
383 9974 FORMAT( ' 7 = ZHEGV, with ITYPE=2 and UPLO=''U'':',
384 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
385 $ / ' 8 = ZHPGV, with ITYPE=2 and UPLO=''U'':',
386 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
387 $ / ' 9 = ZHPGV, with ITYPE=2 and UPLO=''L'':',
388 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
389 $ / '10 = ZHPGV, with ITYPE=2 and UPLO=''L'':',
390 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
391 $ / '11 = ZHEGV, with ITYPE=3 and UPLO=''U'':',
392 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
393 $ / '12 = ZHPGV, with ITYPE=3 and UPLO=''U'':',
394 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
395 $ / '13 = ZHEGV, with ITYPE=3 and UPLO=''L'':',
396 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
397 $ / '14 = ZHPGV, with ITYPE=3 and UPLO=''L'':',
398 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ' )
399 *
400 * Singular Value Decomposition
401 *
402 9973 FORMAT( ' Matrix types (see xCHKBD for details):',
403 $ / ' Diagonal matrices:', / ' 1: Zero', 28X,
404 $ ' 5: Clustered entries', / ' 2: Identity', 24X,
405 $ ' 6: Large, evenly spaced entries',
406 $ / ' 3: Evenly spaced entries', 11X,
407 $ ' 7: Small, evenly spaced entries',
408 $ / ' 4: Geometrically spaced entries',
409 $ / ' General matrices:', / ' 8: Evenly spaced sing. vals.',
410 $ 7X, '12: Small, evenly spaced sing vals',
411 $ / ' 9: Geometrically spaced sing vals ',
412 $ '13: Random, O(1) entries', / ' 10: Clustered sing. vals.',
413 $ 11X, '14: Random, scaled near overflow',
414 $ / ' 11: Large, evenly spaced sing vals ',
415 $ '15: Random, scaled near underflow' )
416 *
417 9972 FORMAT( / ' Test ratios: ',
418 $ '(B: bidiagonal, S: diagonal, Q, P, U, and V: ', A10, / 16X,
419 $ 'X: m x nrhs, Y = Q'' X, and Z = U'' Y)',
420 $ / ' 1: norm( A - Q B P'' ) / ( norm(A) max(m,n) ulp )',
421 $ / ' 2: norm( I - Q'' Q ) / ( m ulp )',
422 $ / ' 3: norm( I - P'' P ) / ( n ulp )',
423 $ / ' 4: norm( B - U S V'' ) / ( norm(B) min(m,n) ulp )', /
424 $ ' 5: norm( Y - U Z ) / ( norm(Z) max(min(m,n),k) ulp )'
425 $ , / ' 6: norm( I - U'' U ) / ( min(m,n) ulp )',
426 $ / ' 7: norm( I - V'' V ) / ( min(m,n) ulp )' )
427 9971 FORMAT( ' 8: Test ordering of S (0 if nondecreasing, 1/ulp ',
428 $ ' otherwise)', /
429 $ ' 9: norm( S - S2 ) / ( norm(S) ulp ),',
430 $ ' where S2 is computed', / 44X,
431 $ 'without computing U and V''',
432 $ / ' 10: Sturm sequence test ',
433 $ '(0 if sing. vals of B within THRESH of S)',
434 $ / ' 11: norm( A - (QU) S (V'' P'') ) / ',
435 $ '( norm(A) max(m,n) ulp )', /
436 $ ' 12: norm( X - (QU) Z ) / ( |X| max(M,k) ulp )',
437 $ / ' 13: norm( I - (QU)''(QU) ) / ( M ulp )',
438 $ / ' 14: norm( I - (V'' P'') (P V) ) / ( N ulp )' )
439 *
440 * Band reduction to bidiagonal form
441 *
442 9970 FORMAT( ' Matrix types (see xCHKBB for details):',
443 $ / ' Diagonal matrices:', / ' 1: Zero', 28X,
444 $ ' 5: Clustered entries', / ' 2: Identity', 24X,
445 $ ' 6: Large, evenly spaced entries',
446 $ / ' 3: Evenly spaced entries', 11X,
447 $ ' 7: Small, evenly spaced entries',
448 $ / ' 4: Geometrically spaced entries',
449 $ / ' General matrices:', / ' 8: Evenly spaced sing. vals.',
450 $ 7X, '12: Small, evenly spaced sing vals',
451 $ / ' 9: Geometrically spaced sing vals ',
452 $ '13: Random, O(1) entries', / ' 10: Clustered sing. vals.',
453 $ 11X, '14: Random, scaled near overflow',
454 $ / ' 11: Large, evenly spaced sing vals ',
455 $ '15: Random, scaled near underflow' )
456 *
457 9969 FORMAT( / ' Test ratios: ', '(B: upper bidiagonal, Q and P: ',
458 $ A10, / 16X, 'C: m x nrhs, PT = P'', Y = Q'' C)',
459 $ / ' 1: norm( A - Q B PT ) / ( norm(A) max(m,n) ulp )',
460 $ / ' 2: norm( I - Q'' Q ) / ( m ulp )',
461 $ / ' 3: norm( I - PT PT'' ) / ( n ulp )',
462 $ / ' 4: norm( Y - Q'' C ) / ( norm(Y) max(m,nrhs) ulp )' )
463 9968 FORMAT( / ' Tests performed: See sdrvst.f' )
464 9967 FORMAT( / ' Tests performed: See cdrvst.f' )
465 *
466 * End of DLAHD2
467 *
468 END
2 *
3 * -- LAPACK auxiliary test routine (version 2.0) --
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 * DLAHD2 prints header information for the different test paths.
16 *
17 * Arguments
18 * =========
19 *
20 * IOUNIT (input) INTEGER.
21 * On entry, IOUNIT specifies the unit number to which the
22 * header information should be printed.
23 *
24 * PATH (input) CHARACTER*3.
25 * On entry, PATH contains the name of the path for which the
26 * header information is to be printed. Current paths are
27 *
28 * DHS, ZHS: Non-symmetric eigenproblem.
29 * DST, ZST: Symmetric eigenproblem.
30 * DSG, ZSG: Symmetric Generalized eigenproblem.
31 * DBD, ZBD: Singular Value Decomposition (SVD)
32 * DBB, ZBB: General Banded reduction to bidiagonal form
33 *
34 * These paths also are supplied in double precision (replace
35 * leading S by D and leading C by Z in path names).
36 *
37 * =====================================================================
38 *
39 * .. Local Scalars ..
40 LOGICAL CORZ, SORD
41 CHARACTER*2 C2
42 INTEGER J
43 * ..
44 * .. External Functions ..
45 LOGICAL LSAME, LSAMEN
46 EXTERNAL LSAME, LSAMEN
47 * ..
48 * .. Executable Statements ..
49 *
50 IF( IOUNIT.LE.0 )
51 $ RETURN
52 SORD = LSAME( PATH, 'S' ) .OR. LSAME( PATH, 'D' )
53 CORZ = LSAME( PATH, 'C' ) .OR. LSAME( PATH, 'Z' )
54 IF( .NOT.SORD .AND. .NOT.CORZ ) THEN
55 WRITE( IOUNIT, FMT = 9999 )PATH
56 END IF
57 C2 = PATH( 2: 3 )
58 *
59 IF( LSAMEN( 2, C2, 'HS' ) ) THEN
60 IF( SORD ) THEN
61 *
62 * Real Non-symmetric Eigenvalue Problem:
63 *
64 WRITE( IOUNIT, FMT = 9998 )PATH
65 *
66 * Matrix types
67 *
68 WRITE( IOUNIT, FMT = 9988 )
69 WRITE( IOUNIT, FMT = 9987 )
70 WRITE( IOUNIT, FMT = 9986 )'pairs ', 'pairs ', 'prs.',
71 $ 'prs.'
72 WRITE( IOUNIT, FMT = 9985 )
73 *
74 * Tests performed
75 *
76 WRITE( IOUNIT, FMT = 9984 )'orthogonal', '''=transpose',
77 $ ( '''', J = 1, 6 )
78 *
79 ELSE
80 *
81 * Complex Non-symmetric Eigenvalue Problem:
82 *
83 WRITE( IOUNIT, FMT = 9997 )PATH
84 *
85 * Matrix types
86 *
87 WRITE( IOUNIT, FMT = 9988 )
88 WRITE( IOUNIT, FMT = 9987 )
89 WRITE( IOUNIT, FMT = 9986 )'e.vals', 'e.vals', 'e.vs',
90 $ 'e.vs'
91 WRITE( IOUNIT, FMT = 9985 )
92 *
93 * Tests performed
94 *
95 WRITE( IOUNIT, FMT = 9984 )'unitary', '*=conj.transp.',
96 $ ( '*', J = 1, 6 )
97 END IF
98 *
99 ELSE IF( LSAMEN( 2, C2, 'ST' ) ) THEN
100 *
101 IF( SORD ) THEN
102 *
103 * Real Symmetric Eigenvalue Problem:
104 *
105 WRITE( IOUNIT, FMT = 9996 )PATH
106 *
107 * Matrix types
108 *
109 WRITE( IOUNIT, FMT = 9983 )
110 WRITE( IOUNIT, FMT = 9982 )
111 WRITE( IOUNIT, FMT = 9981 )'Symmetric'
112 *
113 * Tests performed
114 *
115 WRITE( IOUNIT, FMT = 9968 )
116 *
117 ELSE
118 *
119 * Complex Hermitian Eigenvalue Problem:
120 *
121 WRITE( IOUNIT, FMT = 9995 )PATH
122 *
123 * Matrix types
124 *
125 WRITE( IOUNIT, FMT = 9983 )
126 WRITE( IOUNIT, FMT = 9982 )
127 WRITE( IOUNIT, FMT = 9981 )'Hermitian'
128 *
129 * Tests performed
130 *
131 WRITE( IOUNIT, FMT = 9967 )
132 END IF
133 *
134 ELSE IF( LSAMEN( 2, C2, 'SG' ) ) THEN
135 *
136 IF( SORD ) THEN
137 *
138 * Real Symmetric Generalized Eigenvalue Problem:
139 *
140 WRITE( IOUNIT, FMT = 9992 )PATH
141 *
142 * Matrix types
143 *
144 WRITE( IOUNIT, FMT = 9980 )
145 WRITE( IOUNIT, FMT = 9979 )
146 WRITE( IOUNIT, FMT = 9978 )'Symmetric'
147 *
148 * Tests performed
149 *
150 WRITE( IOUNIT, FMT = 9977 )
151 WRITE( IOUNIT, FMT = 9976 )
152 *
153 ELSE
154 *
155 * Complex Hermitian Generalized Eigenvalue Problem:
156 *
157 WRITE( IOUNIT, FMT = 9991 )PATH
158 *
159 * Matrix types
160 *
161 WRITE( IOUNIT, FMT = 9980 )
162 WRITE( IOUNIT, FMT = 9979 )
163 WRITE( IOUNIT, FMT = 9978 )'Hermitian'
164 *
165 * Tests performed
166 *
167 WRITE( IOUNIT, FMT = 9975 )
168 WRITE( IOUNIT, FMT = 9974 )
169 *
170 END IF
171 *
172 ELSE IF( LSAMEN( 2, C2, 'BD' ) ) THEN
173 *
174 IF( SORD ) THEN
175 *
176 * Real Singular Value Decomposition:
177 *
178 WRITE( IOUNIT, FMT = 9994 )PATH
179 *
180 * Matrix types
181 *
182 WRITE( IOUNIT, FMT = 9973 )
183 *
184 * Tests performed
185 *
186 WRITE( IOUNIT, FMT = 9972 )'orthogonal'
187 WRITE( IOUNIT, FMT = 9971 )
188 ELSE
189 *
190 * Complex Singular Value Decomposition:
191 *
192 WRITE( IOUNIT, FMT = 9993 )PATH
193 *
194 * Matrix types
195 *
196 WRITE( IOUNIT, FMT = 9973 )
197 *
198 * Tests performed
199 *
200 WRITE( IOUNIT, FMT = 9972 )'unitary '
201 WRITE( IOUNIT, FMT = 9971 )
202 END IF
203 *
204 ELSE IF( LSAMEN( 2, C2, 'BB' ) ) THEN
205 *
206 IF( SORD ) THEN
207 *
208 * Real General Band reduction to bidiagonal form:
209 *
210 WRITE( IOUNIT, FMT = 9990 )PATH
211 *
212 * Matrix types
213 *
214 WRITE( IOUNIT, FMT = 9970 )
215 *
216 * Tests performed
217 *
218 WRITE( IOUNIT, FMT = 9969 )'orthogonal'
219 ELSE
220 *
221 * Complex Band reduction to bidiagonal form:
222 *
223 WRITE( IOUNIT, FMT = 9989 )PATH
224 *
225 * Matrix types
226 *
227 WRITE( IOUNIT, FMT = 9970 )
228 *
229 * Tests performed
230 *
231 WRITE( IOUNIT, FMT = 9969 )'unitary '
232 END IF
233 *
234 ELSE
235 *
236 WRITE( IOUNIT, FMT = 9999 )PATH
237 RETURN
238 END IF
239 *
240 RETURN
241 *
242 9999 FORMAT( 1X, A3, ': no header available' )
243 9998 FORMAT( / 1X, A3, ' -- Real Non-symmetric eigenvalue problem' )
244 9997 FORMAT( / 1X, A3, ' -- Complex Non-symmetric eigenvalue problem' )
245 9996 FORMAT( / 1X, A3, ' -- Real Symmetric eigenvalue problem' )
246 9995 FORMAT( / 1X, A3, ' -- Complex Hermitian eigenvalue problem' )
247 9994 FORMAT( / 1X, A3, ' -- Real Singular Value Decomposition' )
248 9993 FORMAT( / 1X, A3, ' -- Complex Singular Value Decomposition' )
249 9992 FORMAT( / 1X, A3, ' -- Real Symmetric Generalized eigenvalue ',
250 $ 'problem' )
251 9991 FORMAT( / 1X, A3, ' -- Complex Hermitian Generalized eigenvalue ',
252 $ 'problem' )
253 9990 FORMAT( / 1X, A3, ' -- Real Band reduc. to bidiagonal form' )
254 9989 FORMAT( / 1X, A3, ' -- Complex Band reduc. to bidiagonal form' )
255 *
256 9988 FORMAT( ' Matrix types (see xCHKHS for details): ' )
257 *
258 9987 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
259 $ ' ', ' 5=Diagonal: geometr. spaced entries.',
260 $ / ' 2=Identity matrix. ', ' 6=Diagona',
261 $ 'l: clustered entries.', / ' 3=Transposed Jordan block. ',
262 $ ' ', ' 7=Diagonal: large, evenly spaced.', / ' ',
263 $ '4=Diagonal: evenly spaced entries. ', ' 8=Diagonal: s',
264 $ 'mall, evenly spaced.' )
265 9986 FORMAT( ' Dense, Non-Symmetric Matrices:', / ' 9=Well-cond., ev',
266 $ 'enly spaced eigenvals.', ' 14=Ill-cond., geomet. spaced e',
267 $ 'igenals.', / ' 10=Well-cond., geom. spaced eigenvals. ',
268 $ ' 15=Ill-conditioned, clustered e.vals.', / ' 11=Well-cond',
269 $ 'itioned, clustered e.vals. ', ' 16=Ill-cond., random comp',
270 $ 'lex ', A6, / ' 12=Well-cond., random complex ', A6, ' ',
271 $ ' 17=Ill-cond., large rand. complx ', A4, / ' 13=Ill-condi',
272 $ 'tioned, evenly spaced. ', ' 18=Ill-cond., small rand.',
273 $ ' complx ', A4 )
274 9985 FORMAT( ' 19=Matrix with random O(1) entries. ', ' 21=Matrix ',
275 $ 'with small random entries.', / ' 20=Matrix with large ran',
276 $ 'dom entries. ' )
277 9984 FORMAT( / ' Tests performed: ', '(H is Hessenberg, T is Schur,',
278 $ ' U and Z are ', A, ',', / 20X, A, ', W is a diagonal matr',
279 $ 'ix of eigenvalues,', / 20X, 'L and R are the left and rig',
280 $ 'ht eigenvector matrices)', / ' 1 = | A - U H U', A1, ' |',
281 $ ' / ( |A| n ulp ) ', ' 2 = | I - U U', A1, ' | / ',
282 $ '( n ulp )', / ' 3 = | H - Z T Z', A1, ' | / ( |H| n ulp ',
283 $ ') ', ' 4 = | I - Z Z', A1, ' | / ( n ulp )',
284 $ / ' 5 = | A - UZ T (UZ)', A1, ' | / ( |A| n ulp ) ',
285 $ ' 6 = | I - UZ (UZ)', A1, ' | / ( n ulp )', / ' 7 = | T(',
286 $ 'e.vects.) - T(no e.vects.) | / ( |T| ulp )', / ' 8 = | W',
287 $ '(e.vects.) - W(no e.vects.) | / ( |W| ulp )', / ' 9 = | ',
288 $ 'TR - RW | / ( |T| |R| ulp ) ', ' 10 = | LT - WL | / (',
289 $ ' |T| |L| ulp )', / ' 11= |HX - XW| / (|H| |X| ulp) (inv.',
290 $ 'it)', ' 12= |YH - WY| / (|H| |Y| ulp) (inv.it)' )
291 *
292 * Symmetric/Hermitian eigenproblem
293 *
294 9983 FORMAT( ' Matrix types (see xDRVST for details): ' )
295 *
296 9982 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
297 $ ' ', ' 5=Diagonal: clustered entries.', / ' 2=',
298 $ 'Identity matrix. ', ' 6=Diagonal: lar',
299 $ 'ge, evenly spaced.', / ' 3=Diagonal: evenly spaced entri',
300 $ 'es. ', ' 7=Diagonal: small, evenly spaced.', / ' 4=D',
301 $ 'iagonal: geometr. spaced entries.' )
302 9981 FORMAT( ' Dense ', A, ' Matrices:', / ' 8=Evenly spaced eigen',
303 $ 'vals. ', ' 12=Small, evenly spaced eigenvals.',
304 $ / ' 9=Geometrically spaced eigenvals. ', ' 13=Matrix ',
305 $ 'with random O(1) entries.', / ' 10=Clustered eigenvalues.',
306 $ ' ', ' 14=Matrix with large random entries.',
307 $ / ' 11=Large, evenly spaced eigenvals. ', ' 15=Matrix ',
308 $ 'with small random entries.' )
309 *
310 * Symmetric/Hermitian Generalized eigenproblem
311 *
312 9980 FORMAT( ' Matrix types (see xDRVSG for details): ' )
313 *
314 9979 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
315 $ ' ', ' 5=Diagonal: clustered entries.', / ' 2=',
316 $ 'Identity matrix. ', ' 6=Diagonal: lar',
317 $ 'ge, evenly spaced.', / ' 3=Diagonal: evenly spaced entri',
318 $ 'es. ', ' 7=Diagonal: small, evenly spaced.', / ' 4=D',
319 $ 'iagonal: geometr. spaced entries.' )
320 9978 FORMAT( ' Dense or Banded ', A, ' Matrices: ',
321 $ / ' 8=Evenly spaced eigenvals. ',
322 $ ' 15=Matrix with small random entries.',
323 $ / ' 9=Geometrically spaced eigenvals. ',
324 $ ' 16=Evenly spaced eigenvals, KA=1, KB=1.',
325 $ / ' 10=Clustered eigenvalues. ',
326 $ ' 17=Evenly spaced eigenvals, KA=2, KB=1.',
327 $ / ' 11=Large, evenly spaced eigenvals. ',
328 $ ' 18=Evenly spaced eigenvals, KA=2, KB=2.',
329 $ / ' 12=Small, evenly spaced eigenvals. ',
330 $ ' 19=Evenly spaced eigenvals, KA=3, KB=1.',
331 $ / ' 13=Matrix with random O(1) entries. ',
332 $ ' 20=Evenly spaced eigenvals, KA=3, KB=2.',
333 $ / ' 14=Matrix with large random entries.',
334 $ ' 21=Evenly spaced eigenvals, KA=3, KB=3.' )
335 9977 FORMAT( / ' Tests performed: ',
336 $ / '( For each pair (A,B), where A is of the given type ',
337 $ / ' and B is a random well-conditioned matrix. D is ',
338 $ / ' diagonal, and Z is orthogonal. )',
339 $ / ' 1 = DSYGV, with ITYPE=1 and UPLO=''U'':',
340 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
341 $ / ' 2 = DSPGV, with ITYPE=1 and UPLO=''U'':',
342 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
343 $ / ' 3 = DSBGV, with ITYPE=1 and UPLO=''U'':',
344 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
345 $ / ' 4 = DSYGV, with ITYPE=1 and UPLO=''L'':',
346 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
347 $ / ' 5 = DSPGV, with ITYPE=1 and UPLO=''L'':',
348 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
349 $ / ' 6 = DSBGV, with ITYPE=1 and UPLO=''L'':',
350 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ' )
351 9976 FORMAT( ' 7 = DSYGV, with ITYPE=2 and UPLO=''U'':',
352 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
353 $ / ' 8 = DSPGV, with ITYPE=2 and UPLO=''U'':',
354 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
355 $ / ' 9 = DSPGV, with ITYPE=2 and UPLO=''L'':',
356 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
357 $ / '10 = DSPGV, with ITYPE=2 and UPLO=''L'':',
358 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
359 $ / '11 = DSYGV, with ITYPE=3 and UPLO=''U'':',
360 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
361 $ / '12 = DSPGV, with ITYPE=3 and UPLO=''U'':',
362 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
363 $ / '13 = DSYGV, with ITYPE=3 and UPLO=''L'':',
364 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
365 $ / '14 = DSPGV, with ITYPE=3 and UPLO=''L'':',
366 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ' )
367 9975 FORMAT( / ' Tests performed: ',
368 $ / '( For each pair (A,B), where A is of the given type ',
369 $ / ' and B is a random well-conditioned matrix. D is ',
370 $ / ' diagonal, and Z is unitary. )',
371 $ / ' 1 = ZHEGV, with ITYPE=1 and UPLO=''U'':',
372 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
373 $ / ' 2 = ZHPGV, with ITYPE=1 and UPLO=''U'':',
374 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
375 $ / ' 3 = ZHBGV, with ITYPE=1 and UPLO=''U'':',
376 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
377 $ / ' 4 = ZHEGV, with ITYPE=1 and UPLO=''L'':',
378 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
379 $ / ' 5 = ZHPGV, with ITYPE=1 and UPLO=''L'':',
380 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ',
381 $ / ' 6 = ZHBGV, with ITYPE=1 and UPLO=''L'':',
382 $ ' | A Z - B Z D | / ( |A| |Z| n ulp ) ' )
383 9974 FORMAT( ' 7 = ZHEGV, with ITYPE=2 and UPLO=''U'':',
384 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
385 $ / ' 8 = ZHPGV, with ITYPE=2 and UPLO=''U'':',
386 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
387 $ / ' 9 = ZHPGV, with ITYPE=2 and UPLO=''L'':',
388 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
389 $ / '10 = ZHPGV, with ITYPE=2 and UPLO=''L'':',
390 $ ' | A B Z - Z D | / ( |A| |Z| n ulp ) ',
391 $ / '11 = ZHEGV, with ITYPE=3 and UPLO=''U'':',
392 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
393 $ / '12 = ZHPGV, with ITYPE=3 and UPLO=''U'':',
394 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
395 $ / '13 = ZHEGV, with ITYPE=3 and UPLO=''L'':',
396 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ',
397 $ / '14 = ZHPGV, with ITYPE=3 and UPLO=''L'':',
398 $ ' | B A Z - Z D | / ( |A| |Z| n ulp ) ' )
399 *
400 * Singular Value Decomposition
401 *
402 9973 FORMAT( ' Matrix types (see xCHKBD for details):',
403 $ / ' Diagonal matrices:', / ' 1: Zero', 28X,
404 $ ' 5: Clustered entries', / ' 2: Identity', 24X,
405 $ ' 6: Large, evenly spaced entries',
406 $ / ' 3: Evenly spaced entries', 11X,
407 $ ' 7: Small, evenly spaced entries',
408 $ / ' 4: Geometrically spaced entries',
409 $ / ' General matrices:', / ' 8: Evenly spaced sing. vals.',
410 $ 7X, '12: Small, evenly spaced sing vals',
411 $ / ' 9: Geometrically spaced sing vals ',
412 $ '13: Random, O(1) entries', / ' 10: Clustered sing. vals.',
413 $ 11X, '14: Random, scaled near overflow',
414 $ / ' 11: Large, evenly spaced sing vals ',
415 $ '15: Random, scaled near underflow' )
416 *
417 9972 FORMAT( / ' Test ratios: ',
418 $ '(B: bidiagonal, S: diagonal, Q, P, U, and V: ', A10, / 16X,
419 $ 'X: m x nrhs, Y = Q'' X, and Z = U'' Y)',
420 $ / ' 1: norm( A - Q B P'' ) / ( norm(A) max(m,n) ulp )',
421 $ / ' 2: norm( I - Q'' Q ) / ( m ulp )',
422 $ / ' 3: norm( I - P'' P ) / ( n ulp )',
423 $ / ' 4: norm( B - U S V'' ) / ( norm(B) min(m,n) ulp )', /
424 $ ' 5: norm( Y - U Z ) / ( norm(Z) max(min(m,n),k) ulp )'
425 $ , / ' 6: norm( I - U'' U ) / ( min(m,n) ulp )',
426 $ / ' 7: norm( I - V'' V ) / ( min(m,n) ulp )' )
427 9971 FORMAT( ' 8: Test ordering of S (0 if nondecreasing, 1/ulp ',
428 $ ' otherwise)', /
429 $ ' 9: norm( S - S2 ) / ( norm(S) ulp ),',
430 $ ' where S2 is computed', / 44X,
431 $ 'without computing U and V''',
432 $ / ' 10: Sturm sequence test ',
433 $ '(0 if sing. vals of B within THRESH of S)',
434 $ / ' 11: norm( A - (QU) S (V'' P'') ) / ',
435 $ '( norm(A) max(m,n) ulp )', /
436 $ ' 12: norm( X - (QU) Z ) / ( |X| max(M,k) ulp )',
437 $ / ' 13: norm( I - (QU)''(QU) ) / ( M ulp )',
438 $ / ' 14: norm( I - (V'' P'') (P V) ) / ( N ulp )' )
439 *
440 * Band reduction to bidiagonal form
441 *
442 9970 FORMAT( ' Matrix types (see xCHKBB for details):',
443 $ / ' Diagonal matrices:', / ' 1: Zero', 28X,
444 $ ' 5: Clustered entries', / ' 2: Identity', 24X,
445 $ ' 6: Large, evenly spaced entries',
446 $ / ' 3: Evenly spaced entries', 11X,
447 $ ' 7: Small, evenly spaced entries',
448 $ / ' 4: Geometrically spaced entries',
449 $ / ' General matrices:', / ' 8: Evenly spaced sing. vals.',
450 $ 7X, '12: Small, evenly spaced sing vals',
451 $ / ' 9: Geometrically spaced sing vals ',
452 $ '13: Random, O(1) entries', / ' 10: Clustered sing. vals.',
453 $ 11X, '14: Random, scaled near overflow',
454 $ / ' 11: Large, evenly spaced sing vals ',
455 $ '15: Random, scaled near underflow' )
456 *
457 9969 FORMAT( / ' Test ratios: ', '(B: upper bidiagonal, Q and P: ',
458 $ A10, / 16X, 'C: m x nrhs, PT = P'', Y = Q'' C)',
459 $ / ' 1: norm( A - Q B PT ) / ( norm(A) max(m,n) ulp )',
460 $ / ' 2: norm( I - Q'' Q ) / ( m ulp )',
461 $ / ' 3: norm( I - PT PT'' ) / ( n ulp )',
462 $ / ' 4: norm( Y - Q'' C ) / ( norm(Y) max(m,nrhs) ulp )' )
463 9968 FORMAT( / ' Tests performed: See sdrvst.f' )
464 9967 FORMAT( / ' Tests performed: See cdrvst.f' )
465 *
466 * End of DLAHD2
467 *
468 END