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