LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
chbgvx.f
Go to the documentation of this file.
1 *> \brief \b CHBGST
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CHBGVX + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chbgvx.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chbgvx.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chbgvx.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CHBGVX( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB,
22 * LDBB, Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z,
23 * LDZ, WORK, RWORK, IWORK, IFAIL, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER JOBZ, RANGE, UPLO
27 * INTEGER IL, INFO, IU, KA, KB, LDAB, LDBB, LDQ, LDZ, M,
28 * $ N
29 * REAL ABSTOL, VL, VU
30 * ..
31 * .. Array Arguments ..
32 * INTEGER IFAIL( * ), IWORK( * )
33 * REAL RWORK( * ), W( * )
34 * COMPLEX AB( LDAB, * ), BB( LDBB, * ), Q( LDQ, * ),
35 * $ WORK( * ), Z( LDZ, * )
36 * ..
37 *
38 *
39 *> \par Purpose:
40 * =============
41 *>
42 *> \verbatim
43 *>
44 *> CHBGVX computes all the eigenvalues, and optionally, the eigenvectors
45 *> of a complex generalized Hermitian-definite banded eigenproblem, of
46 *> the form A*x=(lambda)*B*x. Here A and B are assumed to be Hermitian
47 *> and banded, and B is also positive definite. Eigenvalues and
48 *> eigenvectors can be selected by specifying either all eigenvalues,
49 *> a range of values or a range of indices for the desired eigenvalues.
50 *> \endverbatim
51 *
52 * Arguments:
53 * ==========
54 *
55 *> \param[in] JOBZ
56 *> \verbatim
57 *> JOBZ is CHARACTER*1
58 *> = 'N': Compute eigenvalues only;
59 *> = 'V': Compute eigenvalues and eigenvectors.
60 *> \endverbatim
61 *>
62 *> \param[in] RANGE
63 *> \verbatim
64 *> RANGE is CHARACTER*1
65 *> = 'A': all eigenvalues will be found;
66 *> = 'V': all eigenvalues in the half-open interval (VL,VU]
67 *> will be found;
68 *> = 'I': the IL-th through IU-th eigenvalues will be found.
69 *> \endverbatim
70 *>
71 *> \param[in] UPLO
72 *> \verbatim
73 *> UPLO is CHARACTER*1
74 *> = 'U': Upper triangles of A and B are stored;
75 *> = 'L': Lower triangles of A and B are stored.
76 *> \endverbatim
77 *>
78 *> \param[in] N
79 *> \verbatim
80 *> N is INTEGER
81 *> The order of the matrices A and B. N >= 0.
82 *> \endverbatim
83 *>
84 *> \param[in] KA
85 *> \verbatim
86 *> KA is INTEGER
87 *> The number of superdiagonals of the matrix A if UPLO = 'U',
88 *> or the number of subdiagonals if UPLO = 'L'. KA >= 0.
89 *> \endverbatim
90 *>
91 *> \param[in] KB
92 *> \verbatim
93 *> KB is INTEGER
94 *> The number of superdiagonals of the matrix B if UPLO = 'U',
95 *> or the number of subdiagonals if UPLO = 'L'. KB >= 0.
96 *> \endverbatim
97 *>
98 *> \param[in,out] AB
99 *> \verbatim
100 *> AB is COMPLEX array, dimension (LDAB, N)
101 *> On entry, the upper or lower triangle of the Hermitian band
102 *> matrix A, stored in the first ka+1 rows of the array. The
103 *> j-th column of A is stored in the j-th column of the array AB
104 *> as follows:
105 *> if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,j-ka)<=i<=j;
106 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+ka).
107 *>
108 *> On exit, the contents of AB are destroyed.
109 *> \endverbatim
110 *>
111 *> \param[in] LDAB
112 *> \verbatim
113 *> LDAB is INTEGER
114 *> The leading dimension of the array AB. LDAB >= KA+1.
115 *> \endverbatim
116 *>
117 *> \param[in,out] BB
118 *> \verbatim
119 *> BB is COMPLEX array, dimension (LDBB, N)
120 *> On entry, the upper or lower triangle of the Hermitian band
121 *> matrix B, stored in the first kb+1 rows of the array. The
122 *> j-th column of B is stored in the j-th column of the array BB
123 *> as follows:
124 *> if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,j-kb)<=i<=j;
125 *> if UPLO = 'L', BB(1+i-j,j) = B(i,j) for j<=i<=min(n,j+kb).
126 *>
127 *> On exit, the factor S from the split Cholesky factorization
128 *> B = S**H*S, as returned by CPBSTF.
129 *> \endverbatim
130 *>
131 *> \param[in] LDBB
132 *> \verbatim
133 *> LDBB is INTEGER
134 *> The leading dimension of the array BB. LDBB >= KB+1.
135 *> \endverbatim
136 *>
137 *> \param[out] Q
138 *> \verbatim
139 *> Q is COMPLEX array, dimension (LDQ, N)
140 *> If JOBZ = 'V', the n-by-n matrix used in the reduction of
141 *> A*x = (lambda)*B*x to standard form, i.e. C*x = (lambda)*x,
142 *> and consequently C to tridiagonal form.
143 *> If JOBZ = 'N', the array Q is not referenced.
144 *> \endverbatim
145 *>
146 *> \param[in] LDQ
147 *> \verbatim
148 *> LDQ is INTEGER
149 *> The leading dimension of the array Q. If JOBZ = 'N',
150 *> LDQ >= 1. If JOBZ = 'V', LDQ >= max(1,N).
151 *> \endverbatim
152 *>
153 *> \param[in] VL
154 *> \verbatim
155 *> VL is REAL
156 *> \endverbatim
157 *>
158 *> \param[in] VU
159 *> \verbatim
160 *> VU is REAL
161 *>
162 *> If RANGE='V', the lower and upper bounds of the interval to
163 *> be searched for eigenvalues. VL < VU.
164 *> Not referenced if RANGE = 'A' or 'I'.
165 *> \endverbatim
166 *>
167 *> \param[in] IL
168 *> \verbatim
169 *> IL is INTEGER
170 *> \endverbatim
171 *>
172 *> \param[in] IU
173 *> \verbatim
174 *> IU is INTEGER
175 *>
176 *> If RANGE='I', the indices (in ascending order) of the
177 *> smallest and largest eigenvalues to be returned.
178 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
179 *> Not referenced if RANGE = 'A' or 'V'.
180 *> \endverbatim
181 *>
182 *> \param[in] ABSTOL
183 *> \verbatim
184 *> ABSTOL is REAL
185 *> The absolute error tolerance for the eigenvalues.
186 *> An approximate eigenvalue is accepted as converged
187 *> when it is determined to lie in an interval [a,b]
188 *> of width less than or equal to
189 *>
190 *> ABSTOL + EPS * max( |a|,|b| ) ,
191 *>
192 *> where EPS is the machine precision. If ABSTOL is less than
193 *> or equal to zero, then EPS*|T| will be used in its place,
194 *> where |T| is the 1-norm of the tridiagonal matrix obtained
195 *> by reducing AP to tridiagonal form.
196 *>
197 *> Eigenvalues will be computed most accurately when ABSTOL is
198 *> set to twice the underflow threshold 2*SLAMCH('S'), not zero.
199 *> If this routine returns with INFO>0, indicating that some
200 *> eigenvectors did not converge, try setting ABSTOL to
201 *> 2*SLAMCH('S').
202 *> \endverbatim
203 *>
204 *> \param[out] M
205 *> \verbatim
206 *> M is INTEGER
207 *> The total number of eigenvalues found. 0 <= M <= N.
208 *> If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
209 *> \endverbatim
210 *>
211 *> \param[out] W
212 *> \verbatim
213 *> W is REAL array, dimension (N)
214 *> If INFO = 0, the eigenvalues in ascending order.
215 *> \endverbatim
216 *>
217 *> \param[out] Z
218 *> \verbatim
219 *> Z is COMPLEX array, dimension (LDZ, N)
220 *> If JOBZ = 'V', then if INFO = 0, Z contains the matrix Z of
221 *> eigenvectors, with the i-th column of Z holding the
222 *> eigenvector associated with W(i). The eigenvectors are
223 *> normalized so that Z**H*B*Z = I.
224 *> If JOBZ = 'N', then Z is not referenced.
225 *> \endverbatim
226 *>
227 *> \param[in] LDZ
228 *> \verbatim
229 *> LDZ is INTEGER
230 *> The leading dimension of the array Z. LDZ >= 1, and if
231 *> JOBZ = 'V', LDZ >= N.
232 *> \endverbatim
233 *>
234 *> \param[out] WORK
235 *> \verbatim
236 *> WORK is COMPLEX array, dimension (N)
237 *> \endverbatim
238 *>
239 *> \param[out] RWORK
240 *> \verbatim
241 *> RWORK is REAL array, dimension (7*N)
242 *> \endverbatim
243 *>
244 *> \param[out] IWORK
245 *> \verbatim
246 *> IWORK is INTEGER array, dimension (5*N)
247 *> \endverbatim
248 *>
249 *> \param[out] IFAIL
250 *> \verbatim
251 *> IFAIL is INTEGER array, dimension (N)
252 *> If JOBZ = 'V', then if INFO = 0, the first M elements of
253 *> IFAIL are zero. If INFO > 0, then IFAIL contains the
254 *> indices of the eigenvectors that failed to converge.
255 *> If JOBZ = 'N', then IFAIL is not referenced.
256 *> \endverbatim
257 *>
258 *> \param[out] INFO
259 *> \verbatim
260 *> INFO is INTEGER
261 *> = 0: successful exit
262 *> < 0: if INFO = -i, the i-th argument had an illegal value
263 *> > 0: if INFO = i, and i is:
264 *> <= N: then i eigenvectors failed to converge. Their
265 *> indices are stored in array IFAIL.
266 *> > N: if INFO = N + i, for 1 <= i <= N, then CPBSTF
267 *> returned INFO = i: B is not positive definite.
268 *> The factorization of B could not be completed and
269 *> no eigenvalues or eigenvectors were computed.
270 *> \endverbatim
271 *
272 * Authors:
273 * ========
274 *
275 *> \author Univ. of Tennessee
276 *> \author Univ. of California Berkeley
277 *> \author Univ. of Colorado Denver
278 *> \author NAG Ltd.
279 *
280 *> \date November 2011
281 *
282 *> \ingroup complexOTHEReigen
283 *
284 *> \par Contributors:
285 * ==================
286 *>
287 *> Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
288 *
289 * =====================================================================
290  SUBROUTINE chbgvx( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB,
291  $ ldbb, q, ldq, vl, vu, il, iu, abstol, m, w, z,
292  $ ldz, work, rwork, iwork, ifail, info )
293 *
294 * -- LAPACK driver routine (version 3.4.0) --
295 * -- LAPACK is a software package provided by Univ. of Tennessee, --
296 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
297 * November 2011
298 *
299 * .. Scalar Arguments ..
300  CHARACTER jobz, range, uplo
301  INTEGER il, info, iu, ka, kb, ldab, ldbb, ldq, ldz, m,
302  $ n
303  REAL abstol, vl, vu
304 * ..
305 * .. Array Arguments ..
306  INTEGER ifail( * ), iwork( * )
307  REAL rwork( * ), w( * )
308  COMPLEX ab( ldab, * ), bb( ldbb, * ), q( ldq, * ),
309  $ work( * ), z( ldz, * )
310 * ..
311 *
312 * =====================================================================
313 *
314 * .. Parameters ..
315  REAL zero
316  parameter( zero = 0.0e+0 )
317  COMPLEX czero, cone
318  parameter( czero = ( 0.0e+0, 0.0e+0 ),
319  $ cone = ( 1.0e+0, 0.0e+0 ) )
320 * ..
321 * .. Local Scalars ..
322  LOGICAL alleig, indeig, test, upper, valeig, wantz
323  CHARACTER order, vect
324  INTEGER i, iinfo, indd, inde, indee, indibl, indisp,
325  $ indiwk, indrwk, indwrk, itmp1, j, jj, nsplit
326  REAL tmp1
327 * ..
328 * .. External Functions ..
329  LOGICAL lsame
330  EXTERNAL lsame
331 * ..
332 * .. External Subroutines ..
333  EXTERNAL ccopy, cgemv, chbgst, chbtrd, clacpy, cpbstf,
335  $ xerbla
336 * ..
337 * .. Intrinsic Functions ..
338  INTRINSIC min
339 * ..
340 * .. Executable Statements ..
341 *
342 * Test the input parameters.
343 *
344  wantz = lsame( jobz, 'V' )
345  upper = lsame( uplo, 'U' )
346  alleig = lsame( range, 'A' )
347  valeig = lsame( range, 'V' )
348  indeig = lsame( range, 'I' )
349 *
350  info = 0
351  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
352  info = -1
353  ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
354  info = -2
355  ELSE IF( .NOT.( upper .OR. lsame( uplo, 'L' ) ) ) THEN
356  info = -3
357  ELSE IF( n.LT.0 ) THEN
358  info = -4
359  ELSE IF( ka.LT.0 ) THEN
360  info = -5
361  ELSE IF( kb.LT.0 .OR. kb.GT.ka ) THEN
362  info = -6
363  ELSE IF( ldab.LT.ka+1 ) THEN
364  info = -8
365  ELSE IF( ldbb.LT.kb+1 ) THEN
366  info = -10
367  ELSE IF( ldq.LT.1 .OR. ( wantz .AND. ldq.LT.n ) ) THEN
368  info = -12
369  ELSE
370  IF( valeig ) THEN
371  IF( n.GT.0 .AND. vu.LE.vl )
372  $ info = -14
373  ELSE IF( indeig ) THEN
374  IF( il.LT.1 .OR. il.GT.max( 1, n ) ) THEN
375  info = -15
376  ELSE IF ( iu.LT.min( n, il ) .OR. iu.GT.n ) THEN
377  info = -16
378  END IF
379  END IF
380  END IF
381  IF( info.EQ.0) THEN
382  IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
383  info = -21
384  END IF
385  END IF
386 *
387  IF( info.NE.0 ) THEN
388  CALL xerbla( 'CHBGVX', -info )
389  return
390  END IF
391 *
392 * Quick return if possible
393 *
394  m = 0
395  IF( n.EQ.0 )
396  $ return
397 *
398 * Form a split Cholesky factorization of B.
399 *
400  CALL cpbstf( uplo, n, kb, bb, ldbb, info )
401  IF( info.NE.0 ) THEN
402  info = n + info
403  return
404  END IF
405 *
406 * Transform problem to standard eigenvalue problem.
407 *
408  CALL chbgst( jobz, uplo, n, ka, kb, ab, ldab, bb, ldbb, q, ldq,
409  $ work, rwork, iinfo )
410 *
411 * Solve the standard eigenvalue problem.
412 * Reduce Hermitian band matrix to tridiagonal form.
413 *
414  indd = 1
415  inde = indd + n
416  indrwk = inde + n
417  indwrk = 1
418  IF( wantz ) THEN
419  vect = 'U'
420  ELSE
421  vect = 'N'
422  END IF
423  CALL chbtrd( vect, uplo, n, ka, ab, ldab, rwork( indd ),
424  $ rwork( inde ), q, ldq, work( indwrk ), iinfo )
425 *
426 * If all eigenvalues are desired and ABSTOL is less than or equal
427 * to zero, then call SSTERF or CSTEQR. If this fails for some
428 * eigenvalue, then try SSTEBZ.
429 *
430  test = .false.
431  IF( indeig ) THEN
432  IF( il.EQ.1 .AND. iu.EQ.n ) THEN
433  test = .true.
434  END IF
435  END IF
436  IF( ( alleig .OR. test ) .AND. ( abstol.LE.zero ) ) THEN
437  CALL scopy( n, rwork( indd ), 1, w, 1 )
438  indee = indrwk + 2*n
439  CALL scopy( n-1, rwork( inde ), 1, rwork( indee ), 1 )
440  IF( .NOT.wantz ) THEN
441  CALL ssterf( n, w, rwork( indee ), info )
442  ELSE
443  CALL clacpy( 'A', n, n, q, ldq, z, ldz )
444  CALL csteqr( jobz, n, w, rwork( indee ), z, ldz,
445  $ rwork( indrwk ), info )
446  IF( info.EQ.0 ) THEN
447  DO 10 i = 1, n
448  ifail( i ) = 0
449  10 continue
450  END IF
451  END IF
452  IF( info.EQ.0 ) THEN
453  m = n
454  go to 30
455  END IF
456  info = 0
457  END IF
458 *
459 * Otherwise, call SSTEBZ and, if eigenvectors are desired,
460 * call CSTEIN.
461 *
462  IF( wantz ) THEN
463  order = 'B'
464  ELSE
465  order = 'E'
466  END IF
467  indibl = 1
468  indisp = indibl + n
469  indiwk = indisp + n
470  CALL sstebz( range, order, n, vl, vu, il, iu, abstol,
471  $ rwork( indd ), rwork( inde ), m, nsplit, w,
472  $ iwork( indibl ), iwork( indisp ), rwork( indrwk ),
473  $ iwork( indiwk ), info )
474 *
475  IF( wantz ) THEN
476  CALL cstein( n, rwork( indd ), rwork( inde ), m, w,
477  $ iwork( indibl ), iwork( indisp ), z, ldz,
478  $ rwork( indrwk ), iwork( indiwk ), ifail, info )
479 *
480 * Apply unitary matrix used in reduction to tridiagonal
481 * form to eigenvectors returned by CSTEIN.
482 *
483  DO 20 j = 1, m
484  CALL ccopy( n, z( 1, j ), 1, work( 1 ), 1 )
485  CALL cgemv( 'N', n, n, cone, q, ldq, work, 1, czero,
486  $ z( 1, j ), 1 )
487  20 continue
488  END IF
489 *
490  30 continue
491 *
492 * If eigenvalues are not in order, then sort them, along with
493 * eigenvectors.
494 *
495  IF( wantz ) THEN
496  DO 50 j = 1, m - 1
497  i = 0
498  tmp1 = w( j )
499  DO 40 jj = j + 1, m
500  IF( w( jj ).LT.tmp1 ) THEN
501  i = jj
502  tmp1 = w( jj )
503  END IF
504  40 continue
505 *
506  IF( i.NE.0 ) THEN
507  itmp1 = iwork( indibl+i-1 )
508  w( i ) = w( j )
509  iwork( indibl+i-1 ) = iwork( indibl+j-1 )
510  w( j ) = tmp1
511  iwork( indibl+j-1 ) = itmp1
512  CALL cswap( n, z( 1, i ), 1, z( 1, j ), 1 )
513  IF( info.NE.0 ) THEN
514  itmp1 = ifail( i )
515  ifail( i ) = ifail( j )
516  ifail( j ) = itmp1
517  END IF
518  END IF
519  50 continue
520  END IF
521 *
522  return
523 *
524 * End of CHBGVX
525 *
526  END