1 SUBROUTINE ZDRVEV( NSIZES, NN, NTYPES, DOTYPE, ISEED, THRESH,
2 $ NOUNIT, A, LDA, H, W, W1, VL, LDVL, VR, LDVR,
3 $ LRE, LDLRE, RESULT, WORK, NWORK, RWORK, IWORK,
4 $ INFO )
5 *
6 * -- LAPACK test routine (version 3.1) --
7 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
8 * November 2006
9 *
10 * .. Scalar Arguments ..
11 INTEGER INFO, LDA, LDLRE, LDVL, LDVR, NOUNIT, NSIZES,
12 $ NTYPES, NWORK
13 DOUBLE PRECISION THRESH
14 * ..
15 * .. Array Arguments ..
16 LOGICAL DOTYPE( * )
17 INTEGER ISEED( 4 ), IWORK( * ), NN( * )
18 DOUBLE PRECISION RESULT( 7 ), RWORK( * )
19 COMPLEX*16 A( LDA, * ), H( LDA, * ), LRE( LDLRE, * ),
20 $ VL( LDVL, * ), VR( LDVR, * ), W( * ), W1( * ),
21 $ WORK( * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * ZDRVEV checks the nonsymmetric eigenvalue problem driver ZGEEV.
28 *
29 * When ZDRVEV is called, a number of matrix "sizes" ("n's") and a
30 * number of matrix "types" are specified. For each size ("n")
31 * and each type of matrix, one matrix will be generated and used
32 * to test the nonsymmetric eigenroutines. For each matrix, 7
33 * tests will be performed:
34 *
35 * (1) | A * VR - VR * W | / ( n |A| ulp )
36 *
37 * Here VR is the matrix of unit right eigenvectors.
38 * W is a diagonal matrix with diagonal entries W(j).
39 *
40 * (2) | A**H * VL - VL * W**H | / ( n |A| ulp )
41 *
42 * Here VL is the matrix of unit left eigenvectors, A**H is the
43 * conjugate-transpose of A, and W is as above.
44 *
45 * (3) | |VR(i)| - 1 | / ulp and whether largest component real
46 *
47 * VR(i) denotes the i-th column of VR.
48 *
49 * (4) | |VL(i)| - 1 | / ulp and whether largest component real
50 *
51 * VL(i) denotes the i-th column of VL.
52 *
53 * (5) W(full) = W(partial)
54 *
55 * W(full) denotes the eigenvalues computed when both VR and VL
56 * are also computed, and W(partial) denotes the eigenvalues
57 * computed when only W, only W and VR, or only W and VL are
58 * computed.
59 *
60 * (6) VR(full) = VR(partial)
61 *
62 * VR(full) denotes the right eigenvectors computed when both VR
63 * and VL are computed, and VR(partial) denotes the result
64 * when only VR is computed.
65 *
66 * (7) VL(full) = VL(partial)
67 *
68 * VL(full) denotes the left eigenvectors computed when both VR
69 * and VL are also computed, and VL(partial) denotes the result
70 * when only VL is computed.
71 *
72 * The "sizes" are specified by an array NN(1:NSIZES); the value of
73 * each element NN(j) specifies one size.
74 * The "types" are specified by a logical array DOTYPE( 1:NTYPES );
75 * if DOTYPE(j) is .TRUE., then matrix type "j" will be generated.
76 * Currently, the list of possible types is:
77 *
78 * (1) The zero matrix.
79 * (2) The identity matrix.
80 * (3) A (transposed) Jordan block, with 1's on the diagonal.
81 *
82 * (4) A diagonal matrix with evenly spaced entries
83 * 1, ..., ULP and random complex angles.
84 * (ULP = (first number larger than 1) - 1 )
85 * (5) A diagonal matrix with geometrically spaced entries
86 * 1, ..., ULP and random complex angles.
87 * (6) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
88 * and random complex angles.
89 *
90 * (7) Same as (4), but multiplied by a constant near
91 * the overflow threshold
92 * (8) Same as (4), but multiplied by a constant near
93 * the underflow threshold
94 *
95 * (9) A matrix of the form U' T U, where U is unitary and
96 * T has evenly spaced entries 1, ..., ULP with random complex
97 * angles on the diagonal and random O(1) entries in the upper
98 * triangle.
99 *
100 * (10) A matrix of the form U' T U, where U is unitary and
101 * T has geometrically spaced entries 1, ..., ULP with random
102 * complex angles on the diagonal and random O(1) entries in
103 * the upper triangle.
104 *
105 * (11) A matrix of the form U' T U, where U is unitary and
106 * T has "clustered" entries 1, ULP,..., ULP with random
107 * complex angles on the diagonal and random O(1) entries in
108 * the upper triangle.
109 *
110 * (12) A matrix of the form U' T U, where U is unitary and
111 * T has complex eigenvalues randomly chosen from
112 * ULP < |z| < 1 and random O(1) entries in the upper
113 * triangle.
114 *
115 * (13) A matrix of the form X' T X, where X has condition
116 * SQRT( ULP ) and T has evenly spaced entries 1, ..., ULP
117 * with random complex angles on the diagonal and random O(1)
118 * entries in the upper triangle.
119 *
120 * (14) A matrix of the form X' T X, where X has condition
121 * SQRT( ULP ) and T has geometrically spaced entries
122 * 1, ..., ULP with random complex angles on the diagonal
123 * and random O(1) entries in the upper triangle.
124 *
125 * (15) A matrix of the form X' T X, where X has condition
126 * SQRT( ULP ) and T has "clustered" entries 1, ULP,..., ULP
127 * with random complex angles on the diagonal and random O(1)
128 * entries in the upper triangle.
129 *
130 * (16) A matrix of the form X' T X, where X has condition
131 * SQRT( ULP ) and T has complex eigenvalues randomly chosen
132 * from ULP < |z| < 1 and random O(1) entries in the upper
133 * triangle.
134 *
135 * (17) Same as (16), but multiplied by a constant
136 * near the overflow threshold
137 * (18) Same as (16), but multiplied by a constant
138 * near the underflow threshold
139 *
140 * (19) Nonsymmetric matrix with random entries chosen from |z| < 1
141 * If N is at least 4, all entries in first two rows and last
142 * row, and first column and last two columns are zero.
143 * (20) Same as (19), but multiplied by a constant
144 * near the overflow threshold
145 * (21) Same as (19), but multiplied by a constant
146 * near the underflow threshold
147 *
148 * Arguments
149 * ==========
150 *
151 * NSIZES (input) INTEGER
152 * The number of sizes of matrices to use. If it is zero,
153 * ZDRVEV does nothing. It must be at least zero.
154 *
155 * NN (input) INTEGER array, dimension (NSIZES)
156 * An array containing the sizes to be used for the matrices.
157 * Zero values will be skipped. The values must be at least
158 * zero.
159 *
160 * NTYPES (input) INTEGER
161 * The number of elements in DOTYPE. If it is zero, ZDRVEV
162 * does nothing. It must be at least zero. If it is MAXTYP+1
163 * and NSIZES is 1, then an additional type, MAXTYP+1 is
164 * defined, which is to use whatever matrix is in A. This
165 * is only useful if DOTYPE(1:MAXTYP) is .FALSE. and
166 * DOTYPE(MAXTYP+1) is .TRUE. .
167 *
168 * DOTYPE (input) LOGICAL array, dimension (NTYPES)
169 * If DOTYPE(j) is .TRUE., then for each size in NN a
170 * matrix of that size and of type j will be generated.
171 * If NTYPES is smaller than the maximum number of types
172 * defined (PARAMETER MAXTYP), then types NTYPES+1 through
173 * MAXTYP will not be generated. If NTYPES is larger
174 * than MAXTYP, DOTYPE(MAXTYP+1) through DOTYPE(NTYPES)
175 * will be ignored.
176 *
177 * ISEED (input/output) INTEGER array, dimension (4)
178 * On entry ISEED specifies the seed of the random number
179 * generator. The array elements should be between 0 and 4095;
180 * if not they will be reduced mod 4096. Also, ISEED(4) must
181 * be odd. The random number generator uses a linear
182 * congruential sequence limited to small integers, and so
183 * should produce machine independent random numbers. The
184 * values of ISEED are changed on exit, and can be used in the
185 * next call to ZDRVEV to continue the same random number
186 * sequence.
187 *
188 * THRESH (input) DOUBLE PRECISION
189 * A test will count as "failed" if the "error", computed as
190 * described above, exceeds THRESH. Note that the error
191 * is scaled to be O(1), so THRESH should be a reasonably
192 * small multiple of 1, e.g., 10 or 100. In particular,
193 * it should not depend on the precision (single vs. double)
194 * or the size of the matrix. It must be at least zero.
195 *
196 * NOUNIT (input) INTEGER
197 * The FORTRAN unit number for printing out error messages
198 * (e.g., if a routine returns INFO not equal to 0.)
199 *
200 * A (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
201 * Used to hold the matrix whose eigenvalues are to be
202 * computed. On exit, A contains the last matrix actually used.
203 *
204 * LDA (input) INTEGER
205 * The leading dimension of A, and H. LDA must be at
206 * least 1 and at least max(NN).
207 *
208 * H (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
209 * Another copy of the test matrix A, modified by ZGEEV.
210 *
211 * W (workspace) COMPLEX*16 array, dimension (max(NN))
212 * The eigenvalues of A. On exit, W are the eigenvalues of
213 * the matrix in A.
214 *
215 * W1 (workspace) COMPLEX*16 array, dimension (max(NN))
216 * Like W, this array contains the eigenvalues of A,
217 * but those computed when ZGEEV only computes a partial
218 * eigendecomposition, i.e. not the eigenvalues and left
219 * and right eigenvectors.
220 *
221 * VL (workspace) COMPLEX*16 array, dimension (LDVL, max(NN))
222 * VL holds the computed left eigenvectors.
223 *
224 * LDVL (input) INTEGER
225 * Leading dimension of VL. Must be at least max(1,max(NN)).
226 *
227 * VR (workspace) COMPLEX*16 array, dimension (LDVR, max(NN))
228 * VR holds the computed right eigenvectors.
229 *
230 * LDVR (input) INTEGER
231 * Leading dimension of VR. Must be at least max(1,max(NN)).
232 *
233 * LRE (workspace) COMPLEX*16 array, dimension (LDLRE, max(NN))
234 * LRE holds the computed right or left eigenvectors.
235 *
236 * LDLRE (input) INTEGER
237 * Leading dimension of LRE. Must be at least max(1,max(NN)).
238 *
239 * RESULT (output) DOUBLE PRECISION array, dimension (7)
240 * The values computed by the seven tests described above.
241 * The values are currently limited to 1/ulp, to avoid
242 * overflow.
243 *
244 * WORK (workspace) COMPLEX*16 array, dimension (NWORK)
245 *
246 * NWORK (input) INTEGER
247 * The number of entries in WORK. This must be at least
248 * 5*NN(j)+2*NN(j)**2 for all j.
249 *
250 * RWORK (workspace) DOUBLE PRECISION array, dimension (2*max(NN))
251 *
252 * IWORK (workspace) INTEGER array, dimension (max(NN))
253 *
254 * INFO (output) INTEGER
255 * If 0, then everything ran OK.
256 * -1: NSIZES < 0
257 * -2: Some NN(j) < 0
258 * -3: NTYPES < 0
259 * -6: THRESH < 0
260 * -9: LDA < 1 or LDA < NMAX, where NMAX is max( NN(j) ).
261 * -14: LDVL < 1 or LDVL < NMAX, where NMAX is max( NN(j) ).
262 * -16: LDVR < 1 or LDVR < NMAX, where NMAX is max( NN(j) ).
263 * -18: LDLRE < 1 or LDLRE < NMAX, where NMAX is max( NN(j) ).
264 * -21: NWORK too small.
265 * If ZLATMR, CLATMS, CLATME or ZGEEV returns an error code,
266 * the absolute value of it is returned.
267 *
268 *-----------------------------------------------------------------------
269 *
270 * Some Local Variables and Parameters:
271 * ---- ----- --------- --- ----------
272 *
273 * ZERO, ONE Real 0 and 1.
274 * MAXTYP The number of types defined.
275 * NMAX Largest value in NN.
276 * NERRS The number of tests which have exceeded THRESH
277 * COND, CONDS,
278 * IMODE Values to be passed to the matrix generators.
279 * ANORM Norm of A; passed to matrix generators.
280 *
281 * OVFL, UNFL Overflow and underflow thresholds.
282 * ULP, ULPINV Finest relative precision and its inverse.
283 * RTULP, RTULPI Square roots of the previous 4 values.
284 *
285 * The following four arrays decode JTYPE:
286 * KTYPE(j) The general type (1-10) for type "j".
287 * KMODE(j) The MODE value to be passed to the matrix
288 * generator for type "j".
289 * KMAGN(j) The order of magnitude ( O(1),
290 * O(overflow^(1/2) ), O(underflow^(1/2) )
291 * KCONDS(j) Selectw whether CONDS is to be 1 or
292 * 1/sqrt(ulp). (0 means irrelevant.)
293 *
294 * =====================================================================
295 *
296 * .. Parameters ..
297 COMPLEX*16 CZERO
298 PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ) )
299 COMPLEX*16 CONE
300 PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
301 DOUBLE PRECISION ZERO, ONE
302 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
303 DOUBLE PRECISION TWO
304 PARAMETER ( TWO = 2.0D+0 )
305 INTEGER MAXTYP
306 PARAMETER ( MAXTYP = 21 )
307 * ..
308 * .. Local Scalars ..
309 LOGICAL BADNN
310 CHARACTER*3 PATH
311 INTEGER IINFO, IMODE, ITYPE, IWK, J, JCOL, JJ, JSIZE,
312 $ JTYPE, MTYPES, N, NERRS, NFAIL, NMAX, NNWORK,
313 $ NTEST, NTESTF, NTESTT
314 DOUBLE PRECISION ANORM, COND, CONDS, OVFL, RTULP, RTULPI, TNRM,
315 $ ULP, ULPINV, UNFL, VMX, VRMX, VTST
316 * ..
317 * .. Local Arrays ..
318 INTEGER IDUMMA( 1 ), IOLDSD( 4 ), KCONDS( MAXTYP ),
319 $ KMAGN( MAXTYP ), KMODE( MAXTYP ),
320 $ KTYPE( MAXTYP )
321 DOUBLE PRECISION RES( 2 )
322 COMPLEX*16 DUM( 1 )
323 * ..
324 * .. External Functions ..
325 DOUBLE PRECISION DLAMCH, DZNRM2
326 EXTERNAL DLAMCH, DZNRM2
327 * ..
328 * .. External Subroutines ..
329 EXTERNAL DLABAD, DLASUM, XERBLA, ZGEEV, ZGET22, ZLACPY,
330 $ ZLASET, ZLATME, ZLATMR, ZLATMS
331 * ..
332 * .. Intrinsic Functions ..
333 INTRINSIC ABS, DBLE, DCMPLX, DIMAG, MAX, MIN, SQRT
334 * ..
335 * .. Data statements ..
336 DATA KTYPE / 1, 2, 3, 5*4, 4*6, 6*6, 3*9 /
337 DATA KMAGN / 3*1, 1, 1, 1, 2, 3, 4*1, 1, 1, 1, 1, 2,
338 $ 3, 1, 2, 3 /
339 DATA KMODE / 3*0, 4, 3, 1, 4, 4, 4, 3, 1, 5, 4, 3,
340 $ 1, 5, 5, 5, 4, 3, 1 /
341 DATA KCONDS / 3*0, 5*0, 4*1, 6*2, 3*0 /
342 * ..
343 * .. Executable Statements ..
344 *
345 PATH( 1: 1 ) = 'Zomplex precision'
346 PATH( 2: 3 ) = 'EV'
347 *
348 * Check for errors
349 *
350 NTESTT = 0
351 NTESTF = 0
352 INFO = 0
353 *
354 * Important constants
355 *
356 BADNN = .FALSE.
357 NMAX = 0
358 DO 10 J = 1, NSIZES
359 NMAX = MAX( NMAX, NN( J ) )
360 IF( NN( J ).LT.0 )
361 $ BADNN = .TRUE.
362 10 CONTINUE
363 *
364 * Check for errors
365 *
366 IF( NSIZES.LT.0 ) THEN
367 INFO = -1
368 ELSE IF( BADNN ) THEN
369 INFO = -2
370 ELSE IF( NTYPES.LT.0 ) THEN
371 INFO = -3
372 ELSE IF( THRESH.LT.ZERO ) THEN
373 INFO = -6
374 ELSE IF( NOUNIT.LE.0 ) THEN
375 INFO = -7
376 ELSE IF( LDA.LT.1 .OR. LDA.LT.NMAX ) THEN
377 INFO = -9
378 ELSE IF( LDVL.LT.1 .OR. LDVL.LT.NMAX ) THEN
379 INFO = -14
380 ELSE IF( LDVR.LT.1 .OR. LDVR.LT.NMAX ) THEN
381 INFO = -16
382 ELSE IF( LDLRE.LT.1 .OR. LDLRE.LT.NMAX ) THEN
383 INFO = -28
384 ELSE IF( 5*NMAX+2*NMAX**2.GT.NWORK ) THEN
385 INFO = -21
386 END IF
387 *
388 IF( INFO.NE.0 ) THEN
389 CALL XERBLA( 'ZDRVEV', -INFO )
390 RETURN
391 END IF
392 *
393 * Quick return if nothing to do
394 *
395 IF( NSIZES.EQ.0 .OR. NTYPES.EQ.0 )
396 $ RETURN
397 *
398 * More Important constants
399 *
400 UNFL = DLAMCH( 'Safe minimum' )
401 OVFL = ONE / UNFL
402 CALL DLABAD( UNFL, OVFL )
403 ULP = DLAMCH( 'Precision' )
404 ULPINV = ONE / ULP
405 RTULP = SQRT( ULP )
406 RTULPI = ONE / RTULP
407 *
408 * Loop over sizes, types
409 *
410 NERRS = 0
411 *
412 DO 270 JSIZE = 1, NSIZES
413 N = NN( JSIZE )
414 IF( NSIZES.NE.1 ) THEN
415 MTYPES = MIN( MAXTYP, NTYPES )
416 ELSE
417 MTYPES = MIN( MAXTYP+1, NTYPES )
418 END IF
419 *
420 DO 260 JTYPE = 1, MTYPES
421 IF( .NOT.DOTYPE( JTYPE ) )
422 $ GO TO 260
423 *
424 * Save ISEED in case of an error.
425 *
426 DO 20 J = 1, 4
427 IOLDSD( J ) = ISEED( J )
428 20 CONTINUE
429 *
430 * Compute "A"
431 *
432 * Control parameters:
433 *
434 * KMAGN KCONDS KMODE KTYPE
435 * =1 O(1) 1 clustered 1 zero
436 * =2 large large clustered 2 identity
437 * =3 small exponential Jordan
438 * =4 arithmetic diagonal, (w/ eigenvalues)
439 * =5 random log symmetric, w/ eigenvalues
440 * =6 random general, w/ eigenvalues
441 * =7 random diagonal
442 * =8 random symmetric
443 * =9 random general
444 * =10 random triangular
445 *
446 IF( MTYPES.GT.MAXTYP )
447 $ GO TO 90
448 *
449 ITYPE = KTYPE( JTYPE )
450 IMODE = KMODE( JTYPE )
451 *
452 * Compute norm
453 *
454 GO TO ( 30, 40, 50 )KMAGN( JTYPE )
455 *
456 30 CONTINUE
457 ANORM = ONE
458 GO TO 60
459 *
460 40 CONTINUE
461 ANORM = OVFL*ULP
462 GO TO 60
463 *
464 50 CONTINUE
465 ANORM = UNFL*ULPINV
466 GO TO 60
467 *
468 60 CONTINUE
469 *
470 CALL ZLASET( 'Full', LDA, N, CZERO, CZERO, A, LDA )
471 IINFO = 0
472 COND = ULPINV
473 *
474 * Special Matrices -- Identity & Jordan block
475 *
476 * Zero
477 *
478 IF( ITYPE.EQ.1 ) THEN
479 IINFO = 0
480 *
481 ELSE IF( ITYPE.EQ.2 ) THEN
482 *
483 * Identity
484 *
485 DO 70 JCOL = 1, N
486 A( JCOL, JCOL ) = DCMPLX( ANORM )
487 70 CONTINUE
488 *
489 ELSE IF( ITYPE.EQ.3 ) THEN
490 *
491 * Jordan Block
492 *
493 DO 80 JCOL = 1, N
494 A( JCOL, JCOL ) = DCMPLX( ANORM )
495 IF( JCOL.GT.1 )
496 $ A( JCOL, JCOL-1 ) = CONE
497 80 CONTINUE
498 *
499 ELSE IF( ITYPE.EQ.4 ) THEN
500 *
501 * Diagonal Matrix, [Eigen]values Specified
502 *
503 CALL ZLATMS( N, N, 'S', ISEED, 'H', RWORK, IMODE, COND,
504 $ ANORM, 0, 0, 'N', A, LDA, WORK( N+1 ),
505 $ IINFO )
506 *
507 ELSE IF( ITYPE.EQ.5 ) THEN
508 *
509 * Hermitian, eigenvalues specified
510 *
511 CALL ZLATMS( N, N, 'S', ISEED, 'H', RWORK, IMODE, COND,
512 $ ANORM, N, N, 'N', A, LDA, WORK( N+1 ),
513 $ IINFO )
514 *
515 ELSE IF( ITYPE.EQ.6 ) THEN
516 *
517 * General, eigenvalues specified
518 *
519 IF( KCONDS( JTYPE ).EQ.1 ) THEN
520 CONDS = ONE
521 ELSE IF( KCONDS( JTYPE ).EQ.2 ) THEN
522 CONDS = RTULPI
523 ELSE
524 CONDS = ZERO
525 END IF
526 *
527 CALL ZLATME( N, 'D', ISEED, WORK, IMODE, COND, CONE, ' ',
528 $ 'T', 'T', 'T', RWORK, 4, CONDS, N, N, ANORM,
529 $ A, LDA, WORK( 2*N+1 ), IINFO )
530 *
531 ELSE IF( ITYPE.EQ.7 ) THEN
532 *
533 * Diagonal, random eigenvalues
534 *
535 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
536 $ 'T', 'N', WORK( N+1 ), 1, ONE,
537 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, 0, 0,
538 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
539 *
540 ELSE IF( ITYPE.EQ.8 ) THEN
541 *
542 * Symmetric, random eigenvalues
543 *
544 CALL ZLATMR( N, N, 'D', ISEED, 'H', WORK, 6, ONE, CONE,
545 $ 'T', 'N', WORK( N+1 ), 1, ONE,
546 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, N,
547 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
548 *
549 ELSE IF( ITYPE.EQ.9 ) THEN
550 *
551 * General, random eigenvalues
552 *
553 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
554 $ 'T', 'N', WORK( N+1 ), 1, ONE,
555 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, N,
556 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
557 IF( N.GE.4 ) THEN
558 CALL ZLASET( 'Full', 2, N, CZERO, CZERO, A, LDA )
559 CALL ZLASET( 'Full', N-3, 1, CZERO, CZERO, A( 3, 1 ),
560 $ LDA )
561 CALL ZLASET( 'Full', N-3, 2, CZERO, CZERO,
562 $ A( 3, N-1 ), LDA )
563 CALL ZLASET( 'Full', 1, N, CZERO, CZERO, A( N, 1 ),
564 $ LDA )
565 END IF
566 *
567 ELSE IF( ITYPE.EQ.10 ) THEN
568 *
569 * Triangular, random eigenvalues
570 *
571 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
572 $ 'T', 'N', WORK( N+1 ), 1, ONE,
573 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, 0,
574 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
575 *
576 ELSE
577 *
578 IINFO = 1
579 END IF
580 *
581 IF( IINFO.NE.0 ) THEN
582 WRITE( NOUNIT, FMT = 9993 )'Generator', IINFO, N, JTYPE,
583 $ IOLDSD
584 INFO = ABS( IINFO )
585 RETURN
586 END IF
587 *
588 90 CONTINUE
589 *
590 * Test for minimal and generous workspace
591 *
592 DO 250 IWK = 1, 2
593 IF( IWK.EQ.1 ) THEN
594 NNWORK = 2*N
595 ELSE
596 NNWORK = 5*N + 2*N**2
597 END IF
598 NNWORK = MAX( NNWORK, 1 )
599 *
600 * Initialize RESULT
601 *
602 DO 100 J = 1, 7
603 RESULT( J ) = -ONE
604 100 CONTINUE
605 *
606 * Compute eigenvalues and eigenvectors, and test them
607 *
608 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
609 CALL ZGEEV( 'V', 'V', N, H, LDA, W, VL, LDVL, VR, LDVR,
610 $ WORK, NNWORK, RWORK, IINFO )
611 IF( IINFO.NE.0 ) THEN
612 RESULT( 1 ) = ULPINV
613 WRITE( NOUNIT, FMT = 9993 )'ZGEEV1', IINFO, N, JTYPE,
614 $ IOLDSD
615 INFO = ABS( IINFO )
616 GO TO 220
617 END IF
618 *
619 * Do Test (1)
620 *
621 CALL ZGET22( 'N', 'N', 'N', N, A, LDA, VR, LDVR, W, WORK,
622 $ RWORK, RES )
623 RESULT( 1 ) = RES( 1 )
624 *
625 * Do Test (2)
626 *
627 CALL ZGET22( 'C', 'N', 'C', N, A, LDA, VL, LDVL, W, WORK,
628 $ RWORK, RES )
629 RESULT( 2 ) = RES( 1 )
630 *
631 * Do Test (3)
632 *
633 DO 120 J = 1, N
634 TNRM = DZNRM2( N, VR( 1, J ), 1 )
635 RESULT( 3 ) = MAX( RESULT( 3 ),
636 $ MIN( ULPINV, ABS( TNRM-ONE ) / ULP ) )
637 VMX = ZERO
638 VRMX = ZERO
639 DO 110 JJ = 1, N
640 VTST = ABS( VR( JJ, J ) )
641 IF( VTST.GT.VMX )
642 $ VMX = VTST
643 IF( DIMAG( VR( JJ, J ) ).EQ.ZERO .AND.
644 $ ABS( DBLE( VR( JJ, J ) ) ).GT.VRMX )
645 $ VRMX = ABS( DBLE( VR( JJ, J ) ) )
646 110 CONTINUE
647 IF( VRMX / VMX.LT.ONE-TWO*ULP )
648 $ RESULT( 3 ) = ULPINV
649 120 CONTINUE
650 *
651 * Do Test (4)
652 *
653 DO 140 J = 1, N
654 TNRM = DZNRM2( N, VL( 1, J ), 1 )
655 RESULT( 4 ) = MAX( RESULT( 4 ),
656 $ MIN( ULPINV, ABS( TNRM-ONE ) / ULP ) )
657 VMX = ZERO
658 VRMX = ZERO
659 DO 130 JJ = 1, N
660 VTST = ABS( VL( JJ, J ) )
661 IF( VTST.GT.VMX )
662 $ VMX = VTST
663 IF( DIMAG( VL( JJ, J ) ).EQ.ZERO .AND.
664 $ ABS( DBLE( VL( JJ, J ) ) ).GT.VRMX )
665 $ VRMX = ABS( DBLE( VL( JJ, J ) ) )
666 130 CONTINUE
667 IF( VRMX / VMX.LT.ONE-TWO*ULP )
668 $ RESULT( 4 ) = ULPINV
669 140 CONTINUE
670 *
671 * Compute eigenvalues only, and test them
672 *
673 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
674 CALL ZGEEV( 'N', 'N', N, H, LDA, W1, DUM, 1, DUM, 1,
675 $ WORK, NNWORK, RWORK, IINFO )
676 IF( IINFO.NE.0 ) THEN
677 RESULT( 1 ) = ULPINV
678 WRITE( NOUNIT, FMT = 9993 )'ZGEEV2', IINFO, N, JTYPE,
679 $ IOLDSD
680 INFO = ABS( IINFO )
681 GO TO 220
682 END IF
683 *
684 * Do Test (5)
685 *
686 DO 150 J = 1, N
687 IF( W( J ).NE.W1( J ) )
688 $ RESULT( 5 ) = ULPINV
689 150 CONTINUE
690 *
691 * Compute eigenvalues and right eigenvectors, and test them
692 *
693 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
694 CALL ZGEEV( 'N', 'V', N, H, LDA, W1, DUM, 1, LRE, LDLRE,
695 $ WORK, NNWORK, RWORK, IINFO )
696 IF( IINFO.NE.0 ) THEN
697 RESULT( 1 ) = ULPINV
698 WRITE( NOUNIT, FMT = 9993 )'ZGEEV3', IINFO, N, JTYPE,
699 $ IOLDSD
700 INFO = ABS( IINFO )
701 GO TO 220
702 END IF
703 *
704 * Do Test (5) again
705 *
706 DO 160 J = 1, N
707 IF( W( J ).NE.W1( J ) )
708 $ RESULT( 5 ) = ULPINV
709 160 CONTINUE
710 *
711 * Do Test (6)
712 *
713 DO 180 J = 1, N
714 DO 170 JJ = 1, N
715 IF( VR( J, JJ ).NE.LRE( J, JJ ) )
716 $ RESULT( 6 ) = ULPINV
717 170 CONTINUE
718 180 CONTINUE
719 *
720 * Compute eigenvalues and left eigenvectors, and test them
721 *
722 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
723 CALL ZGEEV( 'V', 'N', N, H, LDA, W1, LRE, LDLRE, DUM, 1,
724 $ WORK, NNWORK, RWORK, IINFO )
725 IF( IINFO.NE.0 ) THEN
726 RESULT( 1 ) = ULPINV
727 WRITE( NOUNIT, FMT = 9993 )'ZGEEV4', IINFO, N, JTYPE,
728 $ IOLDSD
729 INFO = ABS( IINFO )
730 GO TO 220
731 END IF
732 *
733 * Do Test (5) again
734 *
735 DO 190 J = 1, N
736 IF( W( J ).NE.W1( J ) )
737 $ RESULT( 5 ) = ULPINV
738 190 CONTINUE
739 *
740 * Do Test (7)
741 *
742 DO 210 J = 1, N
743 DO 200 JJ = 1, N
744 IF( VL( J, JJ ).NE.LRE( J, JJ ) )
745 $ RESULT( 7 ) = ULPINV
746 200 CONTINUE
747 210 CONTINUE
748 *
749 * End of Loop -- Check for RESULT(j) > THRESH
750 *
751 220 CONTINUE
752 *
753 NTEST = 0
754 NFAIL = 0
755 DO 230 J = 1, 7
756 IF( RESULT( J ).GE.ZERO )
757 $ NTEST = NTEST + 1
758 IF( RESULT( J ).GE.THRESH )
759 $ NFAIL = NFAIL + 1
760 230 CONTINUE
761 *
762 IF( NFAIL.GT.0 )
763 $ NTESTF = NTESTF + 1
764 IF( NTESTF.EQ.1 ) THEN
765 WRITE( NOUNIT, FMT = 9999 )PATH
766 WRITE( NOUNIT, FMT = 9998 )
767 WRITE( NOUNIT, FMT = 9997 )
768 WRITE( NOUNIT, FMT = 9996 )
769 WRITE( NOUNIT, FMT = 9995 )THRESH
770 NTESTF = 2
771 END IF
772 *
773 DO 240 J = 1, 7
774 IF( RESULT( J ).GE.THRESH ) THEN
775 WRITE( NOUNIT, FMT = 9994 )N, IWK, IOLDSD, JTYPE,
776 $ J, RESULT( J )
777 END IF
778 240 CONTINUE
779 *
780 NERRS = NERRS + NFAIL
781 NTESTT = NTESTT + NTEST
782 *
783 250 CONTINUE
784 260 CONTINUE
785 270 CONTINUE
786 *
787 * Summary
788 *
789 CALL DLASUM( PATH, NOUNIT, NERRS, NTESTT )
790 *
791 9999 FORMAT( / 1X, A3, ' -- Complex Eigenvalue-Eigenvector ',
792 $ 'Decomposition Driver', /
793 $ ' Matrix types (see ZDRVEV for details): ' )
794 *
795 9998 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
796 $ ' ', ' 5=Diagonal: geometr. spaced entries.',
797 $ / ' 2=Identity matrix. ', ' 6=Diagona',
798 $ 'l: clustered entries.', / ' 3=Transposed Jordan block. ',
799 $ ' ', ' 7=Diagonal: large, evenly spaced.', / ' ',
800 $ '4=Diagonal: evenly spaced entries. ', ' 8=Diagonal: s',
801 $ 'mall, evenly spaced.' )
802 9997 FORMAT( ' Dense, Non-Symmetric Matrices:', / ' 9=Well-cond., ev',
803 $ 'enly spaced eigenvals.', ' 14=Ill-cond., geomet. spaced e',
804 $ 'igenals.', / ' 10=Well-cond., geom. spaced eigenvals. ',
805 $ ' 15=Ill-conditioned, clustered e.vals.', / ' 11=Well-cond',
806 $ 'itioned, clustered e.vals. ', ' 16=Ill-cond., random comp',
807 $ 'lex ', A6, / ' 12=Well-cond., random complex ', A6, ' ',
808 $ ' 17=Ill-cond., large rand. complx ', A4, / ' 13=Ill-condi',
809 $ 'tioned, evenly spaced. ', ' 18=Ill-cond., small rand.',
810 $ ' complx ', A4 )
811 9996 FORMAT( ' 19=Matrix with random O(1) entries. ', ' 21=Matrix ',
812 $ 'with small random entries.', / ' 20=Matrix with large ran',
813 $ 'dom entries. ', / )
814 9995 FORMAT( ' Tests performed with test threshold =', F8.2,
815 $ / / ' 1 = | A VR - VR W | / ( n |A| ulp ) ',
816 $ / ' 2 = | conj-trans(A) VL - VL conj-trans(W) | /',
817 $ ' ( n |A| ulp ) ', / ' 3 = | |VR(i)| - 1 | / ulp ',
818 $ / ' 4 = | |VL(i)| - 1 | / ulp ',
819 $ / ' 5 = 0 if W same no matter if VR or VL computed,',
820 $ ' 1/ulp otherwise', /
821 $ ' 6 = 0 if VR same no matter if VL computed,',
822 $ ' 1/ulp otherwise', /
823 $ ' 7 = 0 if VL same no matter if VR computed,',
824 $ ' 1/ulp otherwise', / )
825 9994 FORMAT( ' N=', I5, ', IWK=', I2, ', seed=', 4( I4, ',' ),
826 $ ' type ', I2, ', test(', I2, ')=', G10.3 )
827 9993 FORMAT( ' ZDRVEV: ', A, ' returned INFO=', I6, '.', / 9X, 'N=',
828 $ I6, ', JTYPE=', I6, ', ISEED=(', 3( I5, ',' ), I5, ')' )
829 *
830 RETURN
831 *
832 * End of ZDRVEV
833 *
834 END
2 $ NOUNIT, A, LDA, H, W, W1, VL, LDVL, VR, LDVR,
3 $ LRE, LDLRE, RESULT, WORK, NWORK, RWORK, IWORK,
4 $ INFO )
5 *
6 * -- LAPACK test routine (version 3.1) --
7 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
8 * November 2006
9 *
10 * .. Scalar Arguments ..
11 INTEGER INFO, LDA, LDLRE, LDVL, LDVR, NOUNIT, NSIZES,
12 $ NTYPES, NWORK
13 DOUBLE PRECISION THRESH
14 * ..
15 * .. Array Arguments ..
16 LOGICAL DOTYPE( * )
17 INTEGER ISEED( 4 ), IWORK( * ), NN( * )
18 DOUBLE PRECISION RESULT( 7 ), RWORK( * )
19 COMPLEX*16 A( LDA, * ), H( LDA, * ), LRE( LDLRE, * ),
20 $ VL( LDVL, * ), VR( LDVR, * ), W( * ), W1( * ),
21 $ WORK( * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * ZDRVEV checks the nonsymmetric eigenvalue problem driver ZGEEV.
28 *
29 * When ZDRVEV is called, a number of matrix "sizes" ("n's") and a
30 * number of matrix "types" are specified. For each size ("n")
31 * and each type of matrix, one matrix will be generated and used
32 * to test the nonsymmetric eigenroutines. For each matrix, 7
33 * tests will be performed:
34 *
35 * (1) | A * VR - VR * W | / ( n |A| ulp )
36 *
37 * Here VR is the matrix of unit right eigenvectors.
38 * W is a diagonal matrix with diagonal entries W(j).
39 *
40 * (2) | A**H * VL - VL * W**H | / ( n |A| ulp )
41 *
42 * Here VL is the matrix of unit left eigenvectors, A**H is the
43 * conjugate-transpose of A, and W is as above.
44 *
45 * (3) | |VR(i)| - 1 | / ulp and whether largest component real
46 *
47 * VR(i) denotes the i-th column of VR.
48 *
49 * (4) | |VL(i)| - 1 | / ulp and whether largest component real
50 *
51 * VL(i) denotes the i-th column of VL.
52 *
53 * (5) W(full) = W(partial)
54 *
55 * W(full) denotes the eigenvalues computed when both VR and VL
56 * are also computed, and W(partial) denotes the eigenvalues
57 * computed when only W, only W and VR, or only W and VL are
58 * computed.
59 *
60 * (6) VR(full) = VR(partial)
61 *
62 * VR(full) denotes the right eigenvectors computed when both VR
63 * and VL are computed, and VR(partial) denotes the result
64 * when only VR is computed.
65 *
66 * (7) VL(full) = VL(partial)
67 *
68 * VL(full) denotes the left eigenvectors computed when both VR
69 * and VL are also computed, and VL(partial) denotes the result
70 * when only VL is computed.
71 *
72 * The "sizes" are specified by an array NN(1:NSIZES); the value of
73 * each element NN(j) specifies one size.
74 * The "types" are specified by a logical array DOTYPE( 1:NTYPES );
75 * if DOTYPE(j) is .TRUE., then matrix type "j" will be generated.
76 * Currently, the list of possible types is:
77 *
78 * (1) The zero matrix.
79 * (2) The identity matrix.
80 * (3) A (transposed) Jordan block, with 1's on the diagonal.
81 *
82 * (4) A diagonal matrix with evenly spaced entries
83 * 1, ..., ULP and random complex angles.
84 * (ULP = (first number larger than 1) - 1 )
85 * (5) A diagonal matrix with geometrically spaced entries
86 * 1, ..., ULP and random complex angles.
87 * (6) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
88 * and random complex angles.
89 *
90 * (7) Same as (4), but multiplied by a constant near
91 * the overflow threshold
92 * (8) Same as (4), but multiplied by a constant near
93 * the underflow threshold
94 *
95 * (9) A matrix of the form U' T U, where U is unitary and
96 * T has evenly spaced entries 1, ..., ULP with random complex
97 * angles on the diagonal and random O(1) entries in the upper
98 * triangle.
99 *
100 * (10) A matrix of the form U' T U, where U is unitary and
101 * T has geometrically spaced entries 1, ..., ULP with random
102 * complex angles on the diagonal and random O(1) entries in
103 * the upper triangle.
104 *
105 * (11) A matrix of the form U' T U, where U is unitary and
106 * T has "clustered" entries 1, ULP,..., ULP with random
107 * complex angles on the diagonal and random O(1) entries in
108 * the upper triangle.
109 *
110 * (12) A matrix of the form U' T U, where U is unitary and
111 * T has complex eigenvalues randomly chosen from
112 * ULP < |z| < 1 and random O(1) entries in the upper
113 * triangle.
114 *
115 * (13) A matrix of the form X' T X, where X has condition
116 * SQRT( ULP ) and T has evenly spaced entries 1, ..., ULP
117 * with random complex angles on the diagonal and random O(1)
118 * entries in the upper triangle.
119 *
120 * (14) A matrix of the form X' T X, where X has condition
121 * SQRT( ULP ) and T has geometrically spaced entries
122 * 1, ..., ULP with random complex angles on the diagonal
123 * and random O(1) entries in the upper triangle.
124 *
125 * (15) A matrix of the form X' T X, where X has condition
126 * SQRT( ULP ) and T has "clustered" entries 1, ULP,..., ULP
127 * with random complex angles on the diagonal and random O(1)
128 * entries in the upper triangle.
129 *
130 * (16) A matrix of the form X' T X, where X has condition
131 * SQRT( ULP ) and T has complex eigenvalues randomly chosen
132 * from ULP < |z| < 1 and random O(1) entries in the upper
133 * triangle.
134 *
135 * (17) Same as (16), but multiplied by a constant
136 * near the overflow threshold
137 * (18) Same as (16), but multiplied by a constant
138 * near the underflow threshold
139 *
140 * (19) Nonsymmetric matrix with random entries chosen from |z| < 1
141 * If N is at least 4, all entries in first two rows and last
142 * row, and first column and last two columns are zero.
143 * (20) Same as (19), but multiplied by a constant
144 * near the overflow threshold
145 * (21) Same as (19), but multiplied by a constant
146 * near the underflow threshold
147 *
148 * Arguments
149 * ==========
150 *
151 * NSIZES (input) INTEGER
152 * The number of sizes of matrices to use. If it is zero,
153 * ZDRVEV does nothing. It must be at least zero.
154 *
155 * NN (input) INTEGER array, dimension (NSIZES)
156 * An array containing the sizes to be used for the matrices.
157 * Zero values will be skipped. The values must be at least
158 * zero.
159 *
160 * NTYPES (input) INTEGER
161 * The number of elements in DOTYPE. If it is zero, ZDRVEV
162 * does nothing. It must be at least zero. If it is MAXTYP+1
163 * and NSIZES is 1, then an additional type, MAXTYP+1 is
164 * defined, which is to use whatever matrix is in A. This
165 * is only useful if DOTYPE(1:MAXTYP) is .FALSE. and
166 * DOTYPE(MAXTYP+1) is .TRUE. .
167 *
168 * DOTYPE (input) LOGICAL array, dimension (NTYPES)
169 * If DOTYPE(j) is .TRUE., then for each size in NN a
170 * matrix of that size and of type j will be generated.
171 * If NTYPES is smaller than the maximum number of types
172 * defined (PARAMETER MAXTYP), then types NTYPES+1 through
173 * MAXTYP will not be generated. If NTYPES is larger
174 * than MAXTYP, DOTYPE(MAXTYP+1) through DOTYPE(NTYPES)
175 * will be ignored.
176 *
177 * ISEED (input/output) INTEGER array, dimension (4)
178 * On entry ISEED specifies the seed of the random number
179 * generator. The array elements should be between 0 and 4095;
180 * if not they will be reduced mod 4096. Also, ISEED(4) must
181 * be odd. The random number generator uses a linear
182 * congruential sequence limited to small integers, and so
183 * should produce machine independent random numbers. The
184 * values of ISEED are changed on exit, and can be used in the
185 * next call to ZDRVEV to continue the same random number
186 * sequence.
187 *
188 * THRESH (input) DOUBLE PRECISION
189 * A test will count as "failed" if the "error", computed as
190 * described above, exceeds THRESH. Note that the error
191 * is scaled to be O(1), so THRESH should be a reasonably
192 * small multiple of 1, e.g., 10 or 100. In particular,
193 * it should not depend on the precision (single vs. double)
194 * or the size of the matrix. It must be at least zero.
195 *
196 * NOUNIT (input) INTEGER
197 * The FORTRAN unit number for printing out error messages
198 * (e.g., if a routine returns INFO not equal to 0.)
199 *
200 * A (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
201 * Used to hold the matrix whose eigenvalues are to be
202 * computed. On exit, A contains the last matrix actually used.
203 *
204 * LDA (input) INTEGER
205 * The leading dimension of A, and H. LDA must be at
206 * least 1 and at least max(NN).
207 *
208 * H (workspace) COMPLEX*16 array, dimension (LDA, max(NN))
209 * Another copy of the test matrix A, modified by ZGEEV.
210 *
211 * W (workspace) COMPLEX*16 array, dimension (max(NN))
212 * The eigenvalues of A. On exit, W are the eigenvalues of
213 * the matrix in A.
214 *
215 * W1 (workspace) COMPLEX*16 array, dimension (max(NN))
216 * Like W, this array contains the eigenvalues of A,
217 * but those computed when ZGEEV only computes a partial
218 * eigendecomposition, i.e. not the eigenvalues and left
219 * and right eigenvectors.
220 *
221 * VL (workspace) COMPLEX*16 array, dimension (LDVL, max(NN))
222 * VL holds the computed left eigenvectors.
223 *
224 * LDVL (input) INTEGER
225 * Leading dimension of VL. Must be at least max(1,max(NN)).
226 *
227 * VR (workspace) COMPLEX*16 array, dimension (LDVR, max(NN))
228 * VR holds the computed right eigenvectors.
229 *
230 * LDVR (input) INTEGER
231 * Leading dimension of VR. Must be at least max(1,max(NN)).
232 *
233 * LRE (workspace) COMPLEX*16 array, dimension (LDLRE, max(NN))
234 * LRE holds the computed right or left eigenvectors.
235 *
236 * LDLRE (input) INTEGER
237 * Leading dimension of LRE. Must be at least max(1,max(NN)).
238 *
239 * RESULT (output) DOUBLE PRECISION array, dimension (7)
240 * The values computed by the seven tests described above.
241 * The values are currently limited to 1/ulp, to avoid
242 * overflow.
243 *
244 * WORK (workspace) COMPLEX*16 array, dimension (NWORK)
245 *
246 * NWORK (input) INTEGER
247 * The number of entries in WORK. This must be at least
248 * 5*NN(j)+2*NN(j)**2 for all j.
249 *
250 * RWORK (workspace) DOUBLE PRECISION array, dimension (2*max(NN))
251 *
252 * IWORK (workspace) INTEGER array, dimension (max(NN))
253 *
254 * INFO (output) INTEGER
255 * If 0, then everything ran OK.
256 * -1: NSIZES < 0
257 * -2: Some NN(j) < 0
258 * -3: NTYPES < 0
259 * -6: THRESH < 0
260 * -9: LDA < 1 or LDA < NMAX, where NMAX is max( NN(j) ).
261 * -14: LDVL < 1 or LDVL < NMAX, where NMAX is max( NN(j) ).
262 * -16: LDVR < 1 or LDVR < NMAX, where NMAX is max( NN(j) ).
263 * -18: LDLRE < 1 or LDLRE < NMAX, where NMAX is max( NN(j) ).
264 * -21: NWORK too small.
265 * If ZLATMR, CLATMS, CLATME or ZGEEV returns an error code,
266 * the absolute value of it is returned.
267 *
268 *-----------------------------------------------------------------------
269 *
270 * Some Local Variables and Parameters:
271 * ---- ----- --------- --- ----------
272 *
273 * ZERO, ONE Real 0 and 1.
274 * MAXTYP The number of types defined.
275 * NMAX Largest value in NN.
276 * NERRS The number of tests which have exceeded THRESH
277 * COND, CONDS,
278 * IMODE Values to be passed to the matrix generators.
279 * ANORM Norm of A; passed to matrix generators.
280 *
281 * OVFL, UNFL Overflow and underflow thresholds.
282 * ULP, ULPINV Finest relative precision and its inverse.
283 * RTULP, RTULPI Square roots of the previous 4 values.
284 *
285 * The following four arrays decode JTYPE:
286 * KTYPE(j) The general type (1-10) for type "j".
287 * KMODE(j) The MODE value to be passed to the matrix
288 * generator for type "j".
289 * KMAGN(j) The order of magnitude ( O(1),
290 * O(overflow^(1/2) ), O(underflow^(1/2) )
291 * KCONDS(j) Selectw whether CONDS is to be 1 or
292 * 1/sqrt(ulp). (0 means irrelevant.)
293 *
294 * =====================================================================
295 *
296 * .. Parameters ..
297 COMPLEX*16 CZERO
298 PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ) )
299 COMPLEX*16 CONE
300 PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
301 DOUBLE PRECISION ZERO, ONE
302 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
303 DOUBLE PRECISION TWO
304 PARAMETER ( TWO = 2.0D+0 )
305 INTEGER MAXTYP
306 PARAMETER ( MAXTYP = 21 )
307 * ..
308 * .. Local Scalars ..
309 LOGICAL BADNN
310 CHARACTER*3 PATH
311 INTEGER IINFO, IMODE, ITYPE, IWK, J, JCOL, JJ, JSIZE,
312 $ JTYPE, MTYPES, N, NERRS, NFAIL, NMAX, NNWORK,
313 $ NTEST, NTESTF, NTESTT
314 DOUBLE PRECISION ANORM, COND, CONDS, OVFL, RTULP, RTULPI, TNRM,
315 $ ULP, ULPINV, UNFL, VMX, VRMX, VTST
316 * ..
317 * .. Local Arrays ..
318 INTEGER IDUMMA( 1 ), IOLDSD( 4 ), KCONDS( MAXTYP ),
319 $ KMAGN( MAXTYP ), KMODE( MAXTYP ),
320 $ KTYPE( MAXTYP )
321 DOUBLE PRECISION RES( 2 )
322 COMPLEX*16 DUM( 1 )
323 * ..
324 * .. External Functions ..
325 DOUBLE PRECISION DLAMCH, DZNRM2
326 EXTERNAL DLAMCH, DZNRM2
327 * ..
328 * .. External Subroutines ..
329 EXTERNAL DLABAD, DLASUM, XERBLA, ZGEEV, ZGET22, ZLACPY,
330 $ ZLASET, ZLATME, ZLATMR, ZLATMS
331 * ..
332 * .. Intrinsic Functions ..
333 INTRINSIC ABS, DBLE, DCMPLX, DIMAG, MAX, MIN, SQRT
334 * ..
335 * .. Data statements ..
336 DATA KTYPE / 1, 2, 3, 5*4, 4*6, 6*6, 3*9 /
337 DATA KMAGN / 3*1, 1, 1, 1, 2, 3, 4*1, 1, 1, 1, 1, 2,
338 $ 3, 1, 2, 3 /
339 DATA KMODE / 3*0, 4, 3, 1, 4, 4, 4, 3, 1, 5, 4, 3,
340 $ 1, 5, 5, 5, 4, 3, 1 /
341 DATA KCONDS / 3*0, 5*0, 4*1, 6*2, 3*0 /
342 * ..
343 * .. Executable Statements ..
344 *
345 PATH( 1: 1 ) = 'Zomplex precision'
346 PATH( 2: 3 ) = 'EV'
347 *
348 * Check for errors
349 *
350 NTESTT = 0
351 NTESTF = 0
352 INFO = 0
353 *
354 * Important constants
355 *
356 BADNN = .FALSE.
357 NMAX = 0
358 DO 10 J = 1, NSIZES
359 NMAX = MAX( NMAX, NN( J ) )
360 IF( NN( J ).LT.0 )
361 $ BADNN = .TRUE.
362 10 CONTINUE
363 *
364 * Check for errors
365 *
366 IF( NSIZES.LT.0 ) THEN
367 INFO = -1
368 ELSE IF( BADNN ) THEN
369 INFO = -2
370 ELSE IF( NTYPES.LT.0 ) THEN
371 INFO = -3
372 ELSE IF( THRESH.LT.ZERO ) THEN
373 INFO = -6
374 ELSE IF( NOUNIT.LE.0 ) THEN
375 INFO = -7
376 ELSE IF( LDA.LT.1 .OR. LDA.LT.NMAX ) THEN
377 INFO = -9
378 ELSE IF( LDVL.LT.1 .OR. LDVL.LT.NMAX ) THEN
379 INFO = -14
380 ELSE IF( LDVR.LT.1 .OR. LDVR.LT.NMAX ) THEN
381 INFO = -16
382 ELSE IF( LDLRE.LT.1 .OR. LDLRE.LT.NMAX ) THEN
383 INFO = -28
384 ELSE IF( 5*NMAX+2*NMAX**2.GT.NWORK ) THEN
385 INFO = -21
386 END IF
387 *
388 IF( INFO.NE.0 ) THEN
389 CALL XERBLA( 'ZDRVEV', -INFO )
390 RETURN
391 END IF
392 *
393 * Quick return if nothing to do
394 *
395 IF( NSIZES.EQ.0 .OR. NTYPES.EQ.0 )
396 $ RETURN
397 *
398 * More Important constants
399 *
400 UNFL = DLAMCH( 'Safe minimum' )
401 OVFL = ONE / UNFL
402 CALL DLABAD( UNFL, OVFL )
403 ULP = DLAMCH( 'Precision' )
404 ULPINV = ONE / ULP
405 RTULP = SQRT( ULP )
406 RTULPI = ONE / RTULP
407 *
408 * Loop over sizes, types
409 *
410 NERRS = 0
411 *
412 DO 270 JSIZE = 1, NSIZES
413 N = NN( JSIZE )
414 IF( NSIZES.NE.1 ) THEN
415 MTYPES = MIN( MAXTYP, NTYPES )
416 ELSE
417 MTYPES = MIN( MAXTYP+1, NTYPES )
418 END IF
419 *
420 DO 260 JTYPE = 1, MTYPES
421 IF( .NOT.DOTYPE( JTYPE ) )
422 $ GO TO 260
423 *
424 * Save ISEED in case of an error.
425 *
426 DO 20 J = 1, 4
427 IOLDSD( J ) = ISEED( J )
428 20 CONTINUE
429 *
430 * Compute "A"
431 *
432 * Control parameters:
433 *
434 * KMAGN KCONDS KMODE KTYPE
435 * =1 O(1) 1 clustered 1 zero
436 * =2 large large clustered 2 identity
437 * =3 small exponential Jordan
438 * =4 arithmetic diagonal, (w/ eigenvalues)
439 * =5 random log symmetric, w/ eigenvalues
440 * =6 random general, w/ eigenvalues
441 * =7 random diagonal
442 * =8 random symmetric
443 * =9 random general
444 * =10 random triangular
445 *
446 IF( MTYPES.GT.MAXTYP )
447 $ GO TO 90
448 *
449 ITYPE = KTYPE( JTYPE )
450 IMODE = KMODE( JTYPE )
451 *
452 * Compute norm
453 *
454 GO TO ( 30, 40, 50 )KMAGN( JTYPE )
455 *
456 30 CONTINUE
457 ANORM = ONE
458 GO TO 60
459 *
460 40 CONTINUE
461 ANORM = OVFL*ULP
462 GO TO 60
463 *
464 50 CONTINUE
465 ANORM = UNFL*ULPINV
466 GO TO 60
467 *
468 60 CONTINUE
469 *
470 CALL ZLASET( 'Full', LDA, N, CZERO, CZERO, A, LDA )
471 IINFO = 0
472 COND = ULPINV
473 *
474 * Special Matrices -- Identity & Jordan block
475 *
476 * Zero
477 *
478 IF( ITYPE.EQ.1 ) THEN
479 IINFO = 0
480 *
481 ELSE IF( ITYPE.EQ.2 ) THEN
482 *
483 * Identity
484 *
485 DO 70 JCOL = 1, N
486 A( JCOL, JCOL ) = DCMPLX( ANORM )
487 70 CONTINUE
488 *
489 ELSE IF( ITYPE.EQ.3 ) THEN
490 *
491 * Jordan Block
492 *
493 DO 80 JCOL = 1, N
494 A( JCOL, JCOL ) = DCMPLX( ANORM )
495 IF( JCOL.GT.1 )
496 $ A( JCOL, JCOL-1 ) = CONE
497 80 CONTINUE
498 *
499 ELSE IF( ITYPE.EQ.4 ) THEN
500 *
501 * Diagonal Matrix, [Eigen]values Specified
502 *
503 CALL ZLATMS( N, N, 'S', ISEED, 'H', RWORK, IMODE, COND,
504 $ ANORM, 0, 0, 'N', A, LDA, WORK( N+1 ),
505 $ IINFO )
506 *
507 ELSE IF( ITYPE.EQ.5 ) THEN
508 *
509 * Hermitian, eigenvalues specified
510 *
511 CALL ZLATMS( N, N, 'S', ISEED, 'H', RWORK, IMODE, COND,
512 $ ANORM, N, N, 'N', A, LDA, WORK( N+1 ),
513 $ IINFO )
514 *
515 ELSE IF( ITYPE.EQ.6 ) THEN
516 *
517 * General, eigenvalues specified
518 *
519 IF( KCONDS( JTYPE ).EQ.1 ) THEN
520 CONDS = ONE
521 ELSE IF( KCONDS( JTYPE ).EQ.2 ) THEN
522 CONDS = RTULPI
523 ELSE
524 CONDS = ZERO
525 END IF
526 *
527 CALL ZLATME( N, 'D', ISEED, WORK, IMODE, COND, CONE, ' ',
528 $ 'T', 'T', 'T', RWORK, 4, CONDS, N, N, ANORM,
529 $ A, LDA, WORK( 2*N+1 ), IINFO )
530 *
531 ELSE IF( ITYPE.EQ.7 ) THEN
532 *
533 * Diagonal, random eigenvalues
534 *
535 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
536 $ 'T', 'N', WORK( N+1 ), 1, ONE,
537 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, 0, 0,
538 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
539 *
540 ELSE IF( ITYPE.EQ.8 ) THEN
541 *
542 * Symmetric, random eigenvalues
543 *
544 CALL ZLATMR( N, N, 'D', ISEED, 'H', WORK, 6, ONE, CONE,
545 $ 'T', 'N', WORK( N+1 ), 1, ONE,
546 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, N,
547 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
548 *
549 ELSE IF( ITYPE.EQ.9 ) THEN
550 *
551 * General, random eigenvalues
552 *
553 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
554 $ 'T', 'N', WORK( N+1 ), 1, ONE,
555 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, N,
556 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
557 IF( N.GE.4 ) THEN
558 CALL ZLASET( 'Full', 2, N, CZERO, CZERO, A, LDA )
559 CALL ZLASET( 'Full', N-3, 1, CZERO, CZERO, A( 3, 1 ),
560 $ LDA )
561 CALL ZLASET( 'Full', N-3, 2, CZERO, CZERO,
562 $ A( 3, N-1 ), LDA )
563 CALL ZLASET( 'Full', 1, N, CZERO, CZERO, A( N, 1 ),
564 $ LDA )
565 END IF
566 *
567 ELSE IF( ITYPE.EQ.10 ) THEN
568 *
569 * Triangular, random eigenvalues
570 *
571 CALL ZLATMR( N, N, 'D', ISEED, 'N', WORK, 6, ONE, CONE,
572 $ 'T', 'N', WORK( N+1 ), 1, ONE,
573 $ WORK( 2*N+1 ), 1, ONE, 'N', IDUMMA, N, 0,
574 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
575 *
576 ELSE
577 *
578 IINFO = 1
579 END IF
580 *
581 IF( IINFO.NE.0 ) THEN
582 WRITE( NOUNIT, FMT = 9993 )'Generator', IINFO, N, JTYPE,
583 $ IOLDSD
584 INFO = ABS( IINFO )
585 RETURN
586 END IF
587 *
588 90 CONTINUE
589 *
590 * Test for minimal and generous workspace
591 *
592 DO 250 IWK = 1, 2
593 IF( IWK.EQ.1 ) THEN
594 NNWORK = 2*N
595 ELSE
596 NNWORK = 5*N + 2*N**2
597 END IF
598 NNWORK = MAX( NNWORK, 1 )
599 *
600 * Initialize RESULT
601 *
602 DO 100 J = 1, 7
603 RESULT( J ) = -ONE
604 100 CONTINUE
605 *
606 * Compute eigenvalues and eigenvectors, and test them
607 *
608 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
609 CALL ZGEEV( 'V', 'V', N, H, LDA, W, VL, LDVL, VR, LDVR,
610 $ WORK, NNWORK, RWORK, IINFO )
611 IF( IINFO.NE.0 ) THEN
612 RESULT( 1 ) = ULPINV
613 WRITE( NOUNIT, FMT = 9993 )'ZGEEV1', IINFO, N, JTYPE,
614 $ IOLDSD
615 INFO = ABS( IINFO )
616 GO TO 220
617 END IF
618 *
619 * Do Test (1)
620 *
621 CALL ZGET22( 'N', 'N', 'N', N, A, LDA, VR, LDVR, W, WORK,
622 $ RWORK, RES )
623 RESULT( 1 ) = RES( 1 )
624 *
625 * Do Test (2)
626 *
627 CALL ZGET22( 'C', 'N', 'C', N, A, LDA, VL, LDVL, W, WORK,
628 $ RWORK, RES )
629 RESULT( 2 ) = RES( 1 )
630 *
631 * Do Test (3)
632 *
633 DO 120 J = 1, N
634 TNRM = DZNRM2( N, VR( 1, J ), 1 )
635 RESULT( 3 ) = MAX( RESULT( 3 ),
636 $ MIN( ULPINV, ABS( TNRM-ONE ) / ULP ) )
637 VMX = ZERO
638 VRMX = ZERO
639 DO 110 JJ = 1, N
640 VTST = ABS( VR( JJ, J ) )
641 IF( VTST.GT.VMX )
642 $ VMX = VTST
643 IF( DIMAG( VR( JJ, J ) ).EQ.ZERO .AND.
644 $ ABS( DBLE( VR( JJ, J ) ) ).GT.VRMX )
645 $ VRMX = ABS( DBLE( VR( JJ, J ) ) )
646 110 CONTINUE
647 IF( VRMX / VMX.LT.ONE-TWO*ULP )
648 $ RESULT( 3 ) = ULPINV
649 120 CONTINUE
650 *
651 * Do Test (4)
652 *
653 DO 140 J = 1, N
654 TNRM = DZNRM2( N, VL( 1, J ), 1 )
655 RESULT( 4 ) = MAX( RESULT( 4 ),
656 $ MIN( ULPINV, ABS( TNRM-ONE ) / ULP ) )
657 VMX = ZERO
658 VRMX = ZERO
659 DO 130 JJ = 1, N
660 VTST = ABS( VL( JJ, J ) )
661 IF( VTST.GT.VMX )
662 $ VMX = VTST
663 IF( DIMAG( VL( JJ, J ) ).EQ.ZERO .AND.
664 $ ABS( DBLE( VL( JJ, J ) ) ).GT.VRMX )
665 $ VRMX = ABS( DBLE( VL( JJ, J ) ) )
666 130 CONTINUE
667 IF( VRMX / VMX.LT.ONE-TWO*ULP )
668 $ RESULT( 4 ) = ULPINV
669 140 CONTINUE
670 *
671 * Compute eigenvalues only, and test them
672 *
673 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
674 CALL ZGEEV( 'N', 'N', N, H, LDA, W1, DUM, 1, DUM, 1,
675 $ WORK, NNWORK, RWORK, IINFO )
676 IF( IINFO.NE.0 ) THEN
677 RESULT( 1 ) = ULPINV
678 WRITE( NOUNIT, FMT = 9993 )'ZGEEV2', IINFO, N, JTYPE,
679 $ IOLDSD
680 INFO = ABS( IINFO )
681 GO TO 220
682 END IF
683 *
684 * Do Test (5)
685 *
686 DO 150 J = 1, N
687 IF( W( J ).NE.W1( J ) )
688 $ RESULT( 5 ) = ULPINV
689 150 CONTINUE
690 *
691 * Compute eigenvalues and right eigenvectors, and test them
692 *
693 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
694 CALL ZGEEV( 'N', 'V', N, H, LDA, W1, DUM, 1, LRE, LDLRE,
695 $ WORK, NNWORK, RWORK, IINFO )
696 IF( IINFO.NE.0 ) THEN
697 RESULT( 1 ) = ULPINV
698 WRITE( NOUNIT, FMT = 9993 )'ZGEEV3', IINFO, N, JTYPE,
699 $ IOLDSD
700 INFO = ABS( IINFO )
701 GO TO 220
702 END IF
703 *
704 * Do Test (5) again
705 *
706 DO 160 J = 1, N
707 IF( W( J ).NE.W1( J ) )
708 $ RESULT( 5 ) = ULPINV
709 160 CONTINUE
710 *
711 * Do Test (6)
712 *
713 DO 180 J = 1, N
714 DO 170 JJ = 1, N
715 IF( VR( J, JJ ).NE.LRE( J, JJ ) )
716 $ RESULT( 6 ) = ULPINV
717 170 CONTINUE
718 180 CONTINUE
719 *
720 * Compute eigenvalues and left eigenvectors, and test them
721 *
722 CALL ZLACPY( 'F', N, N, A, LDA, H, LDA )
723 CALL ZGEEV( 'V', 'N', N, H, LDA, W1, LRE, LDLRE, DUM, 1,
724 $ WORK, NNWORK, RWORK, IINFO )
725 IF( IINFO.NE.0 ) THEN
726 RESULT( 1 ) = ULPINV
727 WRITE( NOUNIT, FMT = 9993 )'ZGEEV4', IINFO, N, JTYPE,
728 $ IOLDSD
729 INFO = ABS( IINFO )
730 GO TO 220
731 END IF
732 *
733 * Do Test (5) again
734 *
735 DO 190 J = 1, N
736 IF( W( J ).NE.W1( J ) )
737 $ RESULT( 5 ) = ULPINV
738 190 CONTINUE
739 *
740 * Do Test (7)
741 *
742 DO 210 J = 1, N
743 DO 200 JJ = 1, N
744 IF( VL( J, JJ ).NE.LRE( J, JJ ) )
745 $ RESULT( 7 ) = ULPINV
746 200 CONTINUE
747 210 CONTINUE
748 *
749 * End of Loop -- Check for RESULT(j) > THRESH
750 *
751 220 CONTINUE
752 *
753 NTEST = 0
754 NFAIL = 0
755 DO 230 J = 1, 7
756 IF( RESULT( J ).GE.ZERO )
757 $ NTEST = NTEST + 1
758 IF( RESULT( J ).GE.THRESH )
759 $ NFAIL = NFAIL + 1
760 230 CONTINUE
761 *
762 IF( NFAIL.GT.0 )
763 $ NTESTF = NTESTF + 1
764 IF( NTESTF.EQ.1 ) THEN
765 WRITE( NOUNIT, FMT = 9999 )PATH
766 WRITE( NOUNIT, FMT = 9998 )
767 WRITE( NOUNIT, FMT = 9997 )
768 WRITE( NOUNIT, FMT = 9996 )
769 WRITE( NOUNIT, FMT = 9995 )THRESH
770 NTESTF = 2
771 END IF
772 *
773 DO 240 J = 1, 7
774 IF( RESULT( J ).GE.THRESH ) THEN
775 WRITE( NOUNIT, FMT = 9994 )N, IWK, IOLDSD, JTYPE,
776 $ J, RESULT( J )
777 END IF
778 240 CONTINUE
779 *
780 NERRS = NERRS + NFAIL
781 NTESTT = NTESTT + NTEST
782 *
783 250 CONTINUE
784 260 CONTINUE
785 270 CONTINUE
786 *
787 * Summary
788 *
789 CALL DLASUM( PATH, NOUNIT, NERRS, NTESTT )
790 *
791 9999 FORMAT( / 1X, A3, ' -- Complex Eigenvalue-Eigenvector ',
792 $ 'Decomposition Driver', /
793 $ ' Matrix types (see ZDRVEV for details): ' )
794 *
795 9998 FORMAT( / ' Special Matrices:', / ' 1=Zero matrix. ',
796 $ ' ', ' 5=Diagonal: geometr. spaced entries.',
797 $ / ' 2=Identity matrix. ', ' 6=Diagona',
798 $ 'l: clustered entries.', / ' 3=Transposed Jordan block. ',
799 $ ' ', ' 7=Diagonal: large, evenly spaced.', / ' ',
800 $ '4=Diagonal: evenly spaced entries. ', ' 8=Diagonal: s',
801 $ 'mall, evenly spaced.' )
802 9997 FORMAT( ' Dense, Non-Symmetric Matrices:', / ' 9=Well-cond., ev',
803 $ 'enly spaced eigenvals.', ' 14=Ill-cond., geomet. spaced e',
804 $ 'igenals.', / ' 10=Well-cond., geom. spaced eigenvals. ',
805 $ ' 15=Ill-conditioned, clustered e.vals.', / ' 11=Well-cond',
806 $ 'itioned, clustered e.vals. ', ' 16=Ill-cond., random comp',
807 $ 'lex ', A6, / ' 12=Well-cond., random complex ', A6, ' ',
808 $ ' 17=Ill-cond., large rand. complx ', A4, / ' 13=Ill-condi',
809 $ 'tioned, evenly spaced. ', ' 18=Ill-cond., small rand.',
810 $ ' complx ', A4 )
811 9996 FORMAT( ' 19=Matrix with random O(1) entries. ', ' 21=Matrix ',
812 $ 'with small random entries.', / ' 20=Matrix with large ran',
813 $ 'dom entries. ', / )
814 9995 FORMAT( ' Tests performed with test threshold =', F8.2,
815 $ / / ' 1 = | A VR - VR W | / ( n |A| ulp ) ',
816 $ / ' 2 = | conj-trans(A) VL - VL conj-trans(W) | /',
817 $ ' ( n |A| ulp ) ', / ' 3 = | |VR(i)| - 1 | / ulp ',
818 $ / ' 4 = | |VL(i)| - 1 | / ulp ',
819 $ / ' 5 = 0 if W same no matter if VR or VL computed,',
820 $ ' 1/ulp otherwise', /
821 $ ' 6 = 0 if VR same no matter if VL computed,',
822 $ ' 1/ulp otherwise', /
823 $ ' 7 = 0 if VL same no matter if VR computed,',
824 $ ' 1/ulp otherwise', / )
825 9994 FORMAT( ' N=', I5, ', IWK=', I2, ', seed=', 4( I4, ',' ),
826 $ ' type ', I2, ', test(', I2, ')=', G10.3 )
827 9993 FORMAT( ' ZDRVEV: ', A, ' returned INFO=', I6, '.', / 9X, 'N=',
828 $ I6, ', JTYPE=', I6, ', ISEED=(', 3( I5, ',' ), I5, ')' )
829 *
830 RETURN
831 *
832 * End of ZDRVEV
833 *
834 END