001:       SUBROUTINE CTGSNA( JOB, HOWMNY, SELECT, N, A, LDA, B, LDB, VL,
002:      $                   LDVL, VR, LDVR, S, DIF, MM, M, WORK, LWORK,
003:      $                   IWORK, INFO )
004: *
005: *  -- LAPACK routine (version 3.2) --
006: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
007: *     November 2006
008: *
009: *     .. Scalar Arguments ..
010:       CHARACTER          HOWMNY, JOB
011:       INTEGER            INFO, LDA, LDB, LDVL, LDVR, LWORK, M, MM, N
012: *     ..
013: *     .. Array Arguments ..
014:       LOGICAL            SELECT( * )
015:       INTEGER            IWORK( * )
016:       REAL               DIF( * ), S( * )
017:       COMPLEX            A( LDA, * ), B( LDB, * ), VL( LDVL, * ),
018:      $                   VR( LDVR, * ), WORK( * )
019: *     ..
020: *
021: *  Purpose
022: *  =======
023: *
024: *  CTGSNA estimates reciprocal condition numbers for specified
025: *  eigenvalues and/or eigenvectors of a matrix pair (A, B).
026: *
027: *  (A, B) must be in generalized Schur canonical form, that is, A and
028: *  B are both upper triangular.
029: *
030: *  Arguments
031: *  =========
032: *
033: *  JOB     (input) CHARACTER*1
034: *          Specifies whether condition numbers are required for
035: *          eigenvalues (S) or eigenvectors (DIF):
036: *          = 'E': for eigenvalues only (S);
037: *          = 'V': for eigenvectors only (DIF);
038: *          = 'B': for both eigenvalues and eigenvectors (S and DIF).
039: *
040: *  HOWMNY  (input) CHARACTER*1
041: *          = 'A': compute condition numbers for all eigenpairs;
042: *          = 'S': compute condition numbers for selected eigenpairs
043: *                 specified by the array SELECT.
044: *
045: *  SELECT  (input) LOGICAL array, dimension (N)
046: *          If HOWMNY = 'S', SELECT specifies the eigenpairs for which
047: *          condition numbers are required. To select condition numbers
048: *          for the corresponding j-th eigenvalue and/or eigenvector,
049: *          SELECT(j) must be set to .TRUE..
050: *          If HOWMNY = 'A', SELECT is not referenced.
051: *
052: *  N       (input) INTEGER
053: *          The order of the square matrix pair (A, B). N >= 0.
054: *
055: *  A       (input) COMPLEX array, dimension (LDA,N)
056: *          The upper triangular matrix A in the pair (A,B).
057: *
058: *  LDA     (input) INTEGER
059: *          The leading dimension of the array A. LDA >= max(1,N).
060: *
061: *  B       (input) COMPLEX array, dimension (LDB,N)
062: *          The upper triangular matrix B in the pair (A, B).
063: *
064: *  LDB     (input) INTEGER
065: *          The leading dimension of the array B. LDB >= max(1,N).
066: *
067: *  VL      (input) COMPLEX array, dimension (LDVL,M)
068: *          IF JOB = 'E' or 'B', VL must contain left eigenvectors of
069: *          (A, B), corresponding to the eigenpairs specified by HOWMNY
070: *          and SELECT.  The eigenvectors must be stored in consecutive
071: *          columns of VL, as returned by CTGEVC.
072: *          If JOB = 'V', VL is not referenced.
073: *
074: *  LDVL    (input) INTEGER
075: *          The leading dimension of the array VL. LDVL >= 1; and
076: *          If JOB = 'E' or 'B', LDVL >= N.
077: *
078: *  VR      (input) COMPLEX array, dimension (LDVR,M)
079: *          IF JOB = 'E' or 'B', VR must contain right eigenvectors of
080: *          (A, B), corresponding to the eigenpairs specified by HOWMNY
081: *          and SELECT.  The eigenvectors must be stored in consecutive
082: *          columns of VR, as returned by CTGEVC.
083: *          If JOB = 'V', VR is not referenced.
084: *
085: *  LDVR    (input) INTEGER
086: *          The leading dimension of the array VR. LDVR >= 1;
087: *          If JOB = 'E' or 'B', LDVR >= N.
088: *
089: *  S       (output) REAL array, dimension (MM)
090: *          If JOB = 'E' or 'B', the reciprocal condition numbers of the
091: *          selected eigenvalues, stored in consecutive elements of the
092: *          array.
093: *          If JOB = 'V', S is not referenced.
094: *
095: *  DIF     (output) REAL array, dimension (MM)
096: *          If JOB = 'V' or 'B', the estimated reciprocal condition
097: *          numbers of the selected eigenvectors, stored in consecutive
098: *          elements of the array.
099: *          If the eigenvalues cannot be reordered to compute DIF(j),
100: *          DIF(j) is set to 0; this can only occur when the true value
101: *          would be very small anyway.
102: *          For each eigenvalue/vector specified by SELECT, DIF stores
103: *          a Frobenius norm-based estimate of Difl.
104: *          If JOB = 'E', DIF is not referenced.
105: *
106: *  MM      (input) INTEGER
107: *          The number of elements in the arrays S and DIF. MM >= M.
108: *
109: *  M       (output) INTEGER
110: *          The number of elements of the arrays S and DIF used to store
111: *          the specified condition numbers; for each selected eigenvalue
112: *          one element is used. If HOWMNY = 'A', M is set to N.
113: *
114: *  WORK    (workspace/output) COMPLEX array, dimension (MAX(1,LWORK))
115: *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
116: *
117: *  LWORK  (input) INTEGER
118: *          The dimension of the array WORK. LWORK >= max(1,N).
119: *          If JOB = 'V' or 'B', LWORK >= max(1,2*N*N).
120: *
121: *  IWORK   (workspace) INTEGER array, dimension (N+2)
122: *          If JOB = 'E', IWORK is not referenced.
123: *
124: *  INFO    (output) INTEGER
125: *          = 0: Successful exit
126: *          < 0: If INFO = -i, the i-th argument had an illegal value
127: *
128: *  Further Details
129: *  ===============
130: *
131: *  The reciprocal of the condition number of the i-th generalized
132: *  eigenvalue w = (a, b) is defined as
133: *
134: *          S(I) = (|v'Au|**2 + |v'Bu|**2)**(1/2) / (norm(u)*norm(v))
135: *
136: *  where u and v are the right and left eigenvectors of (A, B)
137: *  corresponding to w; |z| denotes the absolute value of the complex
138: *  number, and norm(u) denotes the 2-norm of the vector u. The pair
139: *  (a, b) corresponds to an eigenvalue w = a/b (= v'Au/v'Bu) of the
140: *  matrix pair (A, B). If both a and b equal zero, then (A,B) is
141: *  singular and S(I) = -1 is returned.
142: *
143: *  An approximate error bound on the chordal distance between the i-th
144: *  computed generalized eigenvalue w and the corresponding exact
145: *  eigenvalue lambda is
146: *
147: *          chord(w, lambda) <=   EPS * norm(A, B) / S(I),
148: *
149: *  where EPS is the machine precision.
150: *
151: *  The reciprocal of the condition number of the right eigenvector u
152: *  and left eigenvector v corresponding to the generalized eigenvalue w
153: *  is defined as follows. Suppose
154: *
155: *                   (A, B) = ( a   *  ) ( b  *  )  1
156: *                            ( 0  A22 ),( 0 B22 )  n-1
157: *                              1  n-1     1 n-1
158: *
159: *  Then the reciprocal condition number DIF(I) is
160: *
161: *          Difl[(a, b), (A22, B22)]  = sigma-min( Zl )
162: *
163: *  where sigma-min(Zl) denotes the smallest singular value of
164: *
165: *         Zl = [ kron(a, In-1) -kron(1, A22) ]
166: *              [ kron(b, In-1) -kron(1, B22) ].
167: *
168: *  Here In-1 is the identity matrix of size n-1 and X' is the conjugate
169: *  transpose of X. kron(X, Y) is the Kronecker product between the
170: *  matrices X and Y.
171: *
172: *  We approximate the smallest singular value of Zl with an upper
173: *  bound. This is done by CLATDF.
174: *
175: *  An approximate error bound for a computed eigenvector VL(i) or
176: *  VR(i) is given by
177: *
178: *                      EPS * norm(A, B) / DIF(i).
179: *
180: *  See ref. [2-3] for more details and further references.
181: *
182: *  Based on contributions by
183: *     Bo Kagstrom and Peter Poromaa, Department of Computing Science,
184: *     Umea University, S-901 87 Umea, Sweden.
185: *
186: *  References
187: *  ==========
188: *
189: *  [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
190: *      Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
191: *      M.S. Moonen et al (eds), Linear Algebra for Large Scale and
192: *      Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
193: *
194: *  [2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified
195: *      Eigenvalues of a Regular Matrix Pair (A, B) and Condition
196: *      Estimation: Theory, Algorithms and Software, Report
197: *      UMINF - 94.04, Department of Computing Science, Umea University,
198: *      S-901 87 Umea, Sweden, 1994. Also as LAPACK Working Note 87.
199: *      To appear in Numerical Algorithms, 1996.
200: *
201: *  [3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
202: *      for Solving the Generalized Sylvester Equation and Estimating the
203: *      Separation between Regular Matrix Pairs, Report UMINF - 93.23,
204: *      Department of Computing Science, Umea University, S-901 87 Umea,
205: *      Sweden, December 1993, Revised April 1994, Also as LAPACK Working
206: *      Note 75.
207: *      To appear in ACM Trans. on Math. Software, Vol 22, No 1, 1996.
208: *
209: *  =====================================================================
210: *
211: *     .. Parameters ..
212:       REAL               ZERO, ONE
213:       INTEGER            IDIFJB
214:       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0, IDIFJB = 3 )
215: *     ..
216: *     .. Local Scalars ..
217:       LOGICAL            LQUERY, SOMCON, WANTBH, WANTDF, WANTS
218:       INTEGER            I, IERR, IFST, ILST, K, KS, LWMIN, N1, N2
219:       REAL               BIGNUM, COND, EPS, LNRM, RNRM, SCALE, SMLNUM
220:       COMPLEX            YHAX, YHBX
221: *     ..
222: *     .. Local Arrays ..
223:       COMPLEX            DUMMY( 1 ), DUMMY1( 1 )
224: *     ..
225: *     .. External Functions ..
226:       LOGICAL            LSAME
227:       REAL               SCNRM2, SLAMCH, SLAPY2
228:       COMPLEX            CDOTC
229:       EXTERNAL           LSAME, SCNRM2, SLAMCH, SLAPY2, CDOTC
230: *     ..
231: *     .. External Subroutines ..
232:       EXTERNAL           CGEMV, CLACPY, CTGEXC, CTGSYL, SLABAD, XERBLA
233: *     ..
234: *     .. Intrinsic Functions ..
235:       INTRINSIC          ABS, CMPLX, MAX
236: *     ..
237: *     .. Executable Statements ..
238: *
239: *     Decode and test the input parameters
240: *
241:       WANTBH = LSAME( JOB, 'B' )
242:       WANTS = LSAME( JOB, 'E' ) .OR. WANTBH
243:       WANTDF = LSAME( JOB, 'V' ) .OR. WANTBH
244: *
245:       SOMCON = LSAME( HOWMNY, 'S' )
246: *
247:       INFO = 0
248:       LQUERY = ( LWORK.EQ.-1 )
249: *
250:       IF( .NOT.WANTS .AND. .NOT.WANTDF ) THEN
251:          INFO = -1
252:       ELSE IF( .NOT.LSAME( HOWMNY, 'A' ) .AND. .NOT.SOMCON ) THEN
253:          INFO = -2
254:       ELSE IF( N.LT.0 ) THEN
255:          INFO = -4
256:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
257:          INFO = -6
258:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
259:          INFO = -8
260:       ELSE IF( WANTS .AND. LDVL.LT.N ) THEN
261:          INFO = -10
262:       ELSE IF( WANTS .AND. LDVR.LT.N ) THEN
263:          INFO = -12
264:       ELSE
265: *
266: *        Set M to the number of eigenpairs for which condition numbers
267: *        are required, and test MM.
268: *
269:          IF( SOMCON ) THEN
270:             M = 0
271:             DO 10 K = 1, N
272:                IF( SELECT( K ) )
273:      $            M = M + 1
274:    10       CONTINUE
275:          ELSE
276:             M = N
277:          END IF
278: *
279:          IF( N.EQ.0 ) THEN
280:             LWMIN = 1
281:          ELSE IF( LSAME( JOB, 'V' ) .OR. LSAME( JOB, 'B' ) ) THEN
282:             LWMIN = 2*N*N
283:          ELSE
284:             LWMIN = N
285:          END IF
286:          WORK( 1 ) = LWMIN
287: *
288:          IF( MM.LT.M ) THEN
289:             INFO = -15
290:          ELSE IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
291:             INFO = -18
292:          END IF
293:       END IF
294: *
295:       IF( INFO.NE.0 ) THEN
296:          CALL XERBLA( 'CTGSNA', -INFO )
297:          RETURN
298:       ELSE IF( LQUERY ) THEN
299:          RETURN
300:       END IF
301: *
302: *     Quick return if possible
303: *
304:       IF( N.EQ.0 )
305:      $   RETURN
306: *
307: *     Get machine constants
308: *
309:       EPS = SLAMCH( 'P' )
310:       SMLNUM = SLAMCH( 'S' ) / EPS
311:       BIGNUM = ONE / SMLNUM
312:       CALL SLABAD( SMLNUM, BIGNUM )
313:       KS = 0
314:       DO 20 K = 1, N
315: *
316: *        Determine whether condition numbers are required for the k-th
317: *        eigenpair.
318: *
319:          IF( SOMCON ) THEN
320:             IF( .NOT.SELECT( K ) )
321:      $         GO TO 20
322:          END IF
323: *
324:          KS = KS + 1
325: *
326:          IF( WANTS ) THEN
327: *
328: *           Compute the reciprocal condition number of the k-th
329: *           eigenvalue.
330: *
331:             RNRM = SCNRM2( N, VR( 1, KS ), 1 )
332:             LNRM = SCNRM2( N, VL( 1, KS ), 1 )
333:             CALL CGEMV( 'N', N, N, CMPLX( ONE, ZERO ), A, LDA,
334:      $                  VR( 1, KS ), 1, CMPLX( ZERO, ZERO ), WORK, 1 )
335:             YHAX = CDOTC( N, WORK, 1, VL( 1, KS ), 1 )
336:             CALL CGEMV( 'N', N, N, CMPLX( ONE, ZERO ), B, LDB,
337:      $                  VR( 1, KS ), 1, CMPLX( ZERO, ZERO ), WORK, 1 )
338:             YHBX = CDOTC( N, WORK, 1, VL( 1, KS ), 1 )
339:             COND = SLAPY2( ABS( YHAX ), ABS( YHBX ) )
340:             IF( COND.EQ.ZERO ) THEN
341:                S( KS ) = -ONE
342:             ELSE
343:                S( KS ) = COND / ( RNRM*LNRM )
344:             END IF
345:          END IF
346: *
347:          IF( WANTDF ) THEN
348:             IF( N.EQ.1 ) THEN
349:                DIF( KS ) = SLAPY2( ABS( A( 1, 1 ) ), ABS( B( 1, 1 ) ) )
350:             ELSE
351: *
352: *              Estimate the reciprocal condition number of the k-th
353: *              eigenvectors.
354: *
355: *              Copy the matrix (A, B) to the array WORK and move the
356: *              (k,k)th pair to the (1,1) position.
357: *
358:                CALL CLACPY( 'Full', N, N, A, LDA, WORK, N )
359:                CALL CLACPY( 'Full', N, N, B, LDB, WORK( N*N+1 ), N )
360:                IFST = K
361:                ILST = 1
362: *
363:                CALL CTGEXC( .FALSE., .FALSE., N, WORK, N, WORK( N*N+1 ),
364:      $                      N, DUMMY, 1, DUMMY1, 1, IFST, ILST, IERR )
365: *
366:                IF( IERR.GT.0 ) THEN
367: *
368: *                 Ill-conditioned problem - swap rejected.
369: *
370:                   DIF( KS ) = ZERO
371:                ELSE
372: *
373: *                 Reordering successful, solve generalized Sylvester
374: *                 equation for R and L,
375: *                            A22 * R - L * A11 = A12
376: *                            B22 * R - L * B11 = B12,
377: *                 and compute estimate of Difl[(A11,B11), (A22, B22)].
378: *
379:                   N1 = 1
380:                   N2 = N - N1
381:                   I = N*N + 1
382:                   CALL CTGSYL( 'N', IDIFJB, N2, N1, WORK( N*N1+N1+1 ),
383:      $                         N, WORK, N, WORK( N1+1 ), N,
384:      $                         WORK( N*N1+N1+I ), N, WORK( I ), N,
385:      $                         WORK( N1+I ), N, SCALE, DIF( KS ), DUMMY,
386:      $                         1, IWORK, IERR )
387:                END IF
388:             END IF
389:          END IF
390: *
391:    20 CONTINUE
392:       WORK( 1 ) = LWMIN
393:       RETURN
394: *
395: *     End of CTGSNA
396: *
397:       END
398: