1       SUBROUTINE ZHPGVX( ITYPE, JOBZ, RANGE, UPLO, N, AP, BP, VL, VU,
  2      $                   IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK,
  3      $                   IWORK, IFAIL, INFO )
  4 *
  5 *  -- LAPACK driver routine (version 3.3.1) --
  6 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  7 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  8 *  -- April 2011                                                      --
  9 *
 10 *     .. Scalar Arguments ..
 11       CHARACTER          JOBZ, RANGE, UPLO
 12       INTEGER            IL, INFO, ITYPE, IU, LDZ, M, N
 13       DOUBLE PRECISION   ABSTOL, VL, VU
 14 *     ..
 15 *     .. Array Arguments ..
 16       INTEGER            IFAIL( * ), IWORK( * )
 17       DOUBLE PRECISION   RWORK( * ), W( * )
 18       COMPLEX*16         AP( * ), BP( * ), WORK( * ), Z( LDZ, * )
 19 *     ..
 20 *
 21 *  Purpose
 22 *  =======
 23 *
 24 *  ZHPGVX computes selected eigenvalues and, optionally, eigenvectors
 25 *  of a complex generalized Hermitian-definite eigenproblem, of the form
 26 *  A*x=(lambda)*B*x,  A*Bx=(lambda)*x,  or B*A*x=(lambda)*x.  Here A and
 27 *  B are assumed to be Hermitian, stored in packed format, and B is also
 28 *  positive definite.  Eigenvalues and eigenvectors can be selected by
 29 *  specifying either a range of values or a range of indices for the
 30 *  desired eigenvalues.
 31 *
 32 *  Arguments
 33 *  =========
 34 *
 35 *  ITYPE   (input) INTEGER
 36 *          Specifies the problem type to be solved:
 37 *          = 1:  A*x = (lambda)*B*x
 38 *          = 2:  A*B*x = (lambda)*x
 39 *          = 3:  B*A*x = (lambda)*x
 40 *
 41 *  JOBZ    (input) CHARACTER*1
 42 *          = 'N':  Compute eigenvalues only;
 43 *          = 'V':  Compute eigenvalues and eigenvectors.
 44 *
 45 *  RANGE   (input) CHARACTER*1
 46 *          = 'A': all eigenvalues will be found;
 47 *          = 'V': all eigenvalues in the half-open interval (VL,VU]
 48 *                 will be found;
 49 *          = 'I': the IL-th through IU-th eigenvalues will be found.
 50 *
 51 *  UPLO    (input) CHARACTER*1
 52 *          = 'U':  Upper triangles of A and B are stored;
 53 *          = 'L':  Lower triangles of A and B are stored.
 54 *
 55 *  N       (input) INTEGER
 56 *          The order of the matrices A and B.  N >= 0.
 57 *
 58 *  AP      (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
 59 *          On entry, the upper or lower triangle of the Hermitian matrix
 60 *          A, packed columnwise in a linear array.  The j-th column of A
 61 *          is stored in the array AP as follows:
 62 *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
 63 *          if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
 64 *
 65 *          On exit, the contents of AP are destroyed.
 66 *
 67 *  BP      (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
 68 *          On entry, the upper or lower triangle of the Hermitian matrix
 69 *          B, packed columnwise in a linear array.  The j-th column of B
 70 *          is stored in the array BP as follows:
 71 *          if UPLO = 'U', BP(i + (j-1)*j/2) = B(i,j) for 1<=i<=j;
 72 *          if UPLO = 'L', BP(i + (j-1)*(2*n-j)/2) = B(i,j) for j<=i<=n.
 73 *
 74 *          On exit, the triangular factor U or L from the Cholesky
 75 *          factorization B = U**H*U or B = L*L**H, in the same storage
 76 *          format as B.
 77 *
 78 *  VL      (input) DOUBLE PRECISION
 79 *  VU      (input) DOUBLE PRECISION
 80 *          If RANGE='V', the lower and upper bounds of the interval to
 81 *          be searched for eigenvalues. VL < VU.
 82 *          Not referenced if RANGE = 'A' or 'I'.
 83 *
 84 *  IL      (input) INTEGER
 85 *  IU      (input) INTEGER
 86 *          If RANGE='I', the indices (in ascending order) of the
 87 *          smallest and largest eigenvalues to be returned.
 88 *          1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
 89 *          Not referenced if RANGE = 'A' or 'V'.
 90 *
 91 *  ABSTOL  (input) DOUBLE PRECISION
 92 *          The absolute error tolerance for the eigenvalues.
 93 *          An approximate eigenvalue is accepted as converged
 94 *          when it is determined to lie in an interval [a,b]
 95 *          of width less than or equal to
 96 *
 97 *                  ABSTOL + EPS *   max( |a|,|b| ) ,
 98 *
 99 *          where EPS is the machine precision.  If ABSTOL is less than
100 *          or equal to zero, then  EPS*|T|  will be used in its place,
101 *          where |T| is the 1-norm of the tridiagonal matrix obtained
102 *          by reducing AP to tridiagonal form.
103 *
104 *          Eigenvalues will be computed most accurately when ABSTOL is
105 *          set to twice the underflow threshold 2*DLAMCH('S'), not zero.
106 *          If this routine returns with INFO>0, indicating that some
107 *          eigenvectors did not converge, try setting ABSTOL to
108 *          2*DLAMCH('S').
109 *
110 *  M       (output) INTEGER
111 *          The total number of eigenvalues found.  0 <= M <= N.
112 *          If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
113 *
114 *  W       (output) DOUBLE PRECISION array, dimension (N)
115 *          On normal exit, the first M elements contain the selected
116 *          eigenvalues in ascending order.
117 *
118 *  Z       (output) COMPLEX*16 array, dimension (LDZ, N)
119 *          If JOBZ = 'N', then Z is not referenced.
120 *          If JOBZ = 'V', then if INFO = 0, the first M columns of Z
121 *          contain the orthonormal eigenvectors of the matrix A
122 *          corresponding to the selected eigenvalues, with the i-th
123 *          column of Z holding the eigenvector associated with W(i).
124 *          The eigenvectors are normalized as follows:
125 *          if ITYPE = 1 or 2, Z**H*B*Z = I;
126 *          if ITYPE = 3, Z**H*inv(B)*Z = I.
127 *
128 *          If an eigenvector fails to converge, then that column of Z
129 *          contains the latest approximation to the eigenvector, and the
130 *          index of the eigenvector is returned in IFAIL.
131 *          Note: the user must ensure that at least max(1,M) columns are
132 *          supplied in the array Z; if RANGE = 'V', the exact value of M
133 *          is not known in advance and an upper bound must be used.
134 *
135 *  LDZ     (input) INTEGER
136 *          The leading dimension of the array Z.  LDZ >= 1, and if
137 *          JOBZ = 'V', LDZ >= max(1,N).
138 *
139 *  WORK    (workspace) COMPLEX*16 array, dimension (2*N)
140 *
141 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (7*N)
142 *
143 *  IWORK   (workspace) INTEGER array, dimension (5*N)
144 *
145 *  IFAIL   (output) INTEGER array, dimension (N)
146 *          If JOBZ = 'V', then if INFO = 0, the first M elements of
147 *          IFAIL are zero.  If INFO > 0, then IFAIL contains the
148 *          indices of the eigenvectors that failed to converge.
149 *          If JOBZ = 'N', then IFAIL is not referenced.
150 *
151 *  INFO    (output) INTEGER
152 *          = 0:  successful exit
153 *          < 0:  if INFO = -i, the i-th argument had an illegal value
154 *          > 0:  ZPPTRF or ZHPEVX returned an error code:
155 *             <= N:  if INFO = i, ZHPEVX failed to converge;
156 *                    i eigenvectors failed to converge.  Their indices
157 *                    are stored in array IFAIL.
158 *             > N:   if INFO = N + i, for 1 <= i <= n, then the leading
159 *                    minor of order i of B is not positive definite.
160 *                    The factorization of B could not be completed and
161 *                    no eigenvalues or eigenvectors were computed.
162 *
163 *  Further Details
164 *  ===============
165 *
166 *  Based on contributions by
167 *     Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
168 *
169 *  =====================================================================
170 *
171 *     .. Local Scalars ..
172       LOGICAL            ALLEIG, INDEIG, UPPER, VALEIG, WANTZ
173       CHARACTER          TRANS
174       INTEGER            J
175 *     ..
176 *     .. External Functions ..
177       LOGICAL            LSAME
178       EXTERNAL           LSAME
179 *     ..
180 *     .. External Subroutines ..
181       EXTERNAL           XERBLA, ZHPEVX, ZHPGST, ZPPTRF, ZTPMV, ZTPSV
182 *     ..
183 *     .. Intrinsic Functions ..
184       INTRINSIC          MIN
185 *     ..
186 *     .. Executable Statements ..
187 *
188 *     Test the input parameters.
189 *
190       WANTZ = LSAME( JOBZ, 'V' )
191       UPPER = LSAME( UPLO, 'U' )
192       ALLEIG = LSAME( RANGE'A' )
193       VALEIG = LSAME( RANGE'V' )
194       INDEIG = LSAME( RANGE'I' )
195 *
196       INFO = 0
197       IF( ITYPE.LT.1 .OR. ITYPE.GT.3 ) THEN
198          INFO = -1
199       ELSE IF.NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
200          INFO = -2
201       ELSE IF.NOT.( ALLEIG .OR. VALEIG .OR. INDEIG ) ) THEN
202          INFO = -3
203       ELSE IF.NOT.( UPPER .OR. LSAME( UPLO, 'L' ) ) ) THEN
204          INFO = -4
205       ELSE IF( N.LT.0 ) THEN
206          INFO = -5
207       ELSE 
208          IF( VALEIG ) THEN
209             IF( N.GT.0 .AND. VU.LE.VL ) THEN
210                INFO = -9
211             END IF
212          ELSE IF( INDEIG ) THEN
213             IF( IL.LT.1 ) THEN
214                INFO = -10
215             ELSE IF( IU.LT.MIN( N, IL ) .OR. IU.GT.N ) THEN
216                INFO = -11
217             END IF
218          END IF
219       END IF
220       IF( INFO.EQ.0 ) THEN
221          IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
222             INFO = -16
223          END IF
224       END IF
225 *
226       IF( INFO.NE.0 ) THEN
227          CALL XERBLA( 'ZHPGVX'-INFO )
228          RETURN
229       END IF
230 *
231 *     Quick return if possible
232 *
233       IF( N.EQ.0 )
234      $   RETURN
235 *
236 *     Form a Cholesky factorization of B.
237 *
238       CALL ZPPTRF( UPLO, N, BP, INFO )
239       IF( INFO.NE.0 ) THEN
240          INFO = N + INFO
241          RETURN
242       END IF
243 *
244 *     Transform problem to standard eigenvalue problem and solve.
245 *
246       CALL ZHPGST( ITYPE, UPLO, N, AP, BP, INFO )
247       CALL ZHPEVX( JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABSTOL, M,
248      $             W, Z, LDZ, WORK, RWORK, IWORK, IFAIL, INFO )
249 *
250       IF( WANTZ ) THEN
251 *
252 *        Backtransform eigenvectors to the original problem.
253 *
254          IF( INFO.GT.0 )
255      $      M = INFO - 1
256          IF( ITYPE.EQ.1 .OR. ITYPE.EQ.2 ) THEN
257 *
258 *           For A*x=(lambda)*B*x and A*B*x=(lambda)*x;
259 *           backtransform eigenvectors: x = inv(L)**H *y or inv(U)*y
260 *
261             IF( UPPER ) THEN
262                TRANS = 'N'
263             ELSE
264                TRANS = 'C'
265             END IF
266 *
267             DO 10 J = 1, M
268                CALL ZTPSV( UPLO, TRANS, 'Non-unit', N, BP, Z( 1, J ),
269      $                     1 )
270    10       CONTINUE
271 *
272          ELSE IF( ITYPE.EQ.3 ) THEN
273 *
274 *           For B*A*x=(lambda)*x;
275 *           backtransform eigenvectors: x = L*y or U**H *y
276 *
277             IF( UPPER ) THEN
278                TRANS = 'C'
279             ELSE
280                TRANS = 'N'
281             END IF
282 *
283             DO 20 J = 1, M
284                CALL ZTPMV( UPLO, TRANS, 'Non-unit', N, BP, Z( 1, J ),
285      $                     1 )
286    20       CONTINUE
287          END IF
288       END IF
289 *
290       RETURN
291 *
292 *     End of ZHPGVX
293 *
294       END