1DSYTRD(1)                LAPACK routine (version 3.2)                DSYTRD(1)
2
3
4

NAME

6       DSYTRD  - reduces a real symmetric matrix A to real symmetric tridiago‐
7       nal form T by an orthogonal similarity transformation
8

SYNOPSIS

10       SUBROUTINE DSYTRD( UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO )
11
12           CHARACTER      UPLO
13
14           INTEGER        INFO, LDA, LWORK, N
15
16           DOUBLE         PRECISION A( LDA, * ), D( * ), E( *  ),  TAU(  *  ),
17                          WORK( * )
18

PURPOSE

20       DSYTRD  reduces a real symmetric matrix A to real symmetric tridiagonal
21       form T by an orthogonal similarity transformation: Q**T * A * Q = T.
22

ARGUMENTS

24       UPLO    (input) CHARACTER*1
25               = 'U':  Upper triangle of A is stored;
26               = 'L':  Lower triangle of A is stored.
27
28       N       (input) INTEGER
29               The order of the matrix A.  N >= 0.
30
31       A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
32               On entry, the symmetric matrix A.  If UPLO = 'U',  the  leading
33               N-by-N upper triangular part of A contains the upper triangular
34               part of the matrix A, and the strictly lower triangular part of
35               A  is  not referenced.  If UPLO = 'L', the leading N-by-N lower
36               triangular part of A contains the lower triangular part of  the
37               matrix  A,  and  the strictly upper triangular part of A is not
38               referenced.  On exit, if UPLO = 'U',  the  diagonal  and  first
39               superdiagonal  of  A  are overwritten by the corresponding ele‐
40               ments of the tridiagonal matrix T, and the elements  above  the
41               first superdiagonal, with the array TAU, represent the orthogo‐
42               nal matrix Q as a product of elementary reflectors; if  UPLO  =
43               'L',  the diagonal and first subdiagonal of A are over- written
44               by the corresponding elements of the tridiagonal matrix T,  and
45               the  elements  below the first subdiagonal, with the array TAU,
46               represent the orthogonal matrix Q as a  product  of  elementary
47               reflectors.  See  Further Details.  LDA     (input) INTEGER The
48               leading dimension of the array A.  LDA >= max(1,N).
49
50       D       (output) DOUBLE PRECISION array, dimension (N)
51               The diagonal elements of  the  tridiagonal  matrix  T:  D(i)  =
52               A(i,i).
53
54       E       (output) DOUBLE PRECISION array, dimension (N-1)
55               The  off-diagonal  elements of the tridiagonal matrix T: E(i) =
56               A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
57
58       TAU     (output) DOUBLE PRECISION array, dimension (N-1)
59               The scalar factors of the elementary  reflectors  (see  Further
60               Details).
61
62       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
63       (MAX(1,LWORK))
64               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
65
66       LWORK   (input) INTEGER
67               The dimension of the array WORK.  LWORK >= 1.  For optimum per‐
68               formance  LWORK >= N*NB, where NB is the optimal blocksize.  If
69               LWORK = -1, then a workspace query is assumed; the routine only
70               calculates  the  optimal  size  of the WORK array, returns this
71               value as the first entry of the WORK array, and no  error  mes‐
72               sage related to LWORK is issued by XERBLA.
73
74       INFO    (output) INTEGER
75               = 0:  successful exit
76               < 0:  if INFO = -i, the i-th argument had an illegal value
77

FURTHER DETAILS

79       If  UPLO  = 'U', the matrix Q is represented as a product of elementary
80       reflectors
81          Q = H(n-1) . . . H(2) H(1).
82       Each H(i) has the form
83          H(i) = I - tau * v * v'
84       where tau is a real scalar, and v is a real vector with
85       v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in
86       A(1:i-1,i+1), and tau in TAU(i).
87       If UPLO = 'L', the matrix Q is represented as a product  of  elementary
88       reflectors
89          Q = H(1) H(2) . . . H(n-1).
90       Each H(i) has the form
91          H(i) = I - tau * v * v'
92       where tau is a real scalar, and v is a real vector with
93       v(1:i)  =  0  and v(i+1) = 1; v(i+2:n) is stored on exit in A(i+2:n,i),
94       and tau in TAU(i).
95       The contents of A on exit are illustrated  by  the  following  examples
96       with n = 5:
97       if UPLO = 'U':                       if UPLO = 'L':
98         (  d   e   v2  v3  v4 )              (  d                  )
99         (      d   e   v3  v4 )              (  e   d              )
100         (          d   e   v4 )              (  v1  e   d          )
101         (              d   e  )              (  v1  v2  e   d      )
102         (                   d  )              (  v1  v2  v3  e   d  ) where d
103       and e denote diagonal and off-diagonal elements of T, and vi denotes an
104       element of the vector defining H(i).
105
106
107
108 LAPACK routine (version 3.2)    November 2008                       DSYTRD(1)
Impressum