LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
chpgvd.f
Go to the documentation of this file.
1 *> \brief \b CHPGST
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CHPGVD + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chpgvd.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chpgvd.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chpgvd.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CHPGVD( ITYPE, JOBZ, UPLO, N, AP, BP, W, Z, LDZ, WORK,
22 * LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER JOBZ, UPLO
26 * INTEGER INFO, ITYPE, LDZ, LIWORK, LRWORK, LWORK, N
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IWORK( * )
30 * REAL RWORK( * ), W( * )
31 * COMPLEX AP( * ), BP( * ), WORK( * ), Z( LDZ, * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> CHPGVD computes all the eigenvalues and, optionally, the eigenvectors
41 *> of a complex generalized Hermitian-definite eigenproblem, of the form
42 *> A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x. Here A and
43 *> B are assumed to be Hermitian, stored in packed format, and B is also
44 *> positive definite.
45 *> If eigenvectors are desired, it uses a divide and conquer algorithm.
46 *>
47 *> The divide and conquer algorithm makes very mild assumptions about
48 *> floating point arithmetic. It will work on machines with a guard
49 *> digit in add/subtract, or on those binary machines without guard
50 *> digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or
51 *> Cray-2. It could conceivably fail on hexadecimal or decimal machines
52 *> without guard digits, but we know of none.
53 *> \endverbatim
54 *
55 * Arguments:
56 * ==========
57 *
58 *> \param[in] ITYPE
59 *> \verbatim
60 *> ITYPE is INTEGER
61 *> Specifies the problem type to be solved:
62 *> = 1: A*x = (lambda)*B*x
63 *> = 2: A*B*x = (lambda)*x
64 *> = 3: B*A*x = (lambda)*x
65 *> \endverbatim
66 *>
67 *> \param[in] JOBZ
68 *> \verbatim
69 *> JOBZ is CHARACTER*1
70 *> = 'N': Compute eigenvalues only;
71 *> = 'V': Compute eigenvalues and eigenvectors.
72 *> \endverbatim
73 *>
74 *> \param[in] UPLO
75 *> \verbatim
76 *> UPLO is CHARACTER*1
77 *> = 'U': Upper triangles of A and B are stored;
78 *> = 'L': Lower triangles of A and B are stored.
79 *> \endverbatim
80 *>
81 *> \param[in] N
82 *> \verbatim
83 *> N is INTEGER
84 *> The order of the matrices A and B. N >= 0.
85 *> \endverbatim
86 *>
87 *> \param[in,out] AP
88 *> \verbatim
89 *> AP is COMPLEX array, dimension (N*(N+1)/2)
90 *> On entry, the upper or lower triangle of the Hermitian matrix
91 *> A, packed columnwise in a linear array. The j-th column of A
92 *> is stored in the array AP as follows:
93 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
94 *> if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
95 *>
96 *> On exit, the contents of AP are destroyed.
97 *> \endverbatim
98 *>
99 *> \param[in,out] BP
100 *> \verbatim
101 *> BP is COMPLEX array, dimension (N*(N+1)/2)
102 *> On entry, the upper or lower triangle of the Hermitian matrix
103 *> B, packed columnwise in a linear array. The j-th column of B
104 *> is stored in the array BP as follows:
105 *> if UPLO = 'U', BP(i + (j-1)*j/2) = B(i,j) for 1<=i<=j;
106 *> if UPLO = 'L', BP(i + (j-1)*(2*n-j)/2) = B(i,j) for j<=i<=n.
107 *>
108 *> On exit, the triangular factor U or L from the Cholesky
109 *> factorization B = U**H*U or B = L*L**H, in the same storage
110 *> format as B.
111 *> \endverbatim
112 *>
113 *> \param[out] W
114 *> \verbatim
115 *> W is REAL array, dimension (N)
116 *> If INFO = 0, the eigenvalues in ascending order.
117 *> \endverbatim
118 *>
119 *> \param[out] Z
120 *> \verbatim
121 *> Z is COMPLEX array, dimension (LDZ, N)
122 *> If JOBZ = 'V', then if INFO = 0, Z contains the matrix Z of
123 *> eigenvectors. The eigenvectors are normalized as follows:
124 *> if ITYPE = 1 or 2, Z**H*B*Z = I;
125 *> if ITYPE = 3, Z**H*inv(B)*Z = I.
126 *> If JOBZ = 'N', then Z is not referenced.
127 *> \endverbatim
128 *>
129 *> \param[in] LDZ
130 *> \verbatim
131 *> LDZ is INTEGER
132 *> The leading dimension of the array Z. LDZ >= 1, and if
133 *> JOBZ = 'V', LDZ >= max(1,N).
134 *> \endverbatim
135 *>
136 *> \param[out] WORK
137 *> \verbatim
138 *> WORK is COMPLEX array, dimension (MAX(1,LWORK))
139 *> On exit, if INFO = 0, WORK(1) returns the required LWORK.
140 *> \endverbatim
141 *>
142 *> \param[in] LWORK
143 *> \verbatim
144 *> LWORK is INTEGER
145 *> The dimension of array WORK.
146 *> If N <= 1, LWORK >= 1.
147 *> If JOBZ = 'N' and N > 1, LWORK >= N.
148 *> If JOBZ = 'V' and N > 1, LWORK >= 2*N.
149 *>
150 *> If LWORK = -1, then a workspace query is assumed; the routine
151 *> only calculates the required sizes of the WORK, RWORK and
152 *> IWORK arrays, returns these values as the first entries of
153 *> the WORK, RWORK and IWORK arrays, and no error message
154 *> related to LWORK or LRWORK or LIWORK is issued by XERBLA.
155 *> \endverbatim
156 *>
157 *> \param[out] RWORK
158 *> \verbatim
159 *> RWORK is REAL array, dimension (MAX(1,LRWORK))
160 *> On exit, if INFO = 0, RWORK(1) returns the required LRWORK.
161 *> \endverbatim
162 *>
163 *> \param[in] LRWORK
164 *> \verbatim
165 *> LRWORK is INTEGER
166 *> The dimension of array RWORK.
167 *> If N <= 1, LRWORK >= 1.
168 *> If JOBZ = 'N' and N > 1, LRWORK >= N.
169 *> If JOBZ = 'V' and N > 1, LRWORK >= 1 + 5*N + 2*N**2.
170 *>
171 *> If LRWORK = -1, then a workspace query is assumed; the
172 *> routine only calculates the required sizes of the WORK, RWORK
173 *> and IWORK arrays, returns these values as the first entries
174 *> of the WORK, RWORK and IWORK arrays, and no error message
175 *> related to LWORK or LRWORK or LIWORK is issued by XERBLA.
176 *> \endverbatim
177 *>
178 *> \param[out] IWORK
179 *> \verbatim
180 *> IWORK is INTEGER array, dimension (MAX(1,LIWORK))
181 *> On exit, if INFO = 0, IWORK(1) returns the required LIWORK.
182 *> \endverbatim
183 *>
184 *> \param[in] LIWORK
185 *> \verbatim
186 *> LIWORK is INTEGER
187 *> The dimension of array IWORK.
188 *> If JOBZ = 'N' or N <= 1, LIWORK >= 1.
189 *> If JOBZ = 'V' and N > 1, LIWORK >= 3 + 5*N.
190 *>
191 *> If LIWORK = -1, then a workspace query is assumed; the
192 *> routine only calculates the required sizes of the WORK, RWORK
193 *> and IWORK arrays, returns these values as the first entries
194 *> of the WORK, RWORK and IWORK arrays, and no error message
195 *> related to LWORK or LRWORK or LIWORK is issued by XERBLA.
196 *> \endverbatim
197 *>
198 *> \param[out] INFO
199 *> \verbatim
200 *> INFO is INTEGER
201 *> = 0: successful exit
202 *> < 0: if INFO = -i, the i-th argument had an illegal value
203 *> > 0: CPPTRF or CHPEVD returned an error code:
204 *> <= N: if INFO = i, CHPEVD failed to converge;
205 *> i off-diagonal elements of an intermediate
206 *> tridiagonal form did not convergeto zero;
207 *> > N: if INFO = N + i, for 1 <= i <= n, then the leading
208 *> minor of order i of B is not positive definite.
209 *> The factorization of B could not be completed and
210 *> no eigenvalues or eigenvectors were computed.
211 *> \endverbatim
212 *
213 * Authors:
214 * ========
215 *
216 *> \author Univ. of Tennessee
217 *> \author Univ. of California Berkeley
218 *> \author Univ. of Colorado Denver
219 *> \author NAG Ltd.
220 *
221 *> \date November 2011
222 *
223 *> \ingroup complexOTHEReigen
224 *
225 *> \par Contributors:
226 * ==================
227 *>
228 *> Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
229 *
230 * =====================================================================
231  SUBROUTINE chpgvd( ITYPE, JOBZ, UPLO, N, AP, BP, W, Z, LDZ, WORK,
232  $ lwork, rwork, lrwork, iwork, liwork, info )
233 *
234 * -- LAPACK driver routine (version 3.4.0) --
235 * -- LAPACK is a software package provided by Univ. of Tennessee, --
236 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
237 * November 2011
238 *
239 * .. Scalar Arguments ..
240  CHARACTER jobz, uplo
241  INTEGER info, itype, ldz, liwork, lrwork, lwork, n
242 * ..
243 * .. Array Arguments ..
244  INTEGER iwork( * )
245  REAL rwork( * ), w( * )
246  COMPLEX ap( * ), bp( * ), work( * ), z( ldz, * )
247 * ..
248 *
249 * =====================================================================
250 *
251 * .. Local Scalars ..
252  LOGICAL lquery, upper, wantz
253  CHARACTER trans
254  INTEGER j, liwmin, lrwmin, lwmin, neig
255 * ..
256 * .. External Functions ..
257  LOGICAL lsame
258  EXTERNAL lsame
259 * ..
260 * .. External Subroutines ..
261  EXTERNAL chpevd, chpgst, cpptrf, ctpmv, ctpsv, xerbla
262 * ..
263 * .. Intrinsic Functions ..
264  INTRINSIC max, real
265 * ..
266 * .. Executable Statements ..
267 *
268 * Test the input parameters.
269 *
270  wantz = lsame( jobz, 'V' )
271  upper = lsame( uplo, 'U' )
272  lquery = ( lwork.EQ.-1 .OR. lrwork.EQ.-1 .OR. liwork.EQ.-1 )
273 *
274  info = 0
275  IF( itype.LT.1 .OR. itype.GT.3 ) THEN
276  info = -1
277  ELSE IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
278  info = -2
279  ELSE IF( .NOT.( upper .OR. lsame( uplo, 'L' ) ) ) THEN
280  info = -3
281  ELSE IF( n.LT.0 ) THEN
282  info = -4
283  ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
284  info = -9
285  END IF
286 *
287  IF( info.EQ.0 ) THEN
288  IF( n.LE.1 ) THEN
289  lwmin = 1
290  liwmin = 1
291  lrwmin = 1
292  ELSE
293  IF( wantz ) THEN
294  lwmin = 2*n
295  lrwmin = 1 + 5*n + 2*n**2
296  liwmin = 3 + 5*n
297  ELSE
298  lwmin = n
299  lrwmin = n
300  liwmin = 1
301  END IF
302  END IF
303 *
304  work( 1 ) = lwmin
305  rwork( 1 ) = lrwmin
306  iwork( 1 ) = liwmin
307  IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
308  info = -11
309  ELSE IF( lrwork.LT.lrwmin .AND. .NOT.lquery ) THEN
310  info = -13
311  ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
312  info = -15
313  END IF
314  END IF
315 *
316  IF( info.NE.0 ) THEN
317  CALL xerbla( 'CHPGVD', -info )
318  return
319  ELSE IF( lquery ) THEN
320  return
321  END IF
322 *
323 * Quick return if possible
324 *
325  IF( n.EQ.0 )
326  $ return
327 *
328 * Form a Cholesky factorization of B.
329 *
330  CALL cpptrf( uplo, n, bp, info )
331  IF( info.NE.0 ) THEN
332  info = n + info
333  return
334  END IF
335 *
336 * Transform problem to standard eigenvalue problem and solve.
337 *
338  CALL chpgst( itype, uplo, n, ap, bp, info )
339  CALL chpevd( jobz, uplo, n, ap, w, z, ldz, work, lwork, rwork,
340  $ lrwork, iwork, liwork, info )
341  lwmin = max( REAL( LWMIN ), REAL( WORK( 1 ) ) )
342  lrwmin = max( REAL( LRWMIN ), REAL( RWORK( 1 ) ) )
343  liwmin = max( REAL( LIWMIN ), REAL( IWORK( 1 ) ) )
344 *
345  IF( wantz ) THEN
346 *
347 * Backtransform eigenvectors to the original problem.
348 *
349  neig = n
350  IF( info.GT.0 )
351  $ neig = info - 1
352  IF( itype.EQ.1 .OR. itype.EQ.2 ) THEN
353 *
354 * For A*x=(lambda)*B*x and A*B*x=(lambda)*x;
355 * backtransform eigenvectors: x = inv(L)**H *y or inv(U)*y
356 *
357  IF( upper ) THEN
358  trans = 'N'
359  ELSE
360  trans = 'C'
361  END IF
362 *
363  DO 10 j = 1, neig
364  CALL ctpsv( uplo, trans, 'Non-unit', n, bp, z( 1, j ),
365  $ 1 )
366  10 continue
367 *
368  ELSE IF( itype.EQ.3 ) THEN
369 *
370 * For B*A*x=(lambda)*x;
371 * backtransform eigenvectors: x = L*y or U**H *y
372 *
373  IF( upper ) THEN
374  trans = 'C'
375  ELSE
376  trans = 'N'
377  END IF
378 *
379  DO 20 j = 1, neig
380  CALL ctpmv( uplo, trans, 'Non-unit', n, bp, z( 1, j ),
381  $ 1 )
382  20 continue
383  END IF
384  END IF
385 *
386  work( 1 ) = lwmin
387  rwork( 1 ) = lrwmin
388  iwork( 1 ) = liwmin
389  return
390 *
391 * End of CHPGVD
392 *
393  END