1*> \brief \b SSYTRD 2* 3* =========== DOCUMENTATION =========== 4* 5* Online html documentation available at 6* http://www.netlib.org/lapack/explore-html/ 7* 8*> \htmlonly 9*> Download SSYTRD + dependencies 10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssytrd.f"> 11*> [TGZ]</a> 12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssytrd.f"> 13*> [ZIP]</a> 14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssytrd.f"> 15*> [TXT]</a> 16*> \endhtmlonly 17* 18* Definition: 19* =========== 20* 21* SUBROUTINE SSYTRD( UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO ) 22* 23* .. Scalar Arguments .. 24* CHARACTER UPLO 25* INTEGER INFO, LDA, LWORK, N 26* .. 27* .. Array Arguments .. 28* REAL A( LDA, * ), D( * ), E( * ), TAU( * ), 29* $ WORK( * ) 30* .. 31* 32* 33*> \par Purpose: 34* ============= 35*> 36*> \verbatim 37*> 38*> SSYTRD reduces a real symmetric matrix A to real symmetric 39*> tridiagonal form T by an orthogonal similarity transformation: 40*> Q**T * A * Q = T. 41*> \endverbatim 42* 43* Arguments: 44* ========== 45* 46*> \param[in] UPLO 47*> \verbatim 48*> UPLO is CHARACTER*1 49*> = 'U': Upper triangle of A is stored; 50*> = 'L': Lower triangle of A is stored. 51*> \endverbatim 52*> 53*> \param[in] N 54*> \verbatim 55*> N is INTEGER 56*> The order of the matrix A. N >= 0. 57*> \endverbatim 58*> 59*> \param[in,out] A 60*> \verbatim 61*> A is REAL array, dimension (LDA,N) 62*> On entry, the symmetric matrix A. If UPLO = 'U', the leading 63*> N-by-N upper triangular part of A contains the upper 64*> triangular part of the matrix A, and the strictly lower 65*> triangular part of A is not referenced. If UPLO = 'L', the 66*> leading N-by-N lower triangular part of A contains the lower 67*> triangular part of the matrix A, and the strictly upper 68*> triangular part of A is not referenced. 69*> On exit, if UPLO = 'U', the diagonal and first superdiagonal 70*> of A are overwritten by the corresponding elements of the 71*> tridiagonal matrix T, and the elements above the first 72*> superdiagonal, with the array TAU, represent the orthogonal 73*> matrix Q as a product of elementary reflectors; if UPLO 74*> = 'L', the diagonal and first subdiagonal of A are over- 75*> written by the corresponding elements of the tridiagonal 76*> matrix T, and the elements below the first subdiagonal, with 77*> the array TAU, represent the orthogonal matrix Q as a product 78*> of elementary reflectors. See Further Details. 79*> \endverbatim 80*> 81*> \param[in] LDA 82*> \verbatim 83*> LDA is INTEGER 84*> The leading dimension of the array A. LDA >= max(1,N). 85*> \endverbatim 86*> 87*> \param[out] D 88*> \verbatim 89*> D is REAL array, dimension (N) 90*> The diagonal elements of the tridiagonal matrix T: 91*> D(i) = A(i,i). 92*> \endverbatim 93*> 94*> \param[out] E 95*> \verbatim 96*> E is REAL array, dimension (N-1) 97*> The off-diagonal elements of the tridiagonal matrix T: 98*> E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'. 99*> \endverbatim 100*> 101*> \param[out] TAU 102*> \verbatim 103*> TAU is REAL array, dimension (N-1) 104*> The scalar factors of the elementary reflectors (see Further 105*> Details). 106*> \endverbatim 107*> 108*> \param[out] WORK 109*> \verbatim 110*> WORK is REAL array, dimension (MAX(1,LWORK)) 111*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK. 112*> \endverbatim 113*> 114*> \param[in] LWORK 115*> \verbatim 116*> LWORK is INTEGER 117*> The dimension of the array WORK. LWORK >= 1. 118*> For optimum performance LWORK >= N*NB, where NB is the 119*> optimal blocksize. 120*> 121*> If LWORK = -1, then a workspace query is assumed; the routine 122*> only calculates the optimal size of the WORK array, returns 123*> this value as the first entry of the WORK array, and no error 124*> message related to LWORK is issued by XERBLA. 125*> \endverbatim 126*> 127*> \param[out] INFO 128*> \verbatim 129*> INFO is INTEGER 130*> = 0: successful exit 131*> < 0: if INFO = -i, the i-th argument had an illegal value 132*> \endverbatim 133* 134* Authors: 135* ======== 136* 137*> \author Univ. of Tennessee 138*> \author Univ. of California Berkeley 139*> \author Univ. of Colorado Denver 140*> \author NAG Ltd. 141* 142*> \ingroup realSYcomputational 143* 144*> \par Further Details: 145* ===================== 146*> 147*> \verbatim 148*> 149*> If UPLO = 'U', the matrix Q is represented as a product of elementary 150*> reflectors 151*> 152*> Q = H(n-1) . . . H(2) H(1). 153*> 154*> Each H(i) has the form 155*> 156*> H(i) = I - tau * v * v**T 157*> 158*> where tau is a real scalar, and v is a real vector with 159*> v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in 160*> A(1:i-1,i+1), and tau in TAU(i). 161*> 162*> If UPLO = 'L', the matrix Q is represented as a product of elementary 163*> reflectors 164*> 165*> Q = H(1) H(2) . . . H(n-1). 166*> 167*> Each H(i) has the form 168*> 169*> H(i) = I - tau * v * v**T 170*> 171*> where tau is a real scalar, and v is a real vector with 172*> v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in A(i+2:n,i), 173*> and tau in TAU(i). 174*> 175*> The contents of A on exit are illustrated by the following examples 176*> with n = 5: 177*> 178*> if UPLO = 'U': if UPLO = 'L': 179*> 180*> ( d e v2 v3 v4 ) ( d ) 181*> ( d e v3 v4 ) ( e d ) 182*> ( d e v4 ) ( v1 e d ) 183*> ( d e ) ( v1 v2 e d ) 184*> ( d ) ( v1 v2 v3 e d ) 185*> 186*> where d and e denote diagonal and off-diagonal elements of T, and vi 187*> denotes an element of the vector defining H(i). 188*> \endverbatim 189*> 190* ===================================================================== 191 SUBROUTINE SSYTRD( UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO ) 192* 193* -- LAPACK computational routine -- 194* -- LAPACK is a software package provided by Univ. of Tennessee, -- 195* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- 196* 197* .. Scalar Arguments .. 198 CHARACTER UPLO 199 INTEGER INFO, LDA, LWORK, N 200* .. 201* .. Array Arguments .. 202 REAL A( LDA, * ), D( * ), E( * ), TAU( * ), 203 $ WORK( * ) 204* .. 205* 206* ===================================================================== 207* 208* .. Parameters .. 209 REAL ONE 210 PARAMETER ( ONE = 1.0E+0 ) 211* .. 212* .. Local Scalars .. 213 LOGICAL LQUERY, UPPER 214 INTEGER I, IINFO, IWS, J, KK, LDWORK, LWKOPT, NB, 215 $ NBMIN, NX 216* .. 217* .. External Subroutines .. 218 EXTERNAL SLATRD, SSYR2K, SSYTD2, XERBLA 219* .. 220* .. Intrinsic Functions .. 221 INTRINSIC MAX 222* .. 223* .. External Functions .. 224 LOGICAL LSAME 225 INTEGER ILAENV 226 EXTERNAL LSAME, ILAENV 227* .. 228* .. Executable Statements .. 229* 230* Test the input parameters 231* 232 INFO = 0 233 UPPER = LSAME( UPLO, 'U' ) 234 LQUERY = ( LWORK.EQ.-1 ) 235 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN 236 INFO = -1 237 ELSE IF( N.LT.0 ) THEN 238 INFO = -2 239 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN 240 INFO = -4 241 ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN 242 INFO = -9 243 END IF 244* 245 IF( INFO.EQ.0 ) THEN 246* 247* Determine the block size. 248* 249 NB = ILAENV( 1, 'SSYTRD', UPLO, N, -1, -1, -1 ) 250 LWKOPT = N*NB 251 WORK( 1 ) = LWKOPT 252 END IF 253* 254 IF( INFO.NE.0 ) THEN 255 CALL XERBLA( 'SSYTRD', -INFO ) 256 RETURN 257 ELSE IF( LQUERY ) THEN 258 RETURN 259 END IF 260* 261* Quick return if possible 262* 263 IF( N.EQ.0 ) THEN 264 WORK( 1 ) = 1 265 RETURN 266 END IF 267* 268 NX = N 269 IWS = 1 270 IF( NB.GT.1 .AND. NB.LT.N ) THEN 271* 272* Determine when to cross over from blocked to unblocked code 273* (last block is always handled by unblocked code). 274* 275 NX = MAX( NB, ILAENV( 3, 'SSYTRD', UPLO, N, -1, -1, -1 ) ) 276 IF( NX.LT.N ) THEN 277* 278* Determine if workspace is large enough for blocked code. 279* 280 LDWORK = N 281 IWS = LDWORK*NB 282 IF( LWORK.LT.IWS ) THEN 283* 284* Not enough workspace to use optimal NB: determine the 285* minimum value of NB, and reduce NB or force use of 286* unblocked code by setting NX = N. 287* 288 NB = MAX( LWORK / LDWORK, 1 ) 289 NBMIN = ILAENV( 2, 'SSYTRD', UPLO, N, -1, -1, -1 ) 290 IF( NB.LT.NBMIN ) 291 $ NX = N 292 END IF 293 ELSE 294 NX = N 295 END IF 296 ELSE 297 NB = 1 298 END IF 299* 300 IF( UPPER ) THEN 301* 302* Reduce the upper triangle of A. 303* Columns 1:kk are handled by the unblocked method. 304* 305 KK = N - ( ( N-NX+NB-1 ) / NB )*NB 306 DO 20 I = N - NB + 1, KK + 1, -NB 307* 308* Reduce columns i:i+nb-1 to tridiagonal form and form the 309* matrix W which is needed to update the unreduced part of 310* the matrix 311* 312 CALL SLATRD( UPLO, I+NB-1, NB, A, LDA, E, TAU, WORK, 313 $ LDWORK ) 314* 315* Update the unreduced submatrix A(1:i-1,1:i-1), using an 316* update of the form: A := A - V*W**T - W*V**T 317* 318 CALL SSYR2K( UPLO, 'No transpose', I-1, NB, -ONE, A( 1, I ), 319 $ LDA, WORK, LDWORK, ONE, A, LDA ) 320* 321* Copy superdiagonal elements back into A, and diagonal 322* elements into D 323* 324 DO 10 J = I, I + NB - 1 325 A( J-1, J ) = E( J-1 ) 326 D( J ) = A( J, J ) 327 10 CONTINUE 328 20 CONTINUE 329* 330* Use unblocked code to reduce the last or only block 331* 332 CALL SSYTD2( UPLO, KK, A, LDA, D, E, TAU, IINFO ) 333 ELSE 334* 335* Reduce the lower triangle of A 336* 337 DO 40 I = 1, N - NX, NB 338* 339* Reduce columns i:i+nb-1 to tridiagonal form and form the 340* matrix W which is needed to update the unreduced part of 341* the matrix 342* 343 CALL SLATRD( UPLO, N-I+1, NB, A( I, I ), LDA, E( I ), 344 $ TAU( I ), WORK, LDWORK ) 345* 346* Update the unreduced submatrix A(i+ib:n,i+ib:n), using 347* an update of the form: A := A - V*W**T - W*V**T 348* 349 CALL SSYR2K( UPLO, 'No transpose', N-I-NB+1, NB, -ONE, 350 $ A( I+NB, I ), LDA, WORK( NB+1 ), LDWORK, ONE, 351 $ A( I+NB, I+NB ), LDA ) 352* 353* Copy subdiagonal elements back into A, and diagonal 354* elements into D 355* 356 DO 30 J = I, I + NB - 1 357 A( J+1, J ) = E( J ) 358 D( J ) = A( J, J ) 359 30 CONTINUE 360 40 CONTINUE 361* 362* Use unblocked code to reduce the last or only block 363* 364 CALL SSYTD2( UPLO, N-I+1, A( I, I ), LDA, D( I ), E( I ), 365 $ TAU( I ), IINFO ) 366 END IF 367* 368 WORK( 1 ) = LWKOPT 369 RETURN 370* 371* End of SSYTRD 372* 373 END 374