1 SUBROUTINE ZHPEVD( JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, LWORK,
2 $ RWORK, LRWORK, IWORK, LIWORK, INFO )
3 *
4 * -- LAPACK driver routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER JOBZ, UPLO
11 INTEGER INFO, LDZ, LIWORK, LRWORK, LWORK, N
12 * ..
13 * .. Array Arguments ..
14 INTEGER IWORK( * )
15 DOUBLE PRECISION RWORK( * ), W( * )
16 COMPLEX*16 AP( * ), WORK( * ), Z( LDZ, * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * ZHPEVD computes all the eigenvalues and, optionally, eigenvectors of
23 * a complex Hermitian matrix A in packed storage. If eigenvectors are
24 * desired, it uses a divide and conquer algorithm.
25 *
26 * The divide and conquer algorithm makes very mild assumptions about
27 * floating point arithmetic. It will work on machines with a guard
28 * digit in add/subtract, or on those binary machines without guard
29 * digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or
30 * Cray-2. It could conceivably fail on hexadecimal or decimal machines
31 * without guard digits, but we know of none.
32 *
33 * Arguments
34 * =========
35 *
36 * JOBZ (input) CHARACTER*1
37 * = 'N': Compute eigenvalues only;
38 * = 'V': Compute eigenvalues and eigenvectors.
39 *
40 * UPLO (input) CHARACTER*1
41 * = 'U': Upper triangle of A is stored;
42 * = 'L': Lower triangle of A is stored.
43 *
44 * N (input) INTEGER
45 * The order of the matrix A. N >= 0.
46 *
47 * AP (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
48 * On entry, the upper or lower triangle of the Hermitian matrix
49 * A, packed columnwise in a linear array. The j-th column of A
50 * is stored in the array AP as follows:
51 * if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
52 * if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
53 *
54 * On exit, AP is overwritten by values generated during the
55 * reduction to tridiagonal form. If UPLO = 'U', the diagonal
56 * and first superdiagonal of the tridiagonal matrix T overwrite
57 * the corresponding elements of A, and if UPLO = 'L', the
58 * diagonal and first subdiagonal of T overwrite the
59 * corresponding elements of A.
60 *
61 * W (output) DOUBLE PRECISION array, dimension (N)
62 * If INFO = 0, the eigenvalues in ascending order.
63 *
64 * Z (output) COMPLEX*16 array, dimension (LDZ, N)
65 * If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
66 * eigenvectors of the matrix A, with the i-th column of Z
67 * holding the eigenvector associated with W(i).
68 * If JOBZ = 'N', then Z is not referenced.
69 *
70 * LDZ (input) INTEGER
71 * The leading dimension of the array Z. LDZ >= 1, and if
72 * JOBZ = 'V', LDZ >= max(1,N).
73 *
74 * WORK (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
75 * On exit, if INFO = 0, WORK(1) returns the required LWORK.
76 *
77 * LWORK (input) INTEGER
78 * The dimension of array WORK.
79 * If N <= 1, LWORK must be at least 1.
80 * If JOBZ = 'N' and N > 1, LWORK must be at least N.
81 * If JOBZ = 'V' and N > 1, LWORK must be at least 2*N.
82 *
83 * If LWORK = -1, then a workspace query is assumed; the routine
84 * only calculates the required sizes of the WORK, RWORK and
85 * IWORK arrays, returns these values as the first entries of
86 * the WORK, RWORK and IWORK arrays, and no error message
87 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
88 *
89 * RWORK (workspace/output) DOUBLE PRECISION array,
90 * dimension (LRWORK)
91 * On exit, if INFO = 0, RWORK(1) returns the required LRWORK.
92 *
93 * LRWORK (input) INTEGER
94 * The dimension of array RWORK.
95 * If N <= 1, LRWORK must be at least 1.
96 * If JOBZ = 'N' and N > 1, LRWORK must be at least N.
97 * If JOBZ = 'V' and N > 1, LRWORK must be at least
98 * 1 + 5*N + 2*N**2.
99 *
100 * If LRWORK = -1, then a workspace query is assumed; the
101 * routine only calculates the required sizes of the WORK, RWORK
102 * and IWORK arrays, returns these values as the first entries
103 * of the WORK, RWORK and IWORK arrays, and no error message
104 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
105 *
106 * IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
107 * On exit, if INFO = 0, IWORK(1) returns the required LIWORK.
108 *
109 * LIWORK (input) INTEGER
110 * The dimension of array IWORK.
111 * If JOBZ = 'N' or N <= 1, LIWORK must be at least 1.
112 * If JOBZ = 'V' and N > 1, LIWORK must be at least 3 + 5*N.
113 *
114 * If LIWORK = -1, then a workspace query is assumed; the
115 * routine only calculates the required sizes of the WORK, RWORK
116 * and IWORK arrays, returns these values as the first entries
117 * of the WORK, RWORK and IWORK arrays, and no error message
118 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
119 *
120 * INFO (output) INTEGER
121 * = 0: successful exit
122 * < 0: if INFO = -i, the i-th argument had an illegal value.
123 * > 0: if INFO = i, the algorithm failed to converge; i
124 * off-diagonal elements of an intermediate tridiagonal
125 * form did not converge to zero.
126 *
127 * =====================================================================
128 *
129 * .. Parameters ..
130 DOUBLE PRECISION ZERO, ONE
131 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
132 COMPLEX*16 CONE
133 PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
134 * ..
135 * .. Local Scalars ..
136 LOGICAL LQUERY, WANTZ
137 INTEGER IINFO, IMAX, INDE, INDRWK, INDTAU, INDWRK,
138 $ ISCALE, LIWMIN, LLRWK, LLWRK, LRWMIN, LWMIN
139 DOUBLE PRECISION ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
140 $ SMLNUM
141 * ..
142 * .. External Functions ..
143 LOGICAL LSAME
144 DOUBLE PRECISION DLAMCH, ZLANHP
145 EXTERNAL LSAME, DLAMCH, ZLANHP
146 * ..
147 * .. External Subroutines ..
148 EXTERNAL DSCAL, DSTERF, XERBLA, ZDSCAL, ZHPTRD, ZSTEDC,
149 $ ZUPMTR
150 * ..
151 * .. Intrinsic Functions ..
152 INTRINSIC SQRT
153 * ..
154 * .. Executable Statements ..
155 *
156 * Test the input parameters.
157 *
158 WANTZ = LSAME( JOBZ, 'V' )
159 LQUERY = ( LWORK.EQ.-1 .OR. LRWORK.EQ.-1 .OR. LIWORK.EQ.-1 )
160 *
161 INFO = 0
162 IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
163 INFO = -1
164 ELSE IF( .NOT.( LSAME( UPLO, 'L' ) .OR. LSAME( UPLO, 'U' ) ) )
165 $ THEN
166 INFO = -2
167 ELSE IF( N.LT.0 ) THEN
168 INFO = -3
169 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
170 INFO = -7
171 END IF
172 *
173 IF( INFO.EQ.0 ) THEN
174 IF( N.LE.1 ) THEN
175 LWMIN = 1
176 LIWMIN = 1
177 LRWMIN = 1
178 ELSE
179 IF( WANTZ ) THEN
180 LWMIN = 2*N
181 LRWMIN = 1 + 5*N + 2*N**2
182 LIWMIN = 3 + 5*N
183 ELSE
184 LWMIN = N
185 LRWMIN = N
186 LIWMIN = 1
187 END IF
188 END IF
189 WORK( 1 ) = LWMIN
190 RWORK( 1 ) = LRWMIN
191 IWORK( 1 ) = LIWMIN
192 *
193 IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
194 INFO = -9
195 ELSE IF( LRWORK.LT.LRWMIN .AND. .NOT.LQUERY ) THEN
196 INFO = -11
197 ELSE IF( LIWORK.LT.LIWMIN .AND. .NOT.LQUERY ) THEN
198 INFO = -13
199 END IF
200 END IF
201 *
202 IF( INFO.NE.0 ) THEN
203 CALL XERBLA( 'ZHPEVD', -INFO )
204 RETURN
205 ELSE IF( LQUERY ) THEN
206 RETURN
207 END IF
208 *
209 * Quick return if possible
210 *
211 IF( N.EQ.0 )
212 $ RETURN
213 *
214 IF( N.EQ.1 ) THEN
215 W( 1 ) = AP( 1 )
216 IF( WANTZ )
217 $ Z( 1, 1 ) = CONE
218 RETURN
219 END IF
220 *
221 * Get machine constants.
222 *
223 SAFMIN = DLAMCH( 'Safe minimum' )
224 EPS = DLAMCH( 'Precision' )
225 SMLNUM = SAFMIN / EPS
226 BIGNUM = ONE / SMLNUM
227 RMIN = SQRT( SMLNUM )
228 RMAX = SQRT( BIGNUM )
229 *
230 * Scale matrix to allowable range, if necessary.
231 *
232 ANRM = ZLANHP( 'M', UPLO, N, AP, RWORK )
233 ISCALE = 0
234 IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
235 ISCALE = 1
236 SIGMA = RMIN / ANRM
237 ELSE IF( ANRM.GT.RMAX ) THEN
238 ISCALE = 1
239 SIGMA = RMAX / ANRM
240 END IF
241 IF( ISCALE.EQ.1 ) THEN
242 CALL ZDSCAL( ( N*( N+1 ) ) / 2, SIGMA, AP, 1 )
243 END IF
244 *
245 * Call ZHPTRD to reduce Hermitian packed matrix to tridiagonal form.
246 *
247 INDE = 1
248 INDTAU = 1
249 INDRWK = INDE + N
250 INDWRK = INDTAU + N
251 LLWRK = LWORK - INDWRK + 1
252 LLRWK = LRWORK - INDRWK + 1
253 CALL ZHPTRD( UPLO, N, AP, W, RWORK( INDE ), WORK( INDTAU ),
254 $ IINFO )
255 *
256 * For eigenvalues only, call DSTERF. For eigenvectors, first call
257 * ZUPGTR to generate the orthogonal matrix, then call ZSTEDC.
258 *
259 IF( .NOT.WANTZ ) THEN
260 CALL DSTERF( N, W, RWORK( INDE ), INFO )
261 ELSE
262 CALL ZSTEDC( 'I', N, W, RWORK( INDE ), Z, LDZ, WORK( INDWRK ),
263 $ LLWRK, RWORK( INDRWK ), LLRWK, IWORK, LIWORK,
264 $ INFO )
265 CALL ZUPMTR( 'L', UPLO, 'N', N, N, AP, WORK( INDTAU ), Z, LDZ,
266 $ WORK( INDWRK ), IINFO )
267 END IF
268 *
269 * If matrix was scaled, then rescale eigenvalues appropriately.
270 *
271 IF( ISCALE.EQ.1 ) THEN
272 IF( INFO.EQ.0 ) THEN
273 IMAX = N
274 ELSE
275 IMAX = INFO - 1
276 END IF
277 CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
278 END IF
279 *
280 WORK( 1 ) = LWMIN
281 RWORK( 1 ) = LRWMIN
282 IWORK( 1 ) = LIWMIN
283 RETURN
284 *
285 * End of ZHPEVD
286 *
287 END
2 $ RWORK, LRWORK, IWORK, LIWORK, INFO )
3 *
4 * -- LAPACK driver routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER JOBZ, UPLO
11 INTEGER INFO, LDZ, LIWORK, LRWORK, LWORK, N
12 * ..
13 * .. Array Arguments ..
14 INTEGER IWORK( * )
15 DOUBLE PRECISION RWORK( * ), W( * )
16 COMPLEX*16 AP( * ), WORK( * ), Z( LDZ, * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * ZHPEVD computes all the eigenvalues and, optionally, eigenvectors of
23 * a complex Hermitian matrix A in packed storage. If eigenvectors are
24 * desired, it uses a divide and conquer algorithm.
25 *
26 * The divide and conquer algorithm makes very mild assumptions about
27 * floating point arithmetic. It will work on machines with a guard
28 * digit in add/subtract, or on those binary machines without guard
29 * digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or
30 * Cray-2. It could conceivably fail on hexadecimal or decimal machines
31 * without guard digits, but we know of none.
32 *
33 * Arguments
34 * =========
35 *
36 * JOBZ (input) CHARACTER*1
37 * = 'N': Compute eigenvalues only;
38 * = 'V': Compute eigenvalues and eigenvectors.
39 *
40 * UPLO (input) CHARACTER*1
41 * = 'U': Upper triangle of A is stored;
42 * = 'L': Lower triangle of A is stored.
43 *
44 * N (input) INTEGER
45 * The order of the matrix A. N >= 0.
46 *
47 * AP (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
48 * On entry, the upper or lower triangle of the Hermitian matrix
49 * A, packed columnwise in a linear array. The j-th column of A
50 * is stored in the array AP as follows:
51 * if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
52 * if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
53 *
54 * On exit, AP is overwritten by values generated during the
55 * reduction to tridiagonal form. If UPLO = 'U', the diagonal
56 * and first superdiagonal of the tridiagonal matrix T overwrite
57 * the corresponding elements of A, and if UPLO = 'L', the
58 * diagonal and first subdiagonal of T overwrite the
59 * corresponding elements of A.
60 *
61 * W (output) DOUBLE PRECISION array, dimension (N)
62 * If INFO = 0, the eigenvalues in ascending order.
63 *
64 * Z (output) COMPLEX*16 array, dimension (LDZ, N)
65 * If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
66 * eigenvectors of the matrix A, with the i-th column of Z
67 * holding the eigenvector associated with W(i).
68 * If JOBZ = 'N', then Z is not referenced.
69 *
70 * LDZ (input) INTEGER
71 * The leading dimension of the array Z. LDZ >= 1, and if
72 * JOBZ = 'V', LDZ >= max(1,N).
73 *
74 * WORK (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
75 * On exit, if INFO = 0, WORK(1) returns the required LWORK.
76 *
77 * LWORK (input) INTEGER
78 * The dimension of array WORK.
79 * If N <= 1, LWORK must be at least 1.
80 * If JOBZ = 'N' and N > 1, LWORK must be at least N.
81 * If JOBZ = 'V' and N > 1, LWORK must be at least 2*N.
82 *
83 * If LWORK = -1, then a workspace query is assumed; the routine
84 * only calculates the required sizes of the WORK, RWORK and
85 * IWORK arrays, returns these values as the first entries of
86 * the WORK, RWORK and IWORK arrays, and no error message
87 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
88 *
89 * RWORK (workspace/output) DOUBLE PRECISION array,
90 * dimension (LRWORK)
91 * On exit, if INFO = 0, RWORK(1) returns the required LRWORK.
92 *
93 * LRWORK (input) INTEGER
94 * The dimension of array RWORK.
95 * If N <= 1, LRWORK must be at least 1.
96 * If JOBZ = 'N' and N > 1, LRWORK must be at least N.
97 * If JOBZ = 'V' and N > 1, LRWORK must be at least
98 * 1 + 5*N + 2*N**2.
99 *
100 * If LRWORK = -1, then a workspace query is assumed; the
101 * routine only calculates the required sizes of the WORK, RWORK
102 * and IWORK arrays, returns these values as the first entries
103 * of the WORK, RWORK and IWORK arrays, and no error message
104 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
105 *
106 * IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
107 * On exit, if INFO = 0, IWORK(1) returns the required LIWORK.
108 *
109 * LIWORK (input) INTEGER
110 * The dimension of array IWORK.
111 * If JOBZ = 'N' or N <= 1, LIWORK must be at least 1.
112 * If JOBZ = 'V' and N > 1, LIWORK must be at least 3 + 5*N.
113 *
114 * If LIWORK = -1, then a workspace query is assumed; the
115 * routine only calculates the required sizes of the WORK, RWORK
116 * and IWORK arrays, returns these values as the first entries
117 * of the WORK, RWORK and IWORK arrays, and no error message
118 * related to LWORK or LRWORK or LIWORK is issued by XERBLA.
119 *
120 * INFO (output) INTEGER
121 * = 0: successful exit
122 * < 0: if INFO = -i, the i-th argument had an illegal value.
123 * > 0: if INFO = i, the algorithm failed to converge; i
124 * off-diagonal elements of an intermediate tridiagonal
125 * form did not converge to zero.
126 *
127 * =====================================================================
128 *
129 * .. Parameters ..
130 DOUBLE PRECISION ZERO, ONE
131 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
132 COMPLEX*16 CONE
133 PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
134 * ..
135 * .. Local Scalars ..
136 LOGICAL LQUERY, WANTZ
137 INTEGER IINFO, IMAX, INDE, INDRWK, INDTAU, INDWRK,
138 $ ISCALE, LIWMIN, LLRWK, LLWRK, LRWMIN, LWMIN
139 DOUBLE PRECISION ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
140 $ SMLNUM
141 * ..
142 * .. External Functions ..
143 LOGICAL LSAME
144 DOUBLE PRECISION DLAMCH, ZLANHP
145 EXTERNAL LSAME, DLAMCH, ZLANHP
146 * ..
147 * .. External Subroutines ..
148 EXTERNAL DSCAL, DSTERF, XERBLA, ZDSCAL, ZHPTRD, ZSTEDC,
149 $ ZUPMTR
150 * ..
151 * .. Intrinsic Functions ..
152 INTRINSIC SQRT
153 * ..
154 * .. Executable Statements ..
155 *
156 * Test the input parameters.
157 *
158 WANTZ = LSAME( JOBZ, 'V' )
159 LQUERY = ( LWORK.EQ.-1 .OR. LRWORK.EQ.-1 .OR. LIWORK.EQ.-1 )
160 *
161 INFO = 0
162 IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN
163 INFO = -1
164 ELSE IF( .NOT.( LSAME( UPLO, 'L' ) .OR. LSAME( UPLO, 'U' ) ) )
165 $ THEN
166 INFO = -2
167 ELSE IF( N.LT.0 ) THEN
168 INFO = -3
169 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
170 INFO = -7
171 END IF
172 *
173 IF( INFO.EQ.0 ) THEN
174 IF( N.LE.1 ) THEN
175 LWMIN = 1
176 LIWMIN = 1
177 LRWMIN = 1
178 ELSE
179 IF( WANTZ ) THEN
180 LWMIN = 2*N
181 LRWMIN = 1 + 5*N + 2*N**2
182 LIWMIN = 3 + 5*N
183 ELSE
184 LWMIN = N
185 LRWMIN = N
186 LIWMIN = 1
187 END IF
188 END IF
189 WORK( 1 ) = LWMIN
190 RWORK( 1 ) = LRWMIN
191 IWORK( 1 ) = LIWMIN
192 *
193 IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
194 INFO = -9
195 ELSE IF( LRWORK.LT.LRWMIN .AND. .NOT.LQUERY ) THEN
196 INFO = -11
197 ELSE IF( LIWORK.LT.LIWMIN .AND. .NOT.LQUERY ) THEN
198 INFO = -13
199 END IF
200 END IF
201 *
202 IF( INFO.NE.0 ) THEN
203 CALL XERBLA( 'ZHPEVD', -INFO )
204 RETURN
205 ELSE IF( LQUERY ) THEN
206 RETURN
207 END IF
208 *
209 * Quick return if possible
210 *
211 IF( N.EQ.0 )
212 $ RETURN
213 *
214 IF( N.EQ.1 ) THEN
215 W( 1 ) = AP( 1 )
216 IF( WANTZ )
217 $ Z( 1, 1 ) = CONE
218 RETURN
219 END IF
220 *
221 * Get machine constants.
222 *
223 SAFMIN = DLAMCH( 'Safe minimum' )
224 EPS = DLAMCH( 'Precision' )
225 SMLNUM = SAFMIN / EPS
226 BIGNUM = ONE / SMLNUM
227 RMIN = SQRT( SMLNUM )
228 RMAX = SQRT( BIGNUM )
229 *
230 * Scale matrix to allowable range, if necessary.
231 *
232 ANRM = ZLANHP( 'M', UPLO, N, AP, RWORK )
233 ISCALE = 0
234 IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
235 ISCALE = 1
236 SIGMA = RMIN / ANRM
237 ELSE IF( ANRM.GT.RMAX ) THEN
238 ISCALE = 1
239 SIGMA = RMAX / ANRM
240 END IF
241 IF( ISCALE.EQ.1 ) THEN
242 CALL ZDSCAL( ( N*( N+1 ) ) / 2, SIGMA, AP, 1 )
243 END IF
244 *
245 * Call ZHPTRD to reduce Hermitian packed matrix to tridiagonal form.
246 *
247 INDE = 1
248 INDTAU = 1
249 INDRWK = INDE + N
250 INDWRK = INDTAU + N
251 LLWRK = LWORK - INDWRK + 1
252 LLRWK = LRWORK - INDRWK + 1
253 CALL ZHPTRD( UPLO, N, AP, W, RWORK( INDE ), WORK( INDTAU ),
254 $ IINFO )
255 *
256 * For eigenvalues only, call DSTERF. For eigenvectors, first call
257 * ZUPGTR to generate the orthogonal matrix, then call ZSTEDC.
258 *
259 IF( .NOT.WANTZ ) THEN
260 CALL DSTERF( N, W, RWORK( INDE ), INFO )
261 ELSE
262 CALL ZSTEDC( 'I', N, W, RWORK( INDE ), Z, LDZ, WORK( INDWRK ),
263 $ LLWRK, RWORK( INDRWK ), LLRWK, IWORK, LIWORK,
264 $ INFO )
265 CALL ZUPMTR( 'L', UPLO, 'N', N, N, AP, WORK( INDTAU ), Z, LDZ,
266 $ WORK( INDWRK ), IINFO )
267 END IF
268 *
269 * If matrix was scaled, then rescale eigenvalues appropriately.
270 *
271 IF( ISCALE.EQ.1 ) THEN
272 IF( INFO.EQ.0 ) THEN
273 IMAX = N
274 ELSE
275 IMAX = INFO - 1
276 END IF
277 CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
278 END IF
279 *
280 WORK( 1 ) = LWMIN
281 RWORK( 1 ) = LRWMIN
282 IWORK( 1 ) = LIWMIN
283 RETURN
284 *
285 * End of ZHPEVD
286 *
287 END