1DSYGVD(1)             LAPACK driver routine (version 3.1)            DSYGVD(1)
2
3
4

NAME

6       DSYGVD  -  all  the  eigenvalues, and optionally, the eigenvectors of a
7       real  generalized  symmetric-definite   eigenproblem,   of   the   form
8       A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x
9

SYNOPSIS

11       SUBROUTINE DSYGVD( ITYPE,  JOBZ,  UPLO,  N,  A,  LDA,  B, LDB, W, WORK,
12                          LWORK, IWORK, LIWORK, INFO )
13
14           CHARACTER      JOBZ, UPLO
15
16           INTEGER        INFO, ITYPE, LDA, LDB, LIWORK, LWORK, N
17
18           INTEGER        IWORK( * )
19
20           DOUBLE         PRECISION A( LDA, * ), B( LDB, * ), W( * ), WORK(  *
21                          )
22

PURPOSE

24       DSYGVD  computes  all the eigenvalues, and optionally, the eigenvectors
25       of a real generalized  symmetric-definite  eigenproblem,  of  the  form
26       A*x=(lambda)*B*x,  A*Bx=(lambda)*x,  or B*A*x=(lambda)*x.  Here A and B
27       are assumed to be symmetric and B is also positive definite.  If eigen‐
28       vectors are desired, it uses a divide and conquer algorithm.
29
30       The  divide  and  conquer  algorithm  makes very mild assumptions about
31       floating point arithmetic. It will work on machines with a guard  digit
32       in add/subtract, or on those binary machines without guard digits which
33       subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2. It  could
34       conceivably  fail on hexadecimal or decimal machines without guard dig‐
35       its, but we know of none.
36
37

ARGUMENTS

39       ITYPE   (input) INTEGER
40               Specifies the problem type to be solved:
41               = 1:  A*x = (lambda)*B*x
42               = 2:  A*B*x = (lambda)*x
43               = 3:  B*A*x = (lambda)*x
44
45       JOBZ    (input) CHARACTER*1
46               = 'N':  Compute eigenvalues only;
47               = 'V':  Compute eigenvalues and eigenvectors.
48
49       UPLO    (input) CHARACTER*1
50               = 'U':  Upper triangles of A and B are stored;
51               = 'L':  Lower triangles of A and B are stored.
52
53       N       (input) INTEGER
54               The order of the matrices A and B.  N >= 0.
55
56       A       (input/output) DOUBLE PRECISION array, dimension (LDA, N)
57               On entry, the symmetric matrix A.  If UPLO = 'U',  the  leading
58               N-by-N upper triangular part of A contains the upper triangular
59               part of the matrix A.  If UPLO = 'L', the leading N-by-N  lower
60               triangular  part of A contains the lower triangular part of the
61               matrix A.
62
63               On exit, if JOBZ = 'V', then if INFO = 0, A contains the matrix
64               Z of eigenvectors.  The eigenvectors are normalized as follows:
65               if ITYPE = 1 or 2, Z**T*B*Z = I; if ITYPE = 3, Z**T*inv(B)*Z  =
66               I.   If  JOBZ  =  'N',  then  on  exit  the  upper triangle (if
67               UPLO='U') or the lower triangle (if UPLO='L') of  A,  including
68               the diagonal, is destroyed.
69
70       LDA     (input) INTEGER
71               The leading dimension of the array A.  LDA >= max(1,N).
72
73       B       (input/output) DOUBLE PRECISION array, dimension (LDB, N)
74               On  entry,  the symmetric matrix B.  If UPLO = 'U', the leading
75               N-by-N upper triangular part of B contains the upper triangular
76               part  of the matrix B.  If UPLO = 'L', the leading N-by-N lower
77               triangular part of B contains the lower triangular part of  the
78               matrix B.
79
80               On  exit,  if INFO <= N, the part of B containing the matrix is
81               overwritten by the triangular factor U or L from  the  Cholesky
82               factorization B = U**T*U or B = L*L**T.
83
84       LDB     (input) INTEGER
85               The leading dimension of the array B.  LDB >= max(1,N).
86
87       W       (output) DOUBLE PRECISION array, dimension (N)
88               If INFO = 0, the eigenvalues in ascending order.
89
90       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
91       (MAX(1,LWORK))
92               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
93
94       LWORK   (input) INTEGER
95               The   dimension   of   the   array   WORK.    If   N   <=    1,
96               LWORK  >= 1.  If JOBZ = 'N' and N > 1, LWORK >= 2*N+1.  If JOBZ
97               = 'V' and N > 1, LWORK >= 1 + 6*N + 2*N**2.
98
99               If LWORK = -1, then a workspace query is assumed;  the  routine
100               only calculates the optimal sizes of the WORK and IWORK arrays,
101               returns these values as the first entries of the WORK and IWORK
102               arrays,  and  no  error  message  related to LWORK or LIWORK is
103               issued by XERBLA.
104
105       IWORK   (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
106               On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
107
108       LIWORK  (input) INTEGER
109               The   dimension   of   the   array   IWORK.    If   N   <=   1,
110               LIWORK  >=  1.  If JOBZ  = 'N' and N > 1, LIWORK >= 1.  If JOBZ
111               = 'V' and N > 1, LIWORK >= 3 + 5*N.
112
113               If LIWORK = -1, then a workspace query is assumed; the  routine
114               only calculates the optimal sizes of the WORK and IWORK arrays,
115               returns these values as the first entries of the WORK and IWORK
116               arrays,  and  no  error  message  related to LWORK or LIWORK is
117               issued by XERBLA.
118
119       INFO    (output) INTEGER
120               = 0:  successful exit
121               < 0:  if INFO = -i, the i-th argument had an illegal value
122               > 0:  DPOTRF or DSYEVD returned an error code:
123               <= N:  if INFO = i and JOBZ = 'N', then the algorithm failed to
124               converge;  i off-diagonal elements of an intermediate tridiago‐
125               nal form did not converge to zero; if INFO = i and JOBZ =  'V',
126               then  the algorithm failed to compute an eigenvalue while work‐
127               ing on the submatrix  lying  in  rows  and  columns  INFO/(N+1)
128               through mod(INFO,N+1); > N:   if INFO = N + i, for 1 <= i <= N,
129               then the leading minor of order i of B is  not  positive  defi‐
130               nite.  The factorization of B could not be completed and no ei‐
131               genvalues or eigenvectors were computed.
132

FURTHER DETAILS

134       Based on contributions by
135          Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
136
137       Modified so that no backsubstitution is performed if  DSYEVD  fails  to
138       converge  (NEIG  in  old  code  could  be greater than N causing out of
139       bounds reference to A - reported by Ralf Meyer).   Also  corrected  the
140       description of INFO and the test on ITYPE. Sven, 16 Feb 05.
141
142
143
144 LAPACK driver routine (version 3.N1o)vember 2006                       DSYGVD(1)
Impressum