3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CHBGV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chbgv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chbgv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chbgv.f">
21 * SUBROUTINE CHBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
22 * LDZ, WORK, RWORK, INFO )
24 * .. Scalar Arguments ..
25 * CHARACTER JOBZ, UPLO
26 * INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
28 * .. Array Arguments ..
29 * REAL RWORK( * ), W( * )
30 * COMPLEX AB( LDAB, * ), BB( LDBB, * ), WORK( * ),
40 *> CHBGV computes all the eigenvalues, and optionally, the eigenvectors
41 *> of a complex generalized Hermitian-definite banded eigenproblem, of
42 *> the form A*x=(lambda)*B*x. Here A and B are assumed to be Hermitian
43 *> and banded, and B is also positive definite.
51 *> JOBZ is CHARACTER*1
52 *> = 'N': Compute eigenvalues only;
53 *> = 'V': Compute eigenvalues and eigenvectors.
58 *> UPLO is CHARACTER*1
59 *> = 'U': Upper triangles of A and B are stored;
60 *> = 'L': Lower triangles of A and B are stored.
66 *> The order of the matrices A and B. N >= 0.
72 *> The number of superdiagonals of the matrix A if UPLO = 'U',
73 *> or the number of subdiagonals if UPLO = 'L'. KA >= 0.
79 *> The number of superdiagonals of the matrix B if UPLO = 'U',
80 *> or the number of subdiagonals if UPLO = 'L'. KB >= 0.
85 *> AB is COMPLEX array, dimension (LDAB, N)
86 *> On entry, the upper or lower triangle of the Hermitian band
87 *> matrix A, stored in the first ka+1 rows of the array. The
88 *> j-th column of A is stored in the j-th column of the array AB
90 *> if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,j-ka)<=i<=j;
91 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+ka).
93 *> On exit, the contents of AB are destroyed.
99 *> The leading dimension of the array AB. LDAB >= KA+1.
104 *> BB is COMPLEX array, dimension (LDBB, N)
105 *> On entry, the upper or lower triangle of the Hermitian band
106 *> matrix B, stored in the first kb+1 rows of the array. The
107 *> j-th column of B is stored in the j-th column of the array BB
109 *> if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,j-kb)<=i<=j;
110 *> if UPLO = 'L', BB(1+i-j,j) = B(i,j) for j<=i<=min(n,j+kb).
112 *> On exit, the factor S from the split Cholesky factorization
113 *> B = S**H*S, as returned by CPBSTF.
119 *> The leading dimension of the array BB. LDBB >= KB+1.
124 *> W is REAL array, dimension (N)
125 *> If INFO = 0, the eigenvalues in ascending order.
130 *> Z is COMPLEX array, dimension (LDZ, N)
131 *> If JOBZ = 'V', then if INFO = 0, Z contains the matrix Z of
132 *> eigenvectors, with the i-th column of Z holding the
133 *> eigenvector associated with W(i). The eigenvectors are
134 *> normalized so that Z**H*B*Z = I.
135 *> If JOBZ = 'N', then Z is not referenced.
141 *> The leading dimension of the array Z. LDZ >= 1, and if
142 *> JOBZ = 'V', LDZ >= N.
147 *> WORK is COMPLEX array, dimension (N)
152 *> RWORK is REAL array, dimension (3*N)
158 *> = 0: successful exit
159 *> < 0: if INFO = -i, the i-th argument had an illegal value
160 *> > 0: if INFO = i, and i is:
161 *> <= N: the algorithm failed to converge:
162 *> i off-diagonal elements of an intermediate
163 *> tridiagonal form did not converge to zero;
164 *> > N: if INFO = N + i, for 1 <= i <= N, then CPBSTF
165 *> returned INFO = i: B is not positive definite.
166 *> The factorization of B could not be completed and
167 *> no eigenvalues or eigenvectors were computed.
173 *> \author Univ. of Tennessee
174 *> \author Univ. of California Berkeley
175 *> \author Univ. of Colorado Denver
178 *> \date November 2015
180 *> \ingroup complexOTHEReigen
182 * =====================================================================
183 SUBROUTINE CHBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
184 $ LDZ, WORK, RWORK, INFO )
186 * -- LAPACK driver routine (version 3.6.0) --
187 * -- LAPACK is a software package provided by Univ. of Tennessee, --
188 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
191 * .. Scalar Arguments ..
193 INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
195 * .. Array Arguments ..
196 REAL RWORK( * ), W( * )
197 COMPLEX AB( LDAB, * ), BB( LDBB, * ), WORK( * ),
201 * =====================================================================
203 * .. Local Scalars ..
206 INTEGER IINFO, INDE, INDWRK
208 * .. External Functions ..
212 * .. External Subroutines ..
213 EXTERNAL CHBGST, CHBTRD, CPBSTF, CSTEQR, SSTERF, XERBLA
215 * .. Executable Statements ..
217 * Test the input parameters.
219 WANTZ = LSAME( JOBZ, 'V' )
220 UPPER = LSAME( UPLO, 'U' )
223 IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
225 ELSE IF( .NOT.( UPPER .OR. LSAME( UPLO, 'L' ) ) ) THEN
227 ELSE IF( N.LT.0 ) THEN
229 ELSE IF( KA.LT.0 ) THEN
231 ELSE IF( KB.LT.0 .OR. KB.GT.KA ) THEN
233 ELSE IF( LDAB.LT.KA+1 ) THEN
235 ELSE IF( LDBB.LT.KB+1 ) THEN
237 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
241 CALL XERBLA( 'CHBGV ', -INFO )
245 * Quick return if possible
250 * Form a split Cholesky factorization of B.
252 CALL CPBSTF( UPLO, N, KB, BB, LDBB, INFO )
258 * Transform problem to standard eigenvalue problem.
262 CALL CHBGST( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, Z, LDZ,
263 $ WORK, RWORK( INDWRK ), IINFO )
265 * Reduce to tridiagonal form.
272 CALL CHBTRD( VECT, UPLO, N, KA, AB, LDAB, W, RWORK( INDE ), Z,
275 * For eigenvalues only, call SSTERF. For eigenvectors, call CSTEQR.
277 IF( .NOT.WANTZ ) THEN
278 CALL SSTERF( N, W, RWORK( INDE ), INFO )
280 CALL CSTEQR( JOBZ, N, W, RWORK( INDE ), Z, LDZ,
281 $ RWORK( INDWRK ), INFO )