1       SUBROUTINE ZHPEVX( JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU,
  2      $                   ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK,
  3      $                   IFAIL, INFO )
  4 *
  5 *  -- LAPACK driver routine (version 3.2) --
  6 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  7 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  8 *     November 2006
  9 *
 10 *     .. Scalar Arguments ..
 11       CHARACTER          JOBZ, RANGE, UPLO
 12       INTEGER            IL, INFO, 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( * ), WORK( * ), Z( LDZ, * )
 19 *     ..
 20 *
 21 *  Purpose
 22 *  =======
 23 *
 24 *  ZHPEVX computes selected eigenvalues and, optionally, eigenvectors
 25 *  of a complex Hermitian matrix A in packed storage.
 26 *  Eigenvalues/vectors can be selected by specifying either a range of
 27 *  values or a range of indices for the desired eigenvalues.
 28 *
 29 *  Arguments
 30 *  =========
 31 *
 32 *  JOBZ    (input) CHARACTER*1
 33 *          = 'N':  Compute eigenvalues only;
 34 *          = 'V':  Compute eigenvalues and eigenvectors.
 35 *
 36 *  RANGE   (input) CHARACTER*1
 37 *          = 'A': all eigenvalues will be found;
 38 *          = 'V': all eigenvalues in the half-open interval (VL,VU]
 39 *                 will be found;
 40 *          = 'I': the IL-th through IU-th eigenvalues will be found.
 41 *
 42 *  UPLO    (input) CHARACTER*1
 43 *          = 'U':  Upper triangle of A is stored;
 44 *          = 'L':  Lower triangle of A is stored.
 45 *
 46 *  N       (input) INTEGER
 47 *          The order of the matrix A.  N >= 0.
 48 *
 49 *  AP      (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
 50 *          On entry, the upper or lower triangle of the Hermitian matrix
 51 *          A, packed columnwise in a linear array.  The j-th column of A
 52 *          is stored in the array AP as follows:
 53 *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
 54 *          if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
 55 *
 56 *          On exit, AP is overwritten by values generated during the
 57 *          reduction to tridiagonal form.  If UPLO = 'U', the diagonal
 58 *          and first superdiagonal of the tridiagonal matrix T overwrite
 59 *          the corresponding elements of A, and if UPLO = 'L', the
 60 *          diagonal and first subdiagonal of T overwrite the
 61 *          corresponding elements of A.
 62 *
 63 *  VL      (input) DOUBLE PRECISION
 64 *  VU      (input) DOUBLE PRECISION
 65 *          If RANGE='V', the lower and upper bounds of the interval to
 66 *          be searched for eigenvalues. VL < VU.
 67 *          Not referenced if RANGE = 'A' or 'I'.
 68 *
 69 *  IL      (input) INTEGER
 70 *  IU      (input) INTEGER
 71 *          If RANGE='I', the indices (in ascending order) of the
 72 *          smallest and largest eigenvalues to be returned.
 73 *          1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
 74 *          Not referenced if RANGE = 'A' or 'V'.
 75 *
 76 *  ABSTOL  (input) DOUBLE PRECISION
 77 *          The absolute error tolerance for the eigenvalues.
 78 *          An approximate eigenvalue is accepted as converged
 79 *          when it is determined to lie in an interval [a,b]
 80 *          of width less than or equal to
 81 *
 82 *                  ABSTOL + EPS *   max( |a|,|b| ) ,
 83 *
 84 *          where EPS is the machine precision.  If ABSTOL is less than
 85 *          or equal to zero, then  EPS*|T|  will be used in its place,
 86 *          where |T| is the 1-norm of the tridiagonal matrix obtained
 87 *          by reducing AP to tridiagonal form.
 88 *
 89 *          Eigenvalues will be computed most accurately when ABSTOL is
 90 *          set to twice the underflow threshold 2*DLAMCH('S'), not zero.
 91 *          If this routine returns with INFO>0, indicating that some
 92 *          eigenvectors did not converge, try setting ABSTOL to
 93 *          2*DLAMCH('S').
 94 *
 95 *          See "Computing Small Singular Values of Bidiagonal Matrices
 96 *          with Guaranteed High Relative Accuracy," by Demmel and
 97 *          Kahan, LAPACK Working Note #3.
 98 *
 99 *  M       (output) INTEGER
100 *          The total number of eigenvalues found.  0 <= M <= N.
101 *          If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
102 *
103 *  W       (output) DOUBLE PRECISION array, dimension (N)
104 *          If INFO = 0, the selected eigenvalues in ascending order.
105 *
106 *  Z       (output) COMPLEX*16 array, dimension (LDZ, max(1,M))
107 *          If JOBZ = 'V', then if INFO = 0, the first M columns of Z
108 *          contain the orthonormal eigenvectors of the matrix A
109 *          corresponding to the selected eigenvalues, with the i-th
110 *          column of Z holding the eigenvector associated with W(i).
111 *          If an eigenvector fails to converge, then that column of Z
112 *          contains the latest approximation to the eigenvector, and
113 *          the index of the eigenvector is returned in IFAIL.
114 *          If JOBZ = 'N', then Z is not referenced.
115 *          Note: the user must ensure that at least max(1,M) columns are
116 *          supplied in the array Z; if RANGE = 'V', the exact value of M
117 *          is not known in advance and an upper bound must be used.
118 *
119 *  LDZ     (input) INTEGER
120 *          The leading dimension of the array Z.  LDZ >= 1, and if
121 *          JOBZ = 'V', LDZ >= max(1,N).
122 *
123 *  WORK    (workspace) COMPLEX*16 array, dimension (2*N)
124 *
125 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (7*N)
126 *
127 *  IWORK   (workspace) INTEGER array, dimension (5*N)
128 *
129 *  IFAIL   (output) INTEGER array, dimension (N)
130 *          If JOBZ = 'V', then if INFO = 0, the first M elements of
131 *          IFAIL are zero.  If INFO > 0, then IFAIL contains the
132 *          indices of the eigenvectors that failed to converge.
133 *          If JOBZ = 'N', then IFAIL is not referenced.
134 *
135 *  INFO    (output) INTEGER
136 *          = 0:  successful exit
137 *          < 0:  if INFO = -i, the i-th argument had an illegal value
138 *          > 0:  if INFO = i, then i eigenvectors failed to converge.
139 *                Their indices are stored in array IFAIL.
140 *
141 *  =====================================================================
142 *
143 *     .. Parameters ..
144       DOUBLE PRECISION   ZERO, ONE
145       PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0 )
146       COMPLEX*16         CONE
147       PARAMETER          ( CONE = ( 1.0D00.0D0 ) )
148 *     ..
149 *     .. Local Scalars ..
150       LOGICAL            ALLEIG, INDEIG, TEST, VALEIG, WANTZ
151       CHARACTER          ORDER
152       INTEGER            I, IINFO, IMAX, INDD, INDE, INDEE, INDIBL,
153      $                   INDISP, INDIWK, INDRWK, INDTAU, INDWRK, ISCALE,
154      $                   ITMP1, J, JJ, NSPLIT
155       DOUBLE PRECISION   ABSTLL, ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN,
156      $                   SIGMA, SMLNUM, TMP1, VLL, VUU
157 *     ..
158 *     .. External Functions ..
159       LOGICAL            LSAME
160       DOUBLE PRECISION   DLAMCH, ZLANHP
161       EXTERNAL           LSAME, DLAMCH, ZLANHP
162 *     ..
163 *     .. External Subroutines ..
164       EXTERNAL           DCOPY, DSCAL, DSTEBZ, DSTERF, XERBLA, ZDSCAL,
165      $                   ZHPTRD, ZSTEIN, ZSTEQR, ZSWAP, ZUPGTR, ZUPMTR
166 *     ..
167 *     .. Intrinsic Functions ..
168       INTRINSIC          DBLEMAXMINSQRT
169 *     ..
170 *     .. Executable Statements ..
171 *
172 *     Test the input parameters.
173 *
174       WANTZ = LSAME( JOBZ, 'V' )
175       ALLEIG = LSAME( RANGE'A' )
176       VALEIG = LSAME( RANGE'V' )
177       INDEIG = LSAME( RANGE'I' )
178 *
179       INFO = 0
180       IF.NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
181          INFO = -1
182       ELSE IF.NOT.( ALLEIG .OR. VALEIG .OR. INDEIG ) ) THEN
183          INFO = -2
184       ELSE IF.NOT.( LSAME( UPLO, 'L' ) .OR. LSAME( UPLO, 'U' ) ) )
185      $          THEN
186          INFO = -3
187       ELSE IF( N.LT.0 ) THEN
188          INFO = -4
189       ELSE
190          IF( VALEIG ) THEN
191             IF( N.GT.0 .AND. VU.LE.VL )
192      $         INFO = -7
193          ELSE IF( INDEIG ) THEN
194             IF( IL.LT.1 .OR. IL.GT.MAX1, N ) ) THEN
195                INFO = -8
196             ELSE IF( IU.LT.MIN( N, IL ) .OR. IU.GT.N ) THEN
197                INFO = -9
198             END IF
199          END IF
200       END IF
201       IF( INFO.EQ.0 ) THEN
202          IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) )
203      $      INFO = -14
204       END IF
205 *
206       IF( INFO.NE.0 ) THEN
207          CALL XERBLA( 'ZHPEVX'-INFO )
208          RETURN
209       END IF
210 *
211 *     Quick return if possible
212 *
213       M = 0
214       IF( N.EQ.0 )
215      $   RETURN
216 *
217       IF( N.EQ.1 ) THEN
218          IF( ALLEIG .OR. INDEIG ) THEN
219             M = 1
220             W( 1 ) = AP( 1 )
221          ELSE
222             IF( VL.LT.DBLE( AP( 1 ) ) .AND. VU.GE.DBLE( AP( 1 ) ) ) THEN
223                M = 1
224                W( 1 ) = AP( 1 )
225             END IF
226          END IF
227          IF( WANTZ )
228      $      Z( 11 ) = CONE
229          RETURN
230       END IF
231 *
232 *     Get machine constants.
233 *
234       SAFMIN = DLAMCH( 'Safe minimum' )
235       EPS = DLAMCH( 'Precision' )
236       SMLNUM = SAFMIN / EPS
237       BIGNUM = ONE / SMLNUM
238       RMIN = SQRT( SMLNUM )
239       RMAX = MINSQRT( BIGNUM ), ONE / SQRTSQRT( SAFMIN ) ) )
240 *
241 *     Scale matrix to allowable range, if necessary.
242 *
243       ISCALE = 0
244       ABSTLL = ABSTOL
245       IF( VALEIG ) THEN
246          VLL = VL
247          VUU = VU
248       ELSE
249          VLL = ZERO
250          VUU = ZERO
251       END IF
252       ANRM = ZLANHP( 'M', UPLO, N, AP, RWORK )
253       IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
254          ISCALE = 1
255          SIGMA = RMIN / ANRM
256       ELSE IF( ANRM.GT.RMAX ) THEN
257          ISCALE = 1
258          SIGMA = RMAX / ANRM
259       END IF
260       IF( ISCALE.EQ.1 ) THEN
261          CALL ZDSCAL( ( N*( N+1 ) ) / 2, SIGMA, AP, 1 )
262          IF( ABSTOL.GT.0 )
263      $      ABSTLL = ABSTOL*SIGMA
264          IF( VALEIG ) THEN
265             VLL = VL*SIGMA
266             VUU = VU*SIGMA
267          END IF
268       END IF
269 *
270 *     Call ZHPTRD to reduce Hermitian packed matrix to tridiagonal form.
271 *
272       INDD = 1
273       INDE = INDD + N
274       INDRWK = INDE + N
275       INDTAU = 1
276       INDWRK = INDTAU + N
277       CALL ZHPTRD( UPLO, N, AP, RWORK( INDD ), RWORK( INDE ),
278      $             WORK( INDTAU ), IINFO )
279 *
280 *     If all eigenvalues are desired and ABSTOL is less than or equal
281 *     to zero, then call DSTERF or ZUPGTR and ZSTEQR.  If this fails
282 *     for some eigenvalue, then try DSTEBZ.
283 *
284       TEST = .FALSE.
285       IF (INDEIG) THEN
286          IF (IL.EQ.1 .AND. IU.EQ.N) THEN
287             TEST = .TRUE.
288          END IF
289       END IF
290       IF ((ALLEIG .OR. TEST) .AND. (ABSTOL.LE.ZERO)) THEN
291          CALL DCOPY( N, RWORK( INDD ), 1, W, 1 )
292          INDEE = INDRWK + 2*N
293          IF.NOT.WANTZ ) THEN
294             CALL DCOPY( N-1, RWORK( INDE ), 1, RWORK( INDEE ), 1 )
295             CALL DSTERF( N, W, RWORK( INDEE ), INFO )
296          ELSE
297             CALL ZUPGTR( UPLO, N, AP, WORK( INDTAU ), Z, LDZ,
298      $                   WORK( INDWRK ), IINFO )
299             CALL DCOPY( N-1, RWORK( INDE ), 1, RWORK( INDEE ), 1 )
300             CALL ZSTEQR( JOBZ, N, W, RWORK( INDEE ), Z, LDZ,
301      $                   RWORK( INDRWK ), INFO )
302             IF( INFO.EQ.0 ) THEN
303                DO 10 I = 1, N
304                   IFAIL( I ) = 0
305    10          CONTINUE
306             END IF
307          END IF
308          IF( INFO.EQ.0 ) THEN
309             M = N
310             GO TO 20
311          END IF
312          INFO = 0
313       END IF
314 *
315 *     Otherwise, call DSTEBZ and, if eigenvectors are desired, ZSTEIN.
316 *
317       IF( WANTZ ) THEN
318          ORDER = 'B'
319       ELSE
320          ORDER = 'E'
321       END IF
322       INDIBL = 1
323       INDISP = INDIBL + N
324       INDIWK = INDISP + N
325       CALL DSTEBZ( RANGE, ORDER, N, VLL, VUU, IL, IU, ABSTLL,
326      $             RWORK( INDD ), RWORK( INDE ), M, NSPLIT, W,
327      $             IWORK( INDIBL ), IWORK( INDISP ), RWORK( INDRWK ),
328      $             IWORK( INDIWK ), INFO )
329 *
330       IF( WANTZ ) THEN
331          CALL ZSTEIN( N, RWORK( INDD ), RWORK( INDE ), M, W,
332      $                IWORK( INDIBL ), IWORK( INDISP ), Z, LDZ,
333      $                RWORK( INDRWK ), IWORK( INDIWK ), IFAIL, INFO )
334 *
335 *        Apply unitary matrix used in reduction to tridiagonal
336 *        form to eigenvectors returned by ZSTEIN.
337 *
338          INDWRK = INDTAU + N
339          CALL ZUPMTR( 'L', UPLO, 'N', N, M, AP, WORK( INDTAU ), Z, LDZ,
340      $                WORK( INDWRK ), IINFO )
341       END IF
342 *
343 *     If matrix was scaled, then rescale eigenvalues appropriately.
344 *
345    20 CONTINUE
346       IF( ISCALE.EQ.1 ) THEN
347          IF( INFO.EQ.0 ) THEN
348             IMAX = M
349          ELSE
350             IMAX = INFO - 1
351          END IF
352          CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
353       END IF
354 *
355 *     If eigenvalues are not in order, then sort them, along with
356 *     eigenvectors.
357 *
358       IF( WANTZ ) THEN
359          DO 40 J = 1, M - 1
360             I = 0
361             TMP1 = W( J )
362             DO 30 JJ = J + 1, M
363                IF( W( JJ ).LT.TMP1 ) THEN
364                   I = JJ
365                   TMP1 = W( JJ )
366                END IF
367    30       CONTINUE
368 *
369             IF( I.NE.0 ) THEN
370                ITMP1 = IWORK( INDIBL+I-1 )
371                W( I ) = W( J )
372                IWORK( INDIBL+I-1 ) = IWORK( INDIBL+J-1 )
373                W( J ) = TMP1
374                IWORK( INDIBL+J-1 ) = ITMP1
375                CALL ZSWAP( N, Z( 1, I ), 1, Z( 1, J ), 1 )
376                IF( INFO.NE.0 ) THEN
377                   ITMP1 = IFAIL( I )
378                   IFAIL( I ) = IFAIL( J )
379                   IFAIL( J ) = ITMP1
380                END IF
381             END IF
382    40    CONTINUE
383       END IF
384 *
385       RETURN
386 *
387 *     End of ZHPEVX
388 *
389       END