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