1DSYGVD(1) LAPACK driver routine (version 3.2) DSYGVD(1)
2
3
4
6 DSYGVD - computes all the eigenvalues, and optionally, the eigenvectors
7 of a 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
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
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. The
29 divide and conquer algorithm makes very mild assumptions about floating
30 point arithmetic. It will work on machines with a guard digit in
31 add/subtract, or on those binary machines without guard digits which
32 subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2. It could
33 conceivably fail on hexadecimal or decimal machines without guard dig‐
34 its, but we know of none.
35
37 ITYPE (input) INTEGER
38 Specifies the problem type to be solved:
39 = 1: A*x = (lambda)*B*x
40 = 2: A*B*x = (lambda)*x
41 = 3: B*A*x = (lambda)*x
42
43 JOBZ (input) CHARACTER*1
44 = 'N': Compute eigenvalues only;
45 = 'V': Compute eigenvalues and eigenvectors.
46
47 UPLO (input) CHARACTER*1
48 = 'U': Upper triangles of A and B are stored;
49 = 'L': Lower triangles of A and B are stored.
50
51 N (input) INTEGER
52 The order of the matrices A and B. N >= 0.
53
54 A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
55 On entry, the symmetric matrix A. If UPLO = 'U', the leading
56 N-by-N upper triangular part of A contains the upper triangular
57 part of the matrix A. If UPLO = 'L', the leading N-by-N lower
58 triangular part of A contains the lower triangular part of the
59 matrix A. On exit, if JOBZ = 'V', then if INFO = 0, A contains
60 the matrix Z of eigenvectors. The eigenvectors are normalized
61 as follows: if ITYPE = 1 or 2, Z**T*B*Z = I; if ITYPE = 3,
62 Z**T*inv(B)*Z = I. If JOBZ = 'N', then on exit the upper tri‐
63 angle (if UPLO='U') or the lower triangle (if UPLO='L') of A,
64 including the diagonal, is destroyed.
65
66 LDA (input) INTEGER
67 The leading dimension of the array A. LDA >= max(1,N).
68
69 B (input/output) DOUBLE PRECISION array, dimension (LDB, N)
70 On entry, the symmetric matrix B. If UPLO = 'U', the leading
71 N-by-N upper triangular part of B contains the upper triangular
72 part of the matrix B. If UPLO = 'L', the leading N-by-N lower
73 triangular part of B contains the lower triangular part of the
74 matrix B. On exit, if INFO <= N, the part of B containing the
75 matrix is overwritten by the triangular factor U or L from the
76 Cholesky factorization B = U**T*U or B = L*L**T.
77
78 LDB (input) INTEGER
79 The leading dimension of the array B. LDB >= max(1,N).
80
81 W (output) DOUBLE PRECISION array, dimension (N)
82 If INFO = 0, the eigenvalues in ascending order.
83
84 WORK (workspace/output) DOUBLE PRECISION array, dimension
85 (MAX(1,LWORK))
86 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
87
88 LWORK (input) INTEGER
89 The dimension of the array WORK. If N <= 1,
90 LWORK >= 1. If JOBZ = 'N' and N > 1, LWORK >= 2*N+1. If JOBZ
91 = 'V' and N > 1, LWORK >= 1 + 6*N + 2*N**2. If LWORK = -1,
92 then a workspace query is assumed; the routine only calculates
93 the optimal sizes of the WORK and IWORK arrays, returns these
94 values as the first entries of the WORK and IWORK arrays, and
95 no error message related to LWORK or LIWORK is issued by
96 XERBLA.
97
98 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
99 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
100
101 LIWORK (input) INTEGER
102 The dimension of the array IWORK. If N <= 1,
103 LIWORK >= 1. If JOBZ = 'N' and N > 1, LIWORK >= 1. If JOBZ
104 = 'V' and N > 1, LIWORK >= 3 + 5*N. If LIWORK = -1, then a
105 workspace query is assumed; the routine only calculates the
106 optimal sizes of the WORK and IWORK arrays, returns these val‐
107 ues as the first entries of the WORK and IWORK arrays, and no
108 error message related to LWORK or LIWORK is issued by XERBLA.
109
110 INFO (output) INTEGER
111 = 0: successful exit
112 < 0: if INFO = -i, the i-th argument had an illegal value
113 > 0: DPOTRF or DSYEVD returned an error code:
114 <= N: if INFO = i and JOBZ = 'N', then the algorithm failed to
115 converge; i off-diagonal elements of an intermediate tridiago‐
116 nal form did not converge to zero; if INFO = i and JOBZ = 'V',
117 then the algorithm failed to compute an eigenvalue while work‐
118 ing on the submatrix lying in rows and columns INFO/(N+1)
119 through mod(INFO,N+1); > N: if INFO = N + i, for 1 <= i <= N,
120 then the leading minor of order i of B is not positive defi‐
121 nite. The factorization of B could not be completed and no ei‐
122 genvalues or eigenvectors were computed.
123
125 Based on contributions by
126 Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA Modi‐
127 fied so that no backsubstitution is performed if DSYEVD fails to con‐
128 verge (NEIG in old code could be greater than N causing out of bounds
129 reference to A - reported by Ralf Meyer). Also corrected the descrip‐
130 tion of INFO and the test on ITYPE. Sven, 16 Feb 05.
131
132
133
134 LAPACK driver routine (version 3.N2o)vember 2008 DSYGVD(1)