3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DSBGV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsbgv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsbgv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsbgv.f">
21 * SUBROUTINE DSBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
24 * .. Scalar Arguments ..
25 * CHARACTER JOBZ, UPLO
26 * INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
28 * .. Array Arguments ..
29 * DOUBLE PRECISION AB( LDAB, * ), BB( LDBB, * ), W( * ),
30 * $ WORK( * ), Z( LDZ, * )
39 *> DSBGV computes all the eigenvalues, and optionally, the eigenvectors
40 *> of a real generalized symmetric-definite banded eigenproblem, of
41 *> the form A*x=(lambda)*B*x. Here A and B are assumed to be symmetric
42 *> and banded, and B is also positive definite.
50 *> JOBZ is CHARACTER*1
51 *> = 'N': Compute eigenvalues only;
52 *> = 'V': Compute eigenvalues and eigenvectors.
57 *> UPLO is CHARACTER*1
58 *> = 'U': Upper triangles of A and B are stored;
59 *> = 'L': Lower triangles of A and B are stored.
65 *> The order of the matrices A and B. N >= 0.
71 *> The number of superdiagonals of the matrix A if UPLO = 'U',
72 *> or the number of subdiagonals if UPLO = 'L'. KA >= 0.
78 *> The number of superdiagonals of the matrix B if UPLO = 'U',
79 *> or the number of subdiagonals if UPLO = 'L'. KB >= 0.
84 *> AB is DOUBLE PRECISION array, dimension (LDAB, N)
85 *> On entry, the upper or lower triangle of the symmetric band
86 *> matrix A, stored in the first ka+1 rows of the array. The
87 *> j-th column of A is stored in the j-th column of the array AB
89 *> if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,j-ka)<=i<=j;
90 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+ka).
92 *> On exit, the contents of AB are destroyed.
98 *> The leading dimension of the array AB. LDAB >= KA+1.
103 *> BB is DOUBLE PRECISION array, dimension (LDBB, N)
104 *> On entry, the upper or lower triangle of the symmetric band
105 *> matrix B, stored in the first kb+1 rows of the array. The
106 *> j-th column of B is stored in the j-th column of the array BB
108 *> if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,j-kb)<=i<=j;
109 *> if UPLO = 'L', BB(1+i-j,j) = B(i,j) for j<=i<=min(n,j+kb).
111 *> On exit, the factor S from the split Cholesky factorization
112 *> B = S**T*S, as returned by DPBSTF.
118 *> The leading dimension of the array BB. LDBB >= KB+1.
123 *> W is DOUBLE PRECISION array, dimension (N)
124 *> If INFO = 0, the eigenvalues in ascending order.
129 *> Z is DOUBLE PRECISION array, dimension (LDZ, N)
130 *> If JOBZ = 'V', then if INFO = 0, Z contains the matrix Z of
131 *> eigenvectors, with the i-th column of Z holding the
132 *> eigenvector associated with W(i). The eigenvectors are
133 *> normalized so that Z**T*B*Z = I.
134 *> If JOBZ = 'N', then Z is not referenced.
140 *> The leading dimension of the array Z. LDZ >= 1, and if
141 *> JOBZ = 'V', LDZ >= N.
146 *> WORK is DOUBLE PRECISION array, dimension (3*N)
152 *> = 0: successful exit
153 *> < 0: if INFO = -i, the i-th argument had an illegal value
154 *> > 0: if INFO = i, and i is:
155 *> <= N: the algorithm failed to converge:
156 *> i off-diagonal elements of an intermediate
157 *> tridiagonal form did not converge to zero;
158 *> > N: if INFO = N + i, for 1 <= i <= N, then DPBSTF
159 *> returned INFO = i: B is not positive definite.
160 *> The factorization of B could not be completed and
161 *> no eigenvalues or eigenvectors were computed.
167 *> \author Univ. of Tennessee
168 *> \author Univ. of California Berkeley
169 *> \author Univ. of Colorado Denver
172 *> \date November 2015
174 *> \ingroup doubleOTHEReigen
176 * =====================================================================
177 SUBROUTINE DSBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
180 * -- LAPACK driver routine (version 3.6.0) --
181 * -- LAPACK is a software package provided by Univ. of Tennessee, --
182 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
185 * .. Scalar Arguments ..
187 INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
189 * .. Array Arguments ..
190 DOUBLE PRECISION AB( LDAB, * ), BB( LDBB, * ), W( * ),
191 $ WORK( * ), Z( LDZ, * )
194 * =====================================================================
196 * .. Local Scalars ..
199 INTEGER IINFO, INDE, INDWRK
201 * .. External Functions ..
205 * .. External Subroutines ..
206 EXTERNAL DPBSTF, DSBGST, DSBTRD, DSTEQR, DSTERF, XERBLA
208 * .. Executable Statements ..
210 * Test the input parameters.
212 WANTZ = LSAME( JOBZ, 'V' )
213 UPPER = LSAME( UPLO, 'U' )
216 IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
218 ELSE IF( .NOT.( UPPER .OR. LSAME( UPLO, 'L' ) ) ) THEN
220 ELSE IF( N.LT.0 ) THEN
222 ELSE IF( KA.LT.0 ) THEN
224 ELSE IF( KB.LT.0 .OR. KB.GT.KA ) THEN
226 ELSE IF( LDAB.LT.KA+1 ) THEN
228 ELSE IF( LDBB.LT.KB+1 ) THEN
230 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
234 CALL XERBLA( 'DSBGV ', -INFO )
238 * Quick return if possible
243 * Form a split Cholesky factorization of B.
245 CALL DPBSTF( UPLO, N, KB, BB, LDBB, INFO )
251 * Transform problem to standard eigenvalue problem.
255 CALL DSBGST( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, Z, LDZ,
256 $ WORK( INDWRK ), IINFO )
258 * Reduce to tridiagonal form.
265 CALL DSBTRD( VECT, UPLO, N, KA, AB, LDAB, W, WORK( INDE ), Z, LDZ,
266 $ WORK( INDWRK ), IINFO )
268 * For eigenvalues only, call DSTERF. For eigenvectors, call SSTEQR.
270 IF( .NOT.WANTZ ) THEN
271 CALL DSTERF( N, W, WORK( INDE ), INFO )
273 CALL DSTEQR( JOBZ, N, W, WORK( INDE ), Z, LDZ, WORK( INDWRK ),