1       SUBROUTINE ZHEEVX( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU,
  2      $                   ABSTOL, M, W, Z, LDZ, WORK, LWORK, 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 * @precisions normal z -> c
 10 *
 11 *     .. Scalar Arguments ..
 12       CHARACTER          JOBZ, RANGE, UPLO
 13       INTEGER            IL, INFO, IU, LDA, LDZ, LWORK, M, N
 14       DOUBLE PRECISION   ABSTOL, VL, VU
 15 *     ..
 16 *     .. Array Arguments ..
 17       INTEGER            IFAIL( * ), IWORK( * )
 18       DOUBLE PRECISION   RWORK( * ), W( * )
 19       COMPLEX*16         A( LDA, * ), WORK( * ), Z( LDZ, * )
 20 *     ..
 21 *
 22 *  Purpose
 23 *  =======
 24 *
 25 *  ZHEEVX computes selected eigenvalues and, optionally, eigenvectors
 26 *  of a complex Hermitian matrix A.  Eigenvalues and eigenvectors can
 27 *  be selected by specifying either a range of values or a range of
 28 *  indices for the desired eigenvalues.
 29 *
 30 *  Arguments
 31 *  =========
 32 *
 33 *  JOBZ    (input) CHARACTER*1
 34 *          = 'N':  Compute eigenvalues only;
 35 *          = 'V':  Compute eigenvalues and eigenvectors.
 36 *
 37 *  RANGE   (input) CHARACTER*1
 38 *          = 'A': all eigenvalues will be found.
 39 *          = 'V': all eigenvalues in the half-open interval (VL,VU]
 40 *                 will be found.
 41 *          = 'I': the IL-th through IU-th eigenvalues will be found.
 42 *
 43 *  UPLO    (input) CHARACTER*1
 44 *          = 'U':  Upper triangle of A is stored;
 45 *          = 'L':  Lower triangle of A is stored.
 46 *
 47 *  N       (input) INTEGER
 48 *          The order of the matrix A.  N >= 0.
 49 *
 50 *  A       (input/output) COMPLEX*16 array, dimension (LDA, N)
 51 *          On entry, the Hermitian matrix A.  If UPLO = 'U', the
 52 *          leading N-by-N upper triangular part of A contains the
 53 *          upper triangular part of the matrix A.  If UPLO = 'L',
 54 *          the leading N-by-N lower triangular part of A contains
 55 *          the lower triangular part of the matrix A.
 56 *          On exit, the lower triangle (if UPLO='L') or the upper
 57 *          triangle (if UPLO='U') of A, including the diagonal, is
 58 *          destroyed.
 59 *
 60 *  LDA     (input) INTEGER
 61 *          The leading dimension of the array A.  LDA >= max(1,N).
 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 A 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 *          On normal exit, the first M elements contain the selected
105 *          eigenvalues in ascending order.
106 *
107 *  Z       (output) COMPLEX*16 array, dimension (LDZ, max(1,M))
108 *          If JOBZ = 'V', then if INFO = 0, the first M columns of Z
109 *          contain the orthonormal eigenvectors of the matrix A
110 *          corresponding to the selected eigenvalues, with the i-th
111 *          column of Z holding the eigenvector associated with W(i).
112 *          If an eigenvector fails to converge, then that column of Z
113 *          contains the latest approximation to the eigenvector, and the
114 *          index of the eigenvector is returned in IFAIL.
115 *          If JOBZ = 'N', then Z is not referenced.
116 *          Note: the user must ensure that at least max(1,M) columns are
117 *          supplied in the array Z; if RANGE = 'V', the exact value of M
118 *          is not known in advance and an upper bound must be used.
119 *
120 *  LDZ     (input) INTEGER
121 *          The leading dimension of the array Z.  LDZ >= 1, and if
122 *          JOBZ = 'V', LDZ >= max(1,N).
123 *
124 *  WORK    (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
125 *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
126 *
127 *  LWORK   (input) INTEGER
128 *          The length of the array WORK.  LWORK >= 1, when N <= 1;
129 *          otherwise 2*N.
130 *          For optimal efficiency, LWORK >= (NB+1)*N,
131 *          where NB is the max of the blocksize for ZHETRD and for
132 *          ZUNMTR as returned by ILAENV.
133 *
134 *          If LWORK = -1, then a workspace query is assumed; the routine
135 *          only calculates the optimal size of the WORK array, returns
136 *          this value as the first entry of the WORK array, and no error
137 *          message related to LWORK is issued by XERBLA.
138 *
139 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (7*N)
140 *
141 *  IWORK   (workspace) INTEGER array, dimension (5*N)
142 *
143 *  IFAIL   (output) INTEGER array, dimension (N)
144 *          If JOBZ = 'V', then if INFO = 0, the first M elements of
145 *          IFAIL are zero.  If INFO > 0, then IFAIL contains the
146 *          indices of the eigenvectors that failed to converge.
147 *          If JOBZ = 'N', then IFAIL is not referenced.
148 *
149 *  INFO    (output) INTEGER
150 *          = 0:  successful exit
151 *          < 0:  if INFO = -i, the i-th argument had an illegal value
152 *          > 0:  if INFO = i, then i eigenvectors failed to converge.
153 *                Their indices are stored in array IFAIL.
154 *
155 *  =====================================================================
156 *
157 *     .. Parameters ..
158       DOUBLE PRECISION   ZERO, ONE
159       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
160       COMPLEX*16         CONE
161       PARAMETER          ( CONE = ( 1.0D+00.0D+0 ) )
162 *     ..
163 *     .. Local Scalars ..
164       LOGICAL            ALLEIG, INDEIG, LOWER, LQUERY, TEST, VALEIG,
165      $                   WANTZ
166       CHARACTER          ORDER
167       INTEGER            I, IINFO, IMAX, INDD, INDE, INDEE, INDIBL,
168      $                   INDISP, INDIWK, INDRWK, INDTAU, INDWRK, ISCALE,
169      $                   ITMP1, J, JJ, LLWORK, LWKMIN, LWKOPT, NB,
170      $                   NSPLIT
171       DOUBLE PRECISION   ABSTLL, ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN,
172      $                   SIGMA, SMLNUM, TMP1, VLL, VUU
173 *     ..
174 *     .. External Functions ..
175       LOGICAL            LSAME
176       INTEGER            ILAENV
177       DOUBLE PRECISION   DLAMCH, ZLANHE
178       EXTERNAL           LSAME, ILAENV, DLAMCH, ZLANHE
179 *     ..
180 *     .. External Subroutines ..
181       EXTERNAL           DCOPY, DSCAL, DSTEBZ, DSTERF, XERBLA, ZDSCAL,
182      $                   ZHETRD, ZLACPY, ZSTEIN, ZSTEQR, ZSWAP, ZUNGTR,
183      $                   ZUNMTR
184 *     ..
185 *     .. Intrinsic Functions ..
186       INTRINSIC          DBLEMAXMINSQRT
187 *     ..
188 *     .. Executable Statements ..
189 *
190 *     Test the input parameters.
191 *
192       LOWER = LSAME( UPLO, 'L' )
193       WANTZ = LSAME( JOBZ, 'V' )
194       ALLEIG = LSAME( RANGE'A' )
195       VALEIG = LSAME( RANGE'V' )
196       INDEIG = LSAME( RANGE'I' )
197       LQUERY = ( LWORK.EQ.-1 )
198 *
199       INFO = 0
200       IF.NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
201          INFO = -1
202       ELSE IF.NOT.( ALLEIG .OR. VALEIG .OR. INDEIG ) ) THEN
203          INFO = -2
204       ELSE IF.NOT.( LOWER .OR. LSAME( UPLO, 'U' ) ) ) THEN
205          INFO = -3
206       ELSE IF( N.LT.0 ) THEN
207          INFO = -4
208       ELSE IF( LDA.LT.MAX1, N ) ) THEN
209          INFO = -6
210       ELSE
211          IF( VALEIG ) THEN
212             IF( N.GT.0 .AND. VU.LE.VL )
213      $         INFO = -8
214          ELSE IF( INDEIG ) THEN
215             IF( IL.LT.1 .OR. IL.GT.MAX1, N ) ) THEN
216                INFO = -9
217             ELSE IF( IU.LT.MIN( N, IL ) .OR. IU.GT.N ) THEN
218                INFO = -10
219             END IF
220          END IF
221       END IF
222       IF( INFO.EQ.0 ) THEN
223          IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
224             INFO = -15
225          END IF
226       END IF
227 *
228       IF( INFO.EQ.0 ) THEN
229          IF( N.LE.1 ) THEN
230             LWKMIN = 1
231             WORK( 1 ) = LWKMIN
232          ELSE
233             LWKMIN = 2*N
234             NB = ILAENV( 1'ZHETRD', UPLO, N, -1-1-1 )
235             NB = MAX( NB, ILAENV( 1'ZUNMTR', UPLO, N, -1-1-1 ) )
236             LWKOPT = MAX1, ( NB + 1 )*N )
237             WORK( 1 ) = LWKOPT
238          END IF
239 *
240          IF( LWORK.LT.LWKMIN .AND. .NOT.LQUERY )
241      $      INFO = -17
242       END IF
243 *
244       IF( INFO.NE.0 ) THEN
245          CALL XERBLA( 'ZHEEVX'-INFO )
246          RETURN
247       ELSE IF( LQUERY ) THEN
248          RETURN
249       END IF
250 *
251 *     Quick return if possible
252 *
253       M = 0
254       IF( N.EQ.0 ) THEN
255          RETURN
256       END IF
257 *
258       IF( N.EQ.1 ) THEN
259          IF( ALLEIG .OR. INDEIG ) THEN
260             M = 1
261             W( 1 ) = A( 11 )
262          ELSE IF( VALEIG ) THEN
263             IF( VL.LT.DBLE( A( 11 ) ) .AND. VU.GE.DBLE( A( 11 ) ) )
264      $           THEN
265                M = 1
266                W( 1 ) = A( 11 )
267             END IF
268          END IF
269          IF( WANTZ )
270      $      Z( 11 ) = CONE
271          RETURN
272       END IF
273 *
274 *     Get machine constants.
275 *
276       SAFMIN = DLAMCH( 'Safe minimum' )
277       EPS = DLAMCH( 'Precision' )
278       SMLNUM = SAFMIN / EPS
279       BIGNUM = ONE / SMLNUM
280       RMIN = SQRT( SMLNUM )
281       RMAX = MINSQRT( BIGNUM ), ONE / SQRTSQRT( SAFMIN ) ) )
282 *
283 *     Scale matrix to allowable range, if necessary.
284 *
285       ISCALE = 0
286       ABSTLL = ABSTOL
287       IF( VALEIG ) THEN
288          VLL = VL
289          VUU = VU
290       END IF
291       ANRM = ZLANHE( 'M', UPLO, N, A, LDA, RWORK )
292       IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
293          ISCALE = 1
294          SIGMA = RMIN / ANRM
295       ELSE IF( ANRM.GT.RMAX ) THEN
296          ISCALE = 1
297          SIGMA = RMAX / ANRM
298       END IF
299       IF( ISCALE.EQ.1 ) THEN
300          IF( LOWER ) THEN
301             DO 10 J = 1, N
302                CALL ZDSCAL( N-J+1, SIGMA, A( J, J ), 1 )
303    10       CONTINUE
304          ELSE
305             DO 20 J = 1, N
306                CALL ZDSCAL( J, SIGMA, A( 1, J ), 1 )
307    20       CONTINUE
308          END IF
309          IF( ABSTOL.GT.0 )
310      $      ABSTLL = ABSTOL*SIGMA
311          IF( VALEIG ) THEN
312             VLL = VL*SIGMA
313             VUU = VU*SIGMA
314          END IF
315       END IF
316 *
317 *     Call ZHETRD to reduce Hermitian matrix to tridiagonal form.
318 *
319       INDD = 1
320       INDE = INDD + N
321       INDRWK = INDE + N
322       INDTAU = 1
323       INDWRK = INDTAU + N
324       LLWORK = LWORK - INDWRK + 1
325       CALL ZHETRD( UPLO, N, A, LDA, RWORK( INDD ), RWORK( INDE ),
326      $             WORK( INDTAU ), WORK( INDWRK ), LLWORK, IINFO )
327 *
328 *     If all eigenvalues are desired and ABSTOL is less than or equal to
329 *     zero, then call DSTERF or ZUNGTR and ZSTEQR.  If this fails for
330 *     some eigenvalue, then try DSTEBZ.
331 *
332       TEST = .FALSE.
333       IF( INDEIG ) THEN
334          IF( IL.EQ.1 .AND. IU.EQ.N ) THEN
335             TEST = .TRUE.
336          END IF
337       END IF
338       IF( ( ALLEIG .OR. TEST ) .AND. ( ABSTOL.LE.ZERO ) ) THEN
339          CALL DCOPY( N, RWORK( INDD ), 1, W, 1 )
340          INDEE = INDRWK + 2*N
341          IF.NOT.WANTZ ) THEN
342             CALL DCOPY( N-1, RWORK( INDE ), 1, RWORK( INDEE ), 1 )
343             CALL DSTERF( N, W, RWORK( INDEE ), INFO )
344          ELSE
345             CALL ZLACPY( 'A', N, N, A, LDA, Z, LDZ )
346             CALL ZUNGTR( UPLO, N, Z, LDZ, WORK( INDTAU ),
347      $                   WORK( INDWRK ), LLWORK, IINFO )
348             CALL DCOPY( N-1, RWORK( INDE ), 1, RWORK( INDEE ), 1 )
349             CALL ZSTEQR( JOBZ, N, W, RWORK( INDEE ), Z, LDZ,
350      $                   RWORK( INDRWK ), INFO )
351             IF( INFO.EQ.0 ) THEN
352                DO 30 I = 1, N
353                   IFAIL( I ) = 0
354    30          CONTINUE
355             END IF
356          END IF
357          IF( INFO.EQ.0 ) THEN
358             M = N
359             GO TO 40
360          END IF
361          INFO = 0
362       END IF
363 *
364 *     Otherwise, call DSTEBZ and, if eigenvectors are desired, ZSTEIN.
365 *
366       IF( WANTZ ) THEN
367          ORDER = 'B'
368       ELSE
369          ORDER = 'E'
370       END IF
371       INDIBL = 1
372       INDISP = INDIBL + N
373       INDIWK = INDISP + N
374       CALL DSTEBZ( RANGE, ORDER, N, VLL, VUU, IL, IU, ABSTLL,
375      $             RWORK( INDD ), RWORK( INDE ), M, NSPLIT, W,
376      $             IWORK( INDIBL ), IWORK( INDISP ), RWORK( INDRWK ),
377      $             IWORK( INDIWK ), INFO )
378 *
379       IF( WANTZ ) THEN
380          CALL ZSTEIN( N, RWORK( INDD ), RWORK( INDE ), M, W,
381      $                IWORK( INDIBL ), IWORK( INDISP ), Z, LDZ,
382      $                RWORK( INDRWK ), IWORK( INDIWK ), IFAIL, INFO )
383 *
384 *        Apply unitary matrix used in reduction to tridiagonal
385 *        form to eigenvectors returned by ZSTEIN.
386 *
387          CALL ZUNMTR( 'L', UPLO, 'N', N, M, A, LDA, WORK( INDTAU ), Z,
388      $                LDZ, WORK( INDWRK ), LLWORK, IINFO )
389       END IF
390 *
391 *     If matrix was scaled, then rescale eigenvalues appropriately.
392 *
393    40 CONTINUE
394       IF( ISCALE.EQ.1 ) THEN
395          IF( INFO.EQ.0 ) THEN
396             IMAX = M
397          ELSE
398             IMAX = INFO - 1
399          END IF
400          CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
401       END IF
402 *
403 *     If eigenvalues are not in order, then sort them, along with
404 *     eigenvectors.
405 *
406       IF( WANTZ ) THEN
407          DO 60 J = 1, M - 1
408             I = 0
409             TMP1 = W( J )
410             DO 50 JJ = J + 1, M
411                IF( W( JJ ).LT.TMP1 ) THEN
412                   I = JJ
413                   TMP1 = W( JJ )
414                END IF
415    50       CONTINUE
416 *
417             IF( I.NE.0 ) THEN
418                ITMP1 = IWORK( INDIBL+I-1 )
419                W( I ) = W( J )
420                IWORK( INDIBL+I-1 ) = IWORK( INDIBL+J-1 )
421                W( J ) = TMP1
422                IWORK( INDIBL+J-1 ) = ITMP1
423                CALL ZSWAP( N, Z( 1, I ), 1, Z( 1, J ), 1 )
424                IF( INFO.NE.0 ) THEN
425                   ITMP1 = IFAIL( I )
426                   IFAIL( I ) = IFAIL( J )
427                   IFAIL( J ) = ITMP1
428                END IF
429             END IF
430    60    CONTINUE
431       END IF
432 *
433 *     Set WORK(1) to optimal complex workspace size.
434 *
435       WORK( 1 ) = LWKOPT
436 *
437       RETURN
438 *
439 *     End of ZHEEVX
440 *
441       END