1 *> \brief <b> CGEEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for GE matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CGEEV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgeev.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgeev.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgeev.f">
21 * SUBROUTINE CGEEV( JOBVL, JOBVR, N, A, LDA, W, VL, LDVL, VR, LDVR,
22 * WORK, LWORK, RWORK, INFO )
24 * .. Scalar Arguments ..
25 * CHARACTER JOBVL, JOBVR
26 * INTEGER INFO, LDA, LDVL, LDVR, LWORK, N
28 * .. Array Arguments ..
30 * COMPLEX A( LDA, * ), VL( LDVL, * ), VR( LDVR, * ),
40 *> CGEEV computes for an N-by-N complex nonsymmetric matrix A, the
41 *> eigenvalues and, optionally, the left and/or right eigenvectors.
43 *> The right eigenvector v(j) of A satisfies
44 *> A * v(j) = lambda(j) * v(j)
45 *> where lambda(j) is its eigenvalue.
46 *> The left eigenvector u(j) of A satisfies
47 *> u(j)**H * A = lambda(j) * u(j)**H
48 *> where u(j)**H denotes the conjugate transpose of u(j).
50 *> The computed eigenvectors are normalized to have Euclidean norm
51 *> equal to 1 and largest component real.
59 *> JOBVL is CHARACTER*1
60 *> = 'N': left eigenvectors of A are not computed;
61 *> = 'V': left eigenvectors of are computed.
66 *> JOBVR is CHARACTER*1
67 *> = 'N': right eigenvectors of A are not computed;
68 *> = 'V': right eigenvectors of A are computed.
74 *> The order of the matrix A. N >= 0.
79 *> A is COMPLEX array, dimension (LDA,N)
80 *> On entry, the N-by-N matrix A.
81 *> On exit, A has been overwritten.
87 *> The leading dimension of the array A. LDA >= max(1,N).
92 *> W is COMPLEX array, dimension (N)
93 *> W contains the computed eigenvalues.
98 *> VL is COMPLEX array, dimension (LDVL,N)
99 *> If JOBVL = 'V', the left eigenvectors u(j) are stored one
100 *> after another in the columns of VL, in the same order
101 *> as their eigenvalues.
102 *> If JOBVL = 'N', VL is not referenced.
103 *> u(j) = VL(:,j), the j-th column of VL.
109 *> The leading dimension of the array VL. LDVL >= 1; if
110 *> JOBVL = 'V', LDVL >= N.
115 *> VR is COMPLEX array, dimension (LDVR,N)
116 *> If JOBVR = 'V', the right eigenvectors v(j) are stored one
117 *> after another in the columns of VR, in the same order
118 *> as their eigenvalues.
119 *> If JOBVR = 'N', VR is not referenced.
120 *> v(j) = VR(:,j), the j-th column of VR.
126 *> The leading dimension of the array VR. LDVR >= 1; if
127 *> JOBVR = 'V', LDVR >= N.
132 *> WORK is COMPLEX array, dimension (MAX(1,LWORK))
133 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
139 *> The dimension of the array WORK. LWORK >= max(1,2*N).
140 *> For good performance, LWORK must generally be larger.
142 *> If LWORK = -1, then a workspace query is assumed; the routine
143 *> only calculates the optimal size of the WORK array, returns
144 *> this value as the first entry of the WORK array, and no error
145 *> message related to LWORK is issued by XERBLA.
150 *> RWORK is REAL array, dimension (2*N)
156 *> = 0: successful exit
157 *> < 0: if INFO = -i, the i-th argument had an illegal value.
158 *> > 0: if INFO = i, the QR algorithm failed to compute all the
159 *> eigenvalues, and no eigenvectors have been computed;
160 *> elements and i+1:N of W contain eigenvalues which have
167 *> \author Univ. of Tennessee
168 *> \author Univ. of California Berkeley
169 *> \author Univ. of Colorado Denver
174 * @generated from zgeev.f, fortran z -> c, Tue Apr 19 01:47:44 2016
176 *> \ingroup complexGEeigen
178 * =====================================================================
179 SUBROUTINE CGEEV( JOBVL, JOBVR, N, A, LDA, W, VL, LDVL, VR, LDVR,
180 $ WORK, LWORK, RWORK, INFO )
183 * -- LAPACK driver routine (version 3.6.1) --
184 * -- LAPACK is a software package provided by Univ. of Tennessee, --
185 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
188 * .. Scalar Arguments ..
189 CHARACTER JOBVL, JOBVR
190 INTEGER INFO, LDA, LDVL, LDVR, LWORK, N
192 * .. Array Arguments ..
194 COMPLEX A( LDA, * ), VL( LDVL, * ), VR( LDVR, * ),
198 * =====================================================================
202 PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
204 * .. Local Scalars ..
205 LOGICAL LQUERY, SCALEA, WANTVL, WANTVR
207 INTEGER HSWORK, I, IBAL, IERR, IHI, ILO, IRWORK, ITAU,
208 $ IWRK, K, LWORK_TREVC, MAXWRK, MINWRK, NOUT
209 REAL ANRM, BIGNUM, CSCALE, EPS, SCL, SMLNUM
216 * .. External Subroutines ..
217 EXTERNAL SLABAD, XERBLA, CSSCAL, CGEBAK, CGEBAL, CGEHRD,
218 $ CHSEQR, CLACPY, CLASCL, CSCAL, CTREVC3, CUNGHR
220 * .. External Functions ..
222 INTEGER ISAMAX, ILAENV
223 REAL SLAMCH, SCNRM2, CLANGE
224 EXTERNAL LSAME, ISAMAX, ILAENV, SLAMCH, SCNRM2, CLANGE
226 * .. Intrinsic Functions ..
227 INTRINSIC REAL, CMPLX, CONJG, AIMAG, MAX, SQRT
229 * .. Executable Statements ..
231 * Test the input arguments
234 LQUERY = ( LWORK.EQ.-1 )
235 WANTVL = LSAME( JOBVL, 'V' )
236 WANTVR = LSAME( JOBVR, 'V' )
237 IF( ( .NOT.WANTVL ) .AND. ( .NOT.LSAME( JOBVL, 'N' ) ) ) THEN
239 ELSE IF( ( .NOT.WANTVR ) .AND. ( .NOT.LSAME( JOBVR, 'N' ) ) ) THEN
241 ELSE IF( N.LT.0 ) THEN
243 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
245 ELSE IF( LDVL.LT.1 .OR. ( WANTVL .AND. LDVL.LT.N ) ) THEN
247 ELSE IF( LDVR.LT.1 .OR. ( WANTVR .AND. LDVR.LT.N ) ) THEN
252 * (Note: Comments in the code beginning "Workspace:" describe the
253 * minimal amount of workspace needed at that point in the code,
254 * as well as the preferred amount for good performance.
255 * CWorkspace refers to complex workspace, and RWorkspace to real
256 * workspace. NB refers to the optimal block size for the
257 * immediately following subroutine, as returned by ILAENV.
258 * HSWORK refers to the workspace preferred by CHSEQR, as
259 * calculated below. HSWORK is computed assuming ILO=1 and IHI=N,
267 MAXWRK = N + N*ILAENV( 1, 'CGEHRD', ' ', N, 1, N, 0 )
270 MAXWRK = MAX( MAXWRK, N + ( N - 1 )*ILAENV( 1, 'CUNGHR',
271 $ ' ', N, 1, N, -1 ) )
272 CALL CTREVC3( 'L', 'B', SELECT, N, A, LDA,
273 $ VL, LDVL, VR, LDVR,
274 $ N, NOUT, WORK, -1, RWORK, -1, IERR )
275 LWORK_TREVC = INT( WORK(1) )
276 MAXWRK = MAX( MAXWRK, N + LWORK_TREVC )
277 CALL CHSEQR( 'S', 'V', N, 1, N, A, LDA, W, VL, LDVL,
279 ELSE IF( WANTVR ) THEN
280 MAXWRK = MAX( MAXWRK, N + ( N - 1 )*ILAENV( 1, 'CUNGHR',
281 $ ' ', N, 1, N, -1 ) )
282 CALL CTREVC3( 'R', 'B', SELECT, N, A, LDA,
283 $ VL, LDVL, VR, LDVR,
284 $ N, NOUT, WORK, -1, RWORK, -1, IERR )
285 LWORK_TREVC = INT( WORK(1) )
286 MAXWRK = MAX( MAXWRK, N + LWORK_TREVC )
287 CALL CHSEQR( 'S', 'V', N, 1, N, A, LDA, W, VR, LDVR,
290 CALL CHSEQR( 'E', 'N', N, 1, N, A, LDA, W, VR, LDVR,
293 HSWORK = INT( WORK(1) )
294 MAXWRK = MAX( MAXWRK, HSWORK, MINWRK )
298 IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN
304 CALL XERBLA( 'CGEEV ', -INFO )
306 ELSE IF( LQUERY ) THEN
310 * Quick return if possible
315 * Get machine constants
318 SMLNUM = SLAMCH( 'S' )
319 BIGNUM = ONE / SMLNUM
320 CALL SLABAD( SMLNUM, BIGNUM )
321 SMLNUM = SQRT( SMLNUM ) / EPS
322 BIGNUM = ONE / SMLNUM
324 * Scale A if max element outside range [SMLNUM,BIGNUM]
326 ANRM = CLANGE( 'M', N, N, A, LDA, DUM )
328 IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
331 ELSE IF( ANRM.GT.BIGNUM ) THEN
336 $ CALL CLASCL( 'G', 0, 0, ANRM, CSCALE, N, N, A, LDA, IERR )
340 * (RWorkspace: need N)
343 CALL CGEBAL( 'B', N, A, LDA, ILO, IHI, RWORK( IBAL ), IERR )
345 * Reduce to upper Hessenberg form
346 * (CWorkspace: need 2*N, prefer N+N*NB)
351 CALL CGEHRD( N, ILO, IHI, A, LDA, WORK( ITAU ), WORK( IWRK ),
352 $ LWORK-IWRK+1, IERR )
356 * Want left eigenvectors
357 * Copy Householder vectors to VL
360 CALL CLACPY( 'L', N, N, A, LDA, VL, LDVL )
362 * Generate unitary matrix in VL
363 * (CWorkspace: need 2*N-1, prefer N+(N-1)*NB)
366 CALL CUNGHR( N, ILO, IHI, VL, LDVL, WORK( ITAU ), WORK( IWRK ),
367 $ LWORK-IWRK+1, IERR )
369 * Perform QR iteration, accumulating Schur vectors in VL
370 * (CWorkspace: need 1, prefer HSWORK (see comments) )
374 CALL CHSEQR( 'S', 'V', N, ILO, IHI, A, LDA, W, VL, LDVL,
375 $ WORK( IWRK ), LWORK-IWRK+1, INFO )
379 * Want left and right eigenvectors
380 * Copy Schur vectors to VR
383 CALL CLACPY( 'F', N, N, VL, LDVL, VR, LDVR )
386 ELSE IF( WANTVR ) THEN
388 * Want right eigenvectors
389 * Copy Householder vectors to VR
392 CALL CLACPY( 'L', N, N, A, LDA, VR, LDVR )
394 * Generate unitary matrix in VR
395 * (CWorkspace: need 2*N-1, prefer N+(N-1)*NB)
398 CALL CUNGHR( N, ILO, IHI, VR, LDVR, WORK( ITAU ), WORK( IWRK ),
399 $ LWORK-IWRK+1, IERR )
401 * Perform QR iteration, accumulating Schur vectors in VR
402 * (CWorkspace: need 1, prefer HSWORK (see comments) )
406 CALL CHSEQR( 'S', 'V', N, ILO, IHI, A, LDA, W, VR, LDVR,
407 $ WORK( IWRK ), LWORK-IWRK+1, INFO )
411 * Compute eigenvalues only
412 * (CWorkspace: need 1, prefer HSWORK (see comments) )
416 CALL CHSEQR( 'E', 'N', N, ILO, IHI, A, LDA, W, VR, LDVR,
417 $ WORK( IWRK ), LWORK-IWRK+1, INFO )
420 * If INFO .NE. 0 from CHSEQR, then quit
425 IF( WANTVL .OR. WANTVR ) THEN
427 * Compute left and/or right eigenvectors
428 * (CWorkspace: need 2*N, prefer N + 2*N*NB)
429 * (RWorkspace: need 2*N)
432 CALL CTREVC3( SIDE, 'B', SELECT, N, A, LDA, VL, LDVL, VR, LDVR,
433 $ N, NOUT, WORK( IWRK ), LWORK-IWRK+1,
434 $ RWORK( IRWORK ), N, IERR )
439 * Undo balancing of left eigenvectors
441 * (RWorkspace: need N)
443 CALL CGEBAK( 'B', 'L', N, ILO, IHI, RWORK( IBAL ), N, VL, LDVL,
446 * Normalize left eigenvectors and make largest component real
449 SCL = ONE / SCNRM2( N, VL( 1, I ), 1 )
450 CALL CSSCAL( N, SCL, VL( 1, I ), 1 )
452 RWORK( IRWORK+K-1 ) = REAL( VL( K, I ) )**2 +
453 $ AIMAG( VL( K, I ) )**2
455 K = ISAMAX( N, RWORK( IRWORK ), 1 )
456 TMP = CONJG( VL( K, I ) ) / SQRT( RWORK( IRWORK+K-1 ) )
457 CALL CSCAL( N, TMP, VL( 1, I ), 1 )
458 VL( K, I ) = CMPLX( REAL( VL( K, I ) ), ZERO )
464 * Undo balancing of right eigenvectors
466 * (RWorkspace: need N)
468 CALL CGEBAK( 'B', 'R', N, ILO, IHI, RWORK( IBAL ), N, VR, LDVR,
471 * Normalize right eigenvectors and make largest component real
474 SCL = ONE / SCNRM2( N, VR( 1, I ), 1 )
475 CALL CSSCAL( N, SCL, VR( 1, I ), 1 )
477 RWORK( IRWORK+K-1 ) = REAL( VR( K, I ) )**2 +
478 $ AIMAG( VR( K, I ) )**2
480 K = ISAMAX( N, RWORK( IRWORK ), 1 )
481 TMP = CONJG( VR( K, I ) ) / SQRT( RWORK( IRWORK+K-1 ) )
482 CALL CSCAL( N, TMP, VR( 1, I ), 1 )
483 VR( K, I ) = CMPLX( REAL( VR( K, I ) ), ZERO )
487 * Undo scaling if necessary
491 CALL CLASCL( 'G', 0, 0, CSCALE, ANRM, N-INFO, 1, W( INFO+1 ),
492 $ MAX( N-INFO, 1 ), IERR )
494 CALL CLASCL( 'G', 0, 0, CSCALE, ANRM, ILO-1, 1, W, N, IERR )