1CHEGVD(1) LAPACK driver routine (version 3.2) CHEGVD(1)
2
3
4
6 CHEGVD - computes all the eigenvalues, and optionally, the eigenvectors
7 of a complex generalized Hermitian-definite eigenproblem, of the form
8 A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x
9
11 SUBROUTINE CHEGVD( ITYPE, JOBZ, UPLO, N, A, LDA, B, LDB, W, WORK,
12 LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO )
13
14 CHARACTER JOBZ, UPLO
15
16 INTEGER INFO, ITYPE, LDA, LDB, LIWORK, LRWORK, LWORK, N
17
18 INTEGER IWORK( * )
19
20 REAL RWORK( * ), W( * )
21
22 COMPLEX A( LDA, * ), B( LDB, * ), WORK( * )
23
25 CHEGVD computes all the eigenvalues, and optionally, the eigenvectors
26 of a complex generalized Hermitian-definite eigenproblem, of the form
27 A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x. Here A and B
28 are assumed to be Hermitian and B is also positive definite. If eigen‐
29 vectors are desired, it uses a divide and conquer algorithm. The
30 divide and conquer algorithm makes very mild assumptions about floating
31 point arithmetic. It will work on machines with a guard digit in
32 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
38 ITYPE (input) INTEGER
39 Specifies the problem type to be solved:
40 = 1: A*x = (lambda)*B*x
41 = 2: A*B*x = (lambda)*x
42 = 3: B*A*x = (lambda)*x
43
44 JOBZ (input) CHARACTER*1
45 = 'N': Compute eigenvalues only;
46 = 'V': Compute eigenvalues and eigenvectors.
47
48 UPLO (input) CHARACTER*1
49 = 'U': Upper triangles of A and B are stored;
50 = 'L': Lower triangles of A and B are stored.
51
52 N (input) INTEGER
53 The order of the matrices A and B. N >= 0.
54
55 A (input/output) COMPLEX array, dimension (LDA, N)
56 On entry, the Hermitian matrix A. If UPLO = 'U', the leading
57 N-by-N upper triangular part of A contains the upper triangular
58 part of the matrix A. If UPLO = 'L', the leading N-by-N lower
59 triangular part of A contains the lower triangular part of the
60 matrix A. On exit, if JOBZ = 'V', then if INFO = 0, A contains
61 the matrix Z of eigenvectors. The eigenvectors are normalized
62 as follows: if ITYPE = 1 or 2, Z**H*B*Z = I; if ITYPE = 3,
63 Z**H*inv(B)*Z = I. If JOBZ = 'N', then on exit the upper tri‐
64 angle (if UPLO='U') or the lower triangle (if UPLO='L') of A,
65 including the diagonal, is destroyed.
66
67 LDA (input) INTEGER
68 The leading dimension of the array A. LDA >= max(1,N).
69
70 B (input/output) COMPLEX array, dimension (LDB, N)
71 On entry, the Hermitian matrix B. If UPLO = 'U', the leading
72 N-by-N upper triangular part of B contains the upper triangular
73 part of the matrix B. If UPLO = 'L', the leading N-by-N lower
74 triangular part of B contains the lower triangular part of the
75 matrix B. On exit, if INFO <= N, the part of B containing the
76 matrix is overwritten by the triangular factor U or L from the
77 Cholesky factorization B = U**H*U or B = L*L**H.
78
79 LDB (input) INTEGER
80 The leading dimension of the array B. LDB >= max(1,N).
81
82 W (output) REAL array, dimension (N)
83 If INFO = 0, the eigenvalues in ascending order.
84
85 WORK (workspace/output) COMPLEX array, dimension (MAX(1,LWORK))
86 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
87
88 LWORK (input) INTEGER
89 The length of the array WORK. If N <= 1, LWORK
90 >= 1. If JOBZ = 'N' and N > 1, LWORK >= N + 1. If JOBZ =
91 'V' and N > 1, LWORK >= 2*N + N**2. If LWORK = -1, then a
92 workspace query is assumed; the routine only calculates the
93 optimal sizes of the WORK, RWORK and IWORK arrays, returns
94 these values as the first entries of the WORK, RWORK and IWORK
95 arrays, and no error message related to LWORK or LRWORK or
96 LIWORK is issued by XERBLA.
97
98 RWORK (workspace/output) REAL array, dimension (MAX(1,LRWORK))
99 On exit, if INFO = 0, RWORK(1) returns the optimal LRWORK.
100
101 LRWORK (input) INTEGER
102 The dimension of the array RWORK. If N <= 1,
103 LRWORK >= 1. If JOBZ = 'N' and N > 1, LRWORK >= N. If JOBZ
104 = 'V' and N > 1, LRWORK >= 1 + 5*N + 2*N**2. If LRWORK = -1,
105 then a workspace query is assumed; the routine only calculates
106 the optimal sizes of the WORK, RWORK and IWORK arrays, returns
107 these values as the first entries of the WORK, RWORK and IWORK
108 arrays, and no error message related to LWORK or LRWORK or
109 LIWORK is issued by XERBLA.
110
111 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
112 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
113
114 LIWORK (input) INTEGER
115 The dimension of the array IWORK. If N <= 1,
116 LIWORK >= 1. If JOBZ = 'N' and N > 1, LIWORK >= 1. If JOBZ
117 = 'V' and N > 1, LIWORK >= 3 + 5*N. If LIWORK = -1, then a
118 workspace query is assumed; the routine only calculates the
119 optimal sizes of the WORK, RWORK and IWORK arrays, returns
120 these values as the first entries of the WORK, RWORK and IWORK
121 arrays, and no error message related to LWORK or LRWORK or
122 LIWORK is issued by XERBLA.
123
124 INFO (output) INTEGER
125 = 0: successful exit
126 < 0: if INFO = -i, the i-th argument had an illegal value
127 > 0: CPOTRF or CHEEVD returned an error code:
128 <= N: if INFO = i and JOBZ = 'N', then the algorithm failed to
129 converge; i off-diagonal elements of an intermediate tridiago‐
130 nal form did not converge to zero; if INFO = i and JOBZ = 'V',
131 then the algorithm failed to compute an eigenvalue while work‐
132 ing on the submatrix lying in rows and columns INFO/(N+1)
133 through mod(INFO,N+1); > N: if INFO = N + i, for 1 <= i <= N,
134 then the leading minor of order i of B is not positive defi‐
135 nite. The factorization of B could not be completed and no ei‐
136 genvalues or eigenvectors were computed.
137
139 Based on contributions by
140 Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA Modi‐
141 fied so that no backsubstitution is performed if CHEEVD fails to con‐
142 verge (NEIG in old code could be greater than N causing out of bounds
143 reference to A - reported by Ralf Meyer). Also corrected the descrip‐
144 tion of INFO and the test on ITYPE. Sven, 16 Feb 05.
145
146
147
148 LAPACK driver routine (version 3.N2o)vember 2008 CHEGVD(1)