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

NAME

6       DSYTRD - a real symmetric matrix A to real symmetric tridiagonal form T
7       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
23

ARGUMENTS

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

FURTHER DETAILS

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