1 *> \brief <b> SGEES computes the eigenvalues, the Schur form, and, optionally, the matrix of Schur vectors for GE matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SGEES + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgees.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgees.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgees.f">
21 * SUBROUTINE SGEES( JOBVS, SORT, SELECT, N, A, LDA, SDIM, WR, WI,
22 * VS, LDVS, WORK, LWORK, BWORK, INFO )
24 * .. Scalar Arguments ..
25 * CHARACTER JOBVS, SORT
26 * INTEGER INFO, LDA, LDVS, LWORK, N, SDIM
28 * .. Array Arguments ..
30 * REAL A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ),
33 * .. Function Arguments ..
44 *> SGEES computes for an N-by-N real nonsymmetric matrix A, the
45 *> eigenvalues, the real Schur form T, and, optionally, the matrix of
46 *> Schur vectors Z. This gives the Schur factorization A = Z*T*(Z**T).
48 *> Optionally, it also orders the eigenvalues on the diagonal of the
49 *> real Schur form so that selected eigenvalues are at the top left.
50 *> The leading columns of Z then form an orthonormal basis for the
51 *> invariant subspace corresponding to the selected eigenvalues.
53 *> A matrix is in real Schur form if it is upper quasi-triangular with
54 *> 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will be standardized in the
59 *> where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
67 *> JOBVS is CHARACTER*1
68 *> = 'N': Schur vectors are not computed;
69 *> = 'V': Schur vectors are computed.
74 *> SORT is CHARACTER*1
75 *> Specifies whether or not to order the eigenvalues on the
76 *> diagonal of the Schur form.
77 *> = 'N': Eigenvalues are not ordered;
78 *> = 'S': Eigenvalues are ordered (see SELECT).
83 *> SELECT is LOGICAL FUNCTION of two REAL arguments
84 *> SELECT must be declared EXTERNAL in the calling subroutine.
85 *> If SORT = 'S', SELECT is used to select eigenvalues to sort
86 *> to the top left of the Schur form.
87 *> If SORT = 'N', SELECT is not referenced.
88 *> An eigenvalue WR(j)+sqrt(-1)*WI(j) is selected if
89 *> SELECT(WR(j),WI(j)) is true; i.e., if either one of a complex
90 *> conjugate pair of eigenvalues is selected, then both complex
91 *> eigenvalues are selected.
92 *> Note that a selected complex eigenvalue may no longer
93 *> satisfy SELECT(WR(j),WI(j)) = .TRUE. after ordering, since
94 *> ordering may change the value of complex eigenvalues
95 *> (especially if the eigenvalue is ill-conditioned); in this
96 *> case INFO is set to N+2 (see INFO below).
102 *> The order of the matrix A. N >= 0.
107 *> A is REAL array, dimension (LDA,N)
108 *> On entry, the N-by-N matrix A.
109 *> On exit, A has been overwritten by its real Schur form T.
115 *> The leading dimension of the array A. LDA >= max(1,N).
121 *> If SORT = 'N', SDIM = 0.
122 *> If SORT = 'S', SDIM = number of eigenvalues (after sorting)
123 *> for which SELECT is true. (Complex conjugate
124 *> pairs for which SELECT is true for either
125 *> eigenvalue count as 2.)
130 *> WR is REAL array, dimension (N)
135 *> WI is REAL array, dimension (N)
136 *> WR and WI contain the real and imaginary parts,
137 *> respectively, of the computed eigenvalues in the same order
138 *> that they appear on the diagonal of the output Schur form T.
139 *> Complex conjugate pairs of eigenvalues will appear
140 *> consecutively with the eigenvalue having the positive
141 *> imaginary part first.
146 *> VS is REAL array, dimension (LDVS,N)
147 *> If JOBVS = 'V', VS contains the orthogonal matrix Z of Schur
149 *> If JOBVS = 'N', VS is not referenced.
155 *> The leading dimension of the array VS. LDVS >= 1; if
156 *> JOBVS = 'V', LDVS >= N.
161 *> WORK is REAL array, dimension (MAX(1,LWORK))
162 *> On exit, if INFO = 0, WORK(1) contains the optimal LWORK.
168 *> The dimension of the array WORK. LWORK >= max(1,3*N).
169 *> For good performance, LWORK must generally be larger.
171 *> If LWORK = -1, then a workspace query is assumed; the routine
172 *> only calculates the optimal size of the WORK array, returns
173 *> this value as the first entry of the WORK array, and no error
174 *> message related to LWORK is issued by XERBLA.
179 *> BWORK is LOGICAL array, dimension (N)
180 *> Not referenced if SORT = 'N'.
186 *> = 0: successful exit
187 *> < 0: if INFO = -i, the i-th argument had an illegal value.
188 *> > 0: if INFO = i, and i is
189 *> <= N: the QR algorithm failed to compute all the
190 *> eigenvalues; elements 1:ILO-1 and i+1:N of WR and WI
191 *> contain those eigenvalues which have converged; if
192 *> JOBVS = 'V', VS contains the matrix which reduces A
193 *> to its partially converged Schur form.
194 *> = N+1: the eigenvalues could not be reordered because some
195 *> eigenvalues were too close to separate (the problem
196 *> is very ill-conditioned);
197 *> = N+2: after reordering, roundoff changed values of some
198 *> complex eigenvalues so that leading eigenvalues in
199 *> the Schur form no longer satisfy SELECT=.TRUE. This
200 *> could also be caused by underflow due to scaling.
206 *> \author Univ. of Tennessee
207 *> \author Univ. of California Berkeley
208 *> \author Univ. of Colorado Denver
211 *> \date November 2011
213 *> \ingroup realGEeigen
215 * =====================================================================
216 SUBROUTINE SGEES( JOBVS, SORT, SELECT, N, A, LDA, SDIM, WR, WI,
217 $ VS, LDVS, WORK, LWORK, BWORK, INFO )
219 * -- LAPACK driver routine (version 3.4.0) --
220 * -- LAPACK is a software package provided by Univ. of Tennessee, --
221 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
224 * .. Scalar Arguments ..
225 CHARACTER JOBVS, SORT
226 INTEGER INFO, LDA, LDVS, LWORK, N, SDIM
228 * .. Array Arguments ..
230 REAL A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ),
233 * .. Function Arguments ..
238 * =====================================================================
242 PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
244 * .. Local Scalars ..
245 LOGICAL CURSL, LASTSL, LQUERY, LST2SL, SCALEA, WANTST,
247 INTEGER HSWORK, I, I1, I2, IBAL, ICOND, IERR, IEVAL,
248 $ IHI, ILO, INXT, IP, ITAU, IWRK, MAXWRK, MINWRK
249 REAL ANRM, BIGNUM, CSCALE, EPS, S, SEP, SMLNUM
255 * .. External Subroutines ..
256 EXTERNAL SCOPY, SGEBAK, SGEBAL, SGEHRD, SHSEQR, SLABAD,
257 $ SLACPY, SLASCL, SORGHR, SSWAP, STRSEN, XERBLA
259 * .. External Functions ..
263 EXTERNAL LSAME, ILAENV, SLAMCH, SLANGE
265 * .. Intrinsic Functions ..
268 * .. Executable Statements ..
270 * Test the input arguments
273 LQUERY = ( LWORK.EQ.-1 )
274 WANTVS = LSAME( JOBVS, 'V' )
275 WANTST = LSAME( SORT, 'S' )
276 IF( ( .NOT.WANTVS ) .AND. ( .NOT.LSAME( JOBVS, 'N' ) ) ) THEN
278 ELSE IF( ( .NOT.WANTST ) .AND. ( .NOT.LSAME( SORT, 'N' ) ) ) THEN
280 ELSE IF( N.LT.0 ) THEN
282 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
284 ELSE IF( LDVS.LT.1 .OR. ( WANTVS .AND. LDVS.LT.N ) ) THEN
289 * (Note: Comments in the code beginning "Workspace:" describe the
290 * minimal amount of workspace needed at that point in the code,
291 * as well as the preferred amount for good performance.
292 * NB refers to the optimal block size for the immediately
293 * following subroutine, as returned by ILAENV.
294 * HSWORK refers to the workspace preferred by SHSEQR, as
295 * calculated below. HSWORK is computed assuming ILO=1 and IHI=N,
303 MAXWRK = 2*N + N*ILAENV( 1, 'SGEHRD', ' ', N, 1, N, 0 )
306 CALL SHSEQR( 'S', JOBVS, N, 1, N, A, LDA, WR, WI, VS, LDVS,
310 IF( .NOT.WANTVS ) THEN
311 MAXWRK = MAX( MAXWRK, N + HSWORK )
313 MAXWRK = MAX( MAXWRK, 2*N + ( N - 1 )*ILAENV( 1,
314 $ 'SORGHR', ' ', N, 1, N, -1 ) )
315 MAXWRK = MAX( MAXWRK, N + HSWORK )
320 IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN
326 CALL XERBLA( 'SGEES ', -INFO )
328 ELSE IF( LQUERY ) THEN
332 * Quick return if possible
339 * Get machine constants
342 SMLNUM = SLAMCH( 'S' )
343 BIGNUM = ONE / SMLNUM
344 CALL SLABAD( SMLNUM, BIGNUM )
345 SMLNUM = SQRT( SMLNUM ) / EPS
346 BIGNUM = ONE / SMLNUM
348 * Scale A if max element outside range [SMLNUM,BIGNUM]
350 ANRM = SLANGE( 'M', N, N, A, LDA, DUM )
352 IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
355 ELSE IF( ANRM.GT.BIGNUM ) THEN
360 $ CALL SLASCL( 'G', 0, 0, ANRM, CSCALE, N, N, A, LDA, IERR )
362 * Permute the matrix to make it more nearly triangular
363 * (Workspace: need N)
366 CALL SGEBAL( 'P', N, A, LDA, ILO, IHI, WORK( IBAL ), IERR )
368 * Reduce to upper Hessenberg form
369 * (Workspace: need 3*N, prefer 2*N+N*NB)
373 CALL SGEHRD( N, ILO, IHI, A, LDA, WORK( ITAU ), WORK( IWRK ),
374 $ LWORK-IWRK+1, IERR )
378 * Copy Householder vectors to VS
380 CALL SLACPY( 'L', N, N, A, LDA, VS, LDVS )
382 * Generate orthogonal matrix in VS
383 * (Workspace: need 3*N-1, prefer 2*N+(N-1)*NB)
385 CALL SORGHR( N, ILO, IHI, VS, LDVS, WORK( ITAU ), WORK( IWRK ),
386 $ LWORK-IWRK+1, IERR )
391 * Perform QR iteration, accumulating Schur vectors in VS if desired
392 * (Workspace: need N+1, prefer N+HSWORK (see comments) )
395 CALL SHSEQR( 'S', JOBVS, N, ILO, IHI, A, LDA, WR, WI, VS, LDVS,
396 $ WORK( IWRK ), LWORK-IWRK+1, IEVAL )
400 * Sort eigenvalues if desired
402 IF( WANTST .AND. INFO.EQ.0 ) THEN
404 CALL SLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WR, N, IERR )
405 CALL SLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WI, N, IERR )
408 BWORK( I ) = SELECT( WR( I ), WI( I ) )
411 * Reorder eigenvalues and transform Schur vectors
412 * (Workspace: none needed)
414 CALL STRSEN( 'N', JOBVS, BWORK, N, A, LDA, VS, LDVS, WR, WI,
415 $ SDIM, S, SEP, WORK( IWRK ), LWORK-IWRK+1, IDUM, 1,
424 * (Workspace: need N)
426 CALL SGEBAK( 'P', 'R', N, ILO, IHI, WORK( IBAL ), N, VS, LDVS,
432 * Undo scaling for the Schur form of A
434 CALL SLASCL( 'H', 0, 0, CSCALE, ANRM, N, N, A, LDA, IERR )
435 CALL SCOPY( N, A, LDA+1, WR, 1 )
436 IF( CSCALE.EQ.SMLNUM ) THEN
438 * If scaling back towards underflow, adjust WI if an
439 * offdiagonal element of a 2-by-2 block in the Schur form
442 IF( IEVAL.GT.0 ) THEN
445 CALL SLASCL( 'G', 0, 0, CSCALE, ANRM, ILO-1, 1, WI,
446 $ MAX( ILO-1, 1 ), IERR )
447 ELSE IF( WANTST ) THEN
458 IF( WI( I ).EQ.ZERO ) THEN
461 IF( A( I+1, I ).EQ.ZERO ) THEN
464 ELSE IF( A( I+1, I ).NE.ZERO .AND. A( I, I+1 ).EQ.
469 $ CALL SSWAP( I-1, A( 1, I ), 1, A( 1, I+1 ), 1 )
471 $ CALL SSWAP( N-I-1, A( I, I+2 ), LDA,
472 $ A( I+1, I+2 ), LDA )
474 CALL SSWAP( N, VS( 1, I ), 1, VS( 1, I+1 ), 1 )
476 A( I, I+1 ) = A( I+1, I )
484 * Undo scaling for the imaginary part of the eigenvalues
486 CALL SLASCL( 'G', 0, 0, CSCALE, ANRM, N-IEVAL, 1,
487 $ WI( IEVAL+1 ), MAX( N-IEVAL, 1 ), IERR )
490 IF( WANTST .AND. INFO.EQ.0 ) THEN
492 * Check if reordering successful
499 CURSL = SELECT( WR( I ), WI( I ) )
500 IF( WI( I ).EQ.ZERO ) THEN
504 IF( CURSL .AND. .NOT.LASTSL )
509 * Last eigenvalue of conjugate pair
511 CURSL = CURSL .OR. LASTSL
516 IF( CURSL .AND. .NOT.LST2SL )
520 * First eigenvalue of conjugate pair