LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ssbgv.f
Go to the documentation of this file.
1*> \brief \b SSBGV
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SSBGV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssbgv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssbgv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssbgv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SSBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
20* LDZ, WORK, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER JOBZ, UPLO
24* INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
25* ..
26* .. Array Arguments ..
27* REAL AB( LDAB, * ), BB( LDBB, * ), W( * ),
28* $ WORK( * ), Z( LDZ, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> SSBGV computes all the eigenvalues, and optionally, the eigenvectors
38*> of a real generalized symmetric-definite banded eigenproblem, of
39*> the form A*x=(lambda)*B*x. Here A and B are assumed to be symmetric
40*> and banded, and B is also positive definite.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] JOBZ
47*> \verbatim
48*> JOBZ is CHARACTER*1
49*> = 'N': Compute eigenvalues only;
50*> = 'V': Compute eigenvalues and eigenvectors.
51*> \endverbatim
52*>
53*> \param[in] UPLO
54*> \verbatim
55*> UPLO is CHARACTER*1
56*> = 'U': Upper triangles of A and B are stored;
57*> = 'L': Lower triangles of A and B are stored.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The order of the matrices A and B. N >= 0.
64*> \endverbatim
65*>
66*> \param[in] KA
67*> \verbatim
68*> KA is INTEGER
69*> The number of superdiagonals of the matrix A if UPLO = 'U',
70*> or the number of subdiagonals if UPLO = 'L'. KA >= 0.
71*> \endverbatim
72*>
73*> \param[in] KB
74*> \verbatim
75*> KB is INTEGER
76*> The number of superdiagonals of the matrix B if UPLO = 'U',
77*> or the number of subdiagonals if UPLO = 'L'. KB >= 0.
78*> \endverbatim
79*>
80*> \param[in,out] AB
81*> \verbatim
82*> AB is REAL array, dimension (LDAB, N)
83*> On entry, the upper or lower triangle of the symmetric band
84*> matrix A, stored in the first ka+1 rows of the array. The
85*> j-th column of A is stored in the j-th column of the array AB
86*> as follows:
87*> if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,j-ka)<=i<=j;
88*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+ka).
89*>
90*> On exit, the contents of AB are destroyed.
91*> \endverbatim
92*>
93*> \param[in] LDAB
94*> \verbatim
95*> LDAB is INTEGER
96*> The leading dimension of the array AB. LDAB >= KA+1.
97*> \endverbatim
98*>
99*> \param[in,out] BB
100*> \verbatim
101*> BB is REAL array, dimension (LDBB, N)
102*> On entry, the upper or lower triangle of the symmetric band
103*> matrix B, stored in the first kb+1 rows of the array. The
104*> j-th column of B is stored in the j-th column of the array BB
105*> as follows:
106*> if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,j-kb)<=i<=j;
107*> if UPLO = 'L', BB(1+i-j,j) = B(i,j) for j<=i<=min(n,j+kb).
108*>
109*> On exit, the factor S from the split Cholesky factorization
110*> B = S**T*S, as returned by SPBSTF.
111*> \endverbatim
112*>
113*> \param[in] LDBB
114*> \verbatim
115*> LDBB is INTEGER
116*> The leading dimension of the array BB. LDBB >= KB+1.
117*> \endverbatim
118*>
119*> \param[out] W
120*> \verbatim
121*> W is REAL array, dimension (N)
122*> If INFO = 0, the eigenvalues in ascending order.
123*> \endverbatim
124*>
125*> \param[out] Z
126*> \verbatim
127*> Z is REAL array, dimension (LDZ, N)
128*> If JOBZ = 'V', then if INFO = 0, Z contains the matrix Z of
129*> eigenvectors, with the i-th column of Z holding the
130*> eigenvector associated with W(i). The eigenvectors are
131*> normalized so that Z**T*B*Z = I.
132*> If JOBZ = 'N', then Z is not referenced.
133*> \endverbatim
134*>
135*> \param[in] LDZ
136*> \verbatim
137*> LDZ is INTEGER
138*> The leading dimension of the array Z. LDZ >= 1, and if
139*> JOBZ = 'V', LDZ >= N.
140*> \endverbatim
141*>
142*> \param[out] WORK
143*> \verbatim
144*> WORK is REAL array, dimension (3*N)
145*> \endverbatim
146*>
147*> \param[out] INFO
148*> \verbatim
149*> INFO is INTEGER
150*> = 0: successful exit
151*> < 0: if INFO = -i, the i-th argument had an illegal value
152*> > 0: if INFO = i, and i is:
153*> <= N: the algorithm failed to converge:
154*> i off-diagonal elements of an intermediate
155*> tridiagonal form did not converge to zero;
156*> > N: if INFO = N + i, for 1 <= i <= N, then SPBSTF
157*> returned INFO = i: B is not positive definite.
158*> The factorization of B could not be completed and
159*> no eigenvalues or eigenvectors were computed.
160*> \endverbatim
161*
162* Authors:
163* ========
164*
165*> \author Univ. of Tennessee
166*> \author Univ. of California Berkeley
167*> \author Univ. of Colorado Denver
168*> \author NAG Ltd.
169*
170*> \ingroup hbgv
171*
172* =====================================================================
173 SUBROUTINE ssbgv( JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W,
174 $ Z,
175 $ LDZ, WORK, INFO )
176*
177* -- LAPACK driver routine --
178* -- LAPACK is a software package provided by Univ. of Tennessee, --
179* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
180*
181* .. Scalar Arguments ..
182 CHARACTER JOBZ, UPLO
183 INTEGER INFO, KA, KB, LDAB, LDBB, LDZ, N
184* ..
185* .. Array Arguments ..
186 REAL AB( LDAB, * ), BB( LDBB, * ), W( * ),
187 $ WORK( * ), Z( LDZ, * )
188* ..
189*
190* =====================================================================
191*
192* .. Local Scalars ..
193 LOGICAL UPPER, WANTZ
194 CHARACTER VECT
195 INTEGER IINFO, INDE, INDWRK
196* ..
197* .. External Functions ..
198 LOGICAL LSAME
199 EXTERNAL LSAME
200* ..
201* .. External Subroutines ..
202 EXTERNAL spbstf, ssbgst, ssbtrd, ssteqr, ssterf,
203 $ xerbla
204* ..
205* .. Executable Statements ..
206*
207* Test the input parameters.
208*
209 wantz = lsame( jobz, 'V' )
210 upper = lsame( uplo, 'U' )
211*
212 info = 0
213 IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
214 info = -1
215 ELSE IF( .NOT.( upper .OR. lsame( uplo, 'L' ) ) ) THEN
216 info = -2
217 ELSE IF( n.LT.0 ) THEN
218 info = -3
219 ELSE IF( ka.LT.0 ) THEN
220 info = -4
221 ELSE IF( kb.LT.0 .OR. kb.GT.ka ) THEN
222 info = -5
223 ELSE IF( ldab.LT.ka+1 ) THEN
224 info = -7
225 ELSE IF( ldbb.LT.kb+1 ) THEN
226 info = -9
227 ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
228 info = -12
229 END IF
230 IF( info.NE.0 ) THEN
231 CALL xerbla( 'SSBGV', -info )
232 RETURN
233 END IF
234*
235* Quick return if possible
236*
237 IF( n.EQ.0 )
238 $ RETURN
239*
240* Form a split Cholesky factorization of B.
241*
242 CALL spbstf( uplo, n, kb, bb, ldbb, info )
243 IF( info.NE.0 ) THEN
244 info = n + info
245 RETURN
246 END IF
247*
248* Transform problem to standard eigenvalue problem.
249*
250 inde = 1
251 indwrk = inde + n
252 CALL ssbgst( jobz, uplo, n, ka, kb, ab, ldab, bb, ldbb, z, ldz,
253 $ work( indwrk ), iinfo )
254*
255* Reduce to tridiagonal form.
256*
257 IF( wantz ) THEN
258 vect = 'U'
259 ELSE
260 vect = 'N'
261 END IF
262 CALL ssbtrd( vect, uplo, n, ka, ab, ldab, w, work( inde ), z,
263 $ ldz,
264 $ work( indwrk ), iinfo )
265*
266* For eigenvalues only, call SSTERF. For eigenvectors, call SSTEQR.
267*
268 IF( .NOT.wantz ) THEN
269 CALL ssterf( n, w, work( inde ), info )
270 ELSE
271 CALL ssteqr( jobz, n, w, work( inde ), z, ldz,
272 $ work( indwrk ),
273 $ info )
274 END IF
275 RETURN
276*
277* End of SSBGV
278*
279 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssbgst(vect, uplo, n, ka, kb, ab, ldab, bb, ldbb, x, ldx, work, info)
SSBGST
Definition ssbgst.f:158
subroutine ssbgv(jobz, uplo, n, ka, kb, ab, ldab, bb, ldbb, w, z, ldz, work, info)
SSBGV
Definition ssbgv.f:176
subroutine ssbtrd(vect, uplo, n, kd, ab, ldab, d, e, q, ldq, work, info)
SSBTRD
Definition ssbtrd.f:161
subroutine spbstf(uplo, n, kd, ab, ldab, info)
SPBSTF
Definition spbstf.f:150
subroutine ssteqr(compz, n, d, e, z, ldz, work, info)
SSTEQR
Definition ssteqr.f:129
subroutine ssterf(n, d, e, info)
SSTERF
Definition ssterf.f:84