1       SUBROUTINE DSYT21( ITYPE, UPLO, N, KBAND, A, LDA, D, E, U, LDU, V,
  2      $                   LDV, TAU, WORK, RESULT )
  3 *
  4 *  -- LAPACK test routine (version 3.1) --
  5 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       CHARACTER          UPLO
 10       INTEGER            ITYPE, KBAND, LDA, LDU, LDV, N
 11 *     ..
 12 *     .. Array Arguments ..
 13       DOUBLE PRECISION   A( LDA, * ), D( * ), E( * ), RESULT2 ),
 14      $                   TAU( * ), U( LDU, * ), V( LDV, * ), WORK( * )
 15 *     ..
 16 *
 17 *  Purpose
 18 *  =======
 19 *
 20 *  DSYT21 generally checks a decomposition of the form
 21 *
 22 *     A = U S U'
 23 *
 24 *  where ' means transpose, A is symmetric, U is orthogonal, and S is
 25 *  diagonal (if KBAND=0) or symmetric tridiagonal (if KBAND=1).
 26 *
 27 *  If ITYPE=1, then U is represented as a dense matrix; otherwise U is
 28 *  expressed as a product of Householder transformations, whose vectors
 29 *  are stored in the array "V" and whose scaling constants are in "TAU".
 30 *  We shall use the letter "V" to refer to the product of Householder
 31 *  transformations (which should be equal to U).
 32 *
 33 *  Specifically, if ITYPE=1, then:
 34 *
 35 *     RESULT(1) = | A - U S U' | / ( |A| n ulp ) *and*
 36 *     RESULT(2) = | I - UU' | / ( n ulp )
 37 *
 38 *  If ITYPE=2, then:
 39 *
 40 *     RESULT(1) = | A - V S V' | / ( |A| n ulp )
 41 *
 42 *  If ITYPE=3, then:
 43 *
 44 *     RESULT(1) = | I - VU' | / ( n ulp )
 45 *
 46 *  For ITYPE > 1, the transformation U is expressed as a product
 47 *  V = H(1)...H(n-2),  where H(j) = I  -  tau(j) v(j) v(j)' and each
 48 *  vector v(j) has its first j elements 0 and the remaining n-j elements
 49 *  stored in V(j+1:n,j).
 50 *
 51 *  Arguments
 52 *  =========
 53 *
 54 *  ITYPE   (input) INTEGER
 55 *          Specifies the type of tests to be performed.
 56 *          1: U expressed as a dense orthogonal matrix:
 57 *             RESULT(1) = | A - U S U' | / ( |A| n ulp )   *and*
 58 *             RESULT(2) = | I - UU' | / ( n ulp )
 59 *
 60 *          2: U expressed as a product V of Housholder transformations:
 61 *             RESULT(1) = | A - V S V' | / ( |A| n ulp )
 62 *
 63 *          3: U expressed both as a dense orthogonal matrix and
 64 *             as a product of Housholder transformations:
 65 *             RESULT(1) = | I - VU' | / ( n ulp )
 66 *
 67 *  UPLO    (input) CHARACTER
 68 *          If UPLO='U', the upper triangle of A and V will be used and
 69 *          the (strictly) lower triangle will not be referenced.
 70 *          If UPLO='L', the lower triangle of A and V will be used and
 71 *          the (strictly) upper triangle will not be referenced.
 72 *
 73 *  N       (input) INTEGER
 74 *          The size of the matrix.  If it is zero, DSYT21 does nothing.
 75 *          It must be at least zero.
 76 *
 77 *  KBAND   (input) INTEGER
 78 *          The bandwidth of the matrix.  It may only be zero or one.
 79 *          If zero, then S is diagonal, and E is not referenced.  If
 80 *          one, then S is symmetric tri-diagonal.
 81 *
 82 *  A       (input) DOUBLE PRECISION array, dimension (LDA, N)
 83 *          The original (unfactored) matrix.  It is assumed to be
 84 *          symmetric, and only the upper (UPLO='U') or only the lower
 85 *          (UPLO='L') will be referenced.
 86 *
 87 *  LDA     (input) INTEGER
 88 *          The leading dimension of A.  It must be at least 1
 89 *          and at least N.
 90 *
 91 *  D       (input) DOUBLE PRECISION array, dimension (N)
 92 *          The diagonal of the (symmetric tri-) diagonal matrix.
 93 *
 94 *  E       (input) DOUBLE PRECISION array, dimension (N-1)
 95 *          The off-diagonal of the (symmetric tri-) diagonal matrix.
 96 *          E(1) is the (1,2) and (2,1) element, E(2) is the (2,3) and
 97 *          (3,2) element, etc.
 98 *          Not referenced if KBAND=0.
 99 *
100 *  U       (input) DOUBLE PRECISION array, dimension (LDU, N)
101 *          If ITYPE=1 or 3, this contains the orthogonal matrix in
102 *          the decomposition, expressed as a dense matrix.  If ITYPE=2,
103 *          then it is not referenced.
104 *
105 *  LDU     (input) INTEGER
106 *          The leading dimension of U.  LDU must be at least N and
107 *          at least 1.
108 *
109 *  V       (input) DOUBLE PRECISION array, dimension (LDV, N)
110 *          If ITYPE=2 or 3, the columns of this array contain the
111 *          Householder vectors used to describe the orthogonal matrix
112 *          in the decomposition.  If UPLO='L', then the vectors are in
113 *          the lower triangle, if UPLO='U', then in the upper
114 *          triangle.
115 *          *NOTE* If ITYPE=2 or 3, V is modified and restored.  The
116 *          subdiagonal (if UPLO='L') or the superdiagonal (if UPLO='U')
117 *          is set to one, and later reset to its original value, during
118 *          the course of the calculation.
119 *          If ITYPE=1, then it is neither referenced nor modified.
120 *
121 *  LDV     (input) INTEGER
122 *          The leading dimension of V.  LDV must be at least N and
123 *          at least 1.
124 *
125 *  TAU     (input) DOUBLE PRECISION array, dimension (N)
126 *          If ITYPE >= 2, then TAU(j) is the scalar factor of
127 *          v(j) v(j)' in the Householder transformation H(j) of
128 *          the product  U = H(1)...H(n-2)
129 *          If ITYPE < 2, then TAU is not referenced.
130 *
131 *  WORK    (workspace) DOUBLE PRECISION array, dimension (2*N**2)
132 *
133 *  RESULT  (output) DOUBLE PRECISION array, dimension (2)
134 *          The values computed by the two tests described above.  The
135 *          values are currently limited to 1/ulp, to avoid overflow.
136 *          RESULT(1) is always modified.  RESULT(2) is modified only
137 *          if ITYPE=1.
138 *
139 *  =====================================================================
140 *
141 *     .. Parameters ..
142       DOUBLE PRECISION   ZERO, ONE, TEN
143       PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0, TEN = 10.0D0 )
144 *     ..
145 *     .. Local Scalars ..
146       LOGICAL            LOWER
147       CHARACTER          CUPLO
148       INTEGER            IINFO, J, JCOL, JR, JROW
149       DOUBLE PRECISION   ANORM, ULP, UNFL, VSAVE, WNORM
150 *     ..
151 *     .. External Functions ..
152       LOGICAL            LSAME
153       DOUBLE PRECISION   DLAMCH, DLANGE, DLANSY
154       EXTERNAL           LSAME, DLAMCH, DLANGE, DLANSY
155 *     ..
156 *     .. External Subroutines ..
157       EXTERNAL           DGEMM, DLACPY, DLARFY, DLASET, DORM2L, DORM2R,
158      $                   DSYR, DSYR2
159 *     ..
160 *     .. Intrinsic Functions ..
161       INTRINSIC          DBLEMAXMIN
162 *     ..
163 *     .. Executable Statements ..
164 *
165       RESULT1 ) = ZERO
166       IF( ITYPE.EQ.1 )
167      $   RESULT2 ) = ZERO
168       IF( N.LE.0 )
169      $   RETURN
170 *
171       IF( LSAME( UPLO, 'U' ) ) THEN
172          LOWER = .FALSE.
173          CUPLO = 'U'
174       ELSE
175          LOWER = .TRUE.
176          CUPLO = 'L'
177       END IF
178 *
179       UNFL = DLAMCH( 'Safe minimum' )
180       ULP = DLAMCH( 'Epsilon' )*DLAMCH( 'Base' )
181 *
182 *     Some Error Checks
183 *
184       IF( ITYPE.LT.1 .OR. ITYPE.GT.3 ) THEN
185          RESULT1 ) = TEN / ULP
186          RETURN
187       END IF
188 *
189 *     Do Test 1
190 *
191 *     Norm of A:
192 *
193       IF( ITYPE.EQ.3 ) THEN
194          ANORM = ONE
195       ELSE
196          ANORM = MAX( DLANSY( '1', CUPLO, N, A, LDA, WORK ), UNFL )
197       END IF
198 *
199 *     Compute error matrix:
200 *
201       IF( ITYPE.EQ.1 ) THEN
202 *
203 *        ITYPE=1: error = A - U S U'
204 *
205          CALL DLASET( 'Full', N, N, ZERO, ZERO, WORK, N )
206          CALL DLACPY( CUPLO, N, N, A, LDA, WORK, N )
207 *
208          DO 10 J = 1, N
209             CALL DSYR( CUPLO, N, -D( J ), U( 1, J ), 1, WORK, N )
210    10    CONTINUE
211 *
212          IF( N.GT.1 .AND. KBAND.EQ.1 ) THEN
213             DO 20 J = 1, N - 1
214                CALL DSYR2( CUPLO, N, -E( J ), U( 1, J ), 1, U( 1, J+1 ),
215      $                     1, WORK, N )
216    20       CONTINUE
217          END IF
218          WNORM = DLANSY( '1', CUPLO, N, WORK, N, WORK( N**2+1 ) )
219 *
220       ELSE IF( ITYPE.EQ.2 ) THEN
221 *
222 *        ITYPE=2: error = V S V' - A
223 *
224          CALL DLASET( 'Full', N, N, ZERO, ZERO, WORK, N )
225 *
226          IF( LOWER ) THEN
227             WORK( N**2 ) = D( N )
228             DO 40 J = N - 11-1
229                IF( KBAND.EQ.1 ) THEN
230                   WORK( ( N+1 )*( J-1 )+2 ) = ( ONE-TAU( J ) )*E( J )
231                   DO 30 JR = J + 2, N
232                      WORK( ( J-1 )*N+JR ) = -TAU( J )*E( J )*V( JR, J )
233    30             CONTINUE
234                END IF
235 *
236                VSAVE = V( J+1, J )
237                V( J+1, J ) = ONE
238                CALL DLARFY( 'L', N-J, V( J+1, J ), 1, TAU( J ),
239      $                      WORK( ( N+1 )*J+1 ), N, WORK( N**2+1 ) )
240                V( J+1, J ) = VSAVE
241                WORK( ( N+1 )*( J-1 )+1 ) = D( J )
242    40       CONTINUE
243          ELSE
244             WORK( 1 ) = D( 1 )
245             DO 60 J = 1, N - 1
246                IF( KBAND.EQ.1 ) THEN
247                   WORK( ( N+1 )*J ) = ( ONE-TAU( J ) )*E( J )
248                   DO 50 JR = 1, J - 1
249                      WORK( J*N+JR ) = -TAU( J )*E( J )*V( JR, J+1 )
250    50             CONTINUE
251                END IF
252 *
253                VSAVE = V( J, J+1 )
254                V( J, J+1 ) = ONE
255                CALL DLARFY( 'U', J, V( 1, J+1 ), 1, TAU( J ), WORK, N,
256      $                      WORK( N**2+1 ) )
257                V( J, J+1 ) = VSAVE
258                WORK( ( N+1 )*J+1 ) = D( J+1 )
259    60       CONTINUE
260          END IF
261 *
262          DO 90 JCOL = 1, N
263             IF( LOWER ) THEN
264                DO 70 JROW = JCOL, N
265                   WORK( JROW+N*( JCOL-1 ) ) = WORK( JROW+N*( JCOL-1 ) )
266      $                - A( JROW, JCOL )
267    70          CONTINUE
268             ELSE
269                DO 80 JROW = 1, JCOL
270                   WORK( JROW+N*( JCOL-1 ) ) = WORK( JROW+N*( JCOL-1 ) )
271      $                - A( JROW, JCOL )
272    80          CONTINUE
273             END IF
274    90    CONTINUE
275          WNORM = DLANSY( '1', CUPLO, N, WORK, N, WORK( N**2+1 ) )
276 *
277       ELSE IF( ITYPE.EQ.3 ) THEN
278 *
279 *        ITYPE=3: error = U V' - I
280 *
281          IF( N.LT.2 )
282      $      RETURN
283          CALL DLACPY( ' ', N, N, U, LDU, WORK, N )
284          IF( LOWER ) THEN
285             CALL DORM2R( 'R''T', N, N-1, N-1, V( 21 ), LDV, TAU,
286      $                   WORK( N+1 ), N, WORK( N**2+1 ), IINFO )
287          ELSE
288             CALL DORM2L( 'R''T', N, N-1, N-1, V( 12 ), LDV, TAU,
289      $                   WORK, N, WORK( N**2+1 ), IINFO )
290          END IF
291          IF( IINFO.NE.0 ) THEN
292             RESULT1 ) = TEN / ULP
293             RETURN
294          END IF
295 *
296          DO 100 J = 1, N
297             WORK( ( N+1 )*( J-1 )+1 ) = WORK( ( N+1 )*( J-1 )+1 ) - ONE
298   100    CONTINUE
299 *
300          WNORM = DLANGE( '1', N, N, WORK, N, WORK( N**2+1 ) )
301       END IF
302 *
303       IF( ANORM.GT.WNORM ) THEN
304          RESULT1 ) = ( WNORM / ANORM ) / ( N*ULP )
305       ELSE
306          IF( ANORM.LT.ONE ) THEN
307             RESULT1 ) = ( MIN( WNORM, N*ANORM ) / ANORM ) / ( N*ULP )
308          ELSE
309             RESULT1 ) = MIN( WNORM / ANORM, DBLE( N ) ) / ( N*ULP )
310          END IF
311       END IF
312 *
313 *     Do Test 2
314 *
315 *     Compute  UU' - I
316 *
317       IF( ITYPE.EQ.1 ) THEN
318          CALL DGEMM( 'N''C', N, N, N, ONE, U, LDU, U, LDU, ZERO, WORK,
319      $               N )
320 *
321          DO 110 J = 1, N
322             WORK( ( N+1 )*( J-1 )+1 ) = WORK( ( N+1 )*( J-1 )+1 ) - ONE
323   110    CONTINUE
324 *
325          RESULT2 ) = MIN( DLANGE( '1', N, N, WORK, N,
326      $                 WORK( N**2+1 ) ), DBLE( N ) ) / ( N*ULP )
327       END IF
328 *
329       RETURN
330 *
331 *     End of DSYT21
332 *
333       END