001:       SUBROUTINE ZTGSY2( TRANS, IJOB, M, N, A, LDA, B, LDB, C, LDC, D,
002:      $                   LDD, E, LDE, F, LDF, SCALE, RDSUM, RDSCAL,
003:      $                   INFO )
004: *
005: *  -- LAPACK auxiliary routine (version 3.2) --
006: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
007: *     November 2006
008: *
009: *     .. Scalar Arguments ..
010:       CHARACTER          TRANS
011:       INTEGER            IJOB, INFO, LDA, LDB, LDC, LDD, LDE, LDF, M, N
012:       DOUBLE PRECISION   RDSCAL, RDSUM, SCALE
013: *     ..
014: *     .. Array Arguments ..
015:       COMPLEX*16         A( LDA, * ), B( LDB, * ), C( LDC, * ),
016:      $                   D( LDD, * ), E( LDE, * ), F( LDF, * )
017: *     ..
018: *
019: *  Purpose
020: *  =======
021: *
022: *  ZTGSY2 solves the generalized Sylvester equation
023: *
024: *              A * R - L * B = scale *   C               (1)
025: *              D * R - L * E = scale * F
026: *
027: *  using Level 1 and 2 BLAS, where R and L are unknown M-by-N matrices,
028: *  (A, D), (B, E) and (C, F) are given matrix pairs of size M-by-M,
029: *  N-by-N and M-by-N, respectively. A, B, D and E are upper triangular
030: *  (i.e., (A,D) and (B,E) in generalized Schur form).
031: *
032: *  The solution (R, L) overwrites (C, F). 0 <= SCALE <= 1 is an output
033: *  scaling factor chosen to avoid overflow.
034: *
035: *  In matrix notation solving equation (1) corresponds to solve
036: *  Zx = scale * b, where Z is defined as
037: *
038: *         Z = [ kron(In, A)  -kron(B', Im) ]             (2)
039: *             [ kron(In, D)  -kron(E', Im) ],
040: *
041: *  Ik is the identity matrix of size k and X' is the transpose of X.
042: *  kron(X, Y) is the Kronecker product between the matrices X and Y.
043: *
044: *  If TRANS = 'C', y in the conjugate transposed system Z'y = scale*b
045: *  is solved for, which is equivalent to solve for R and L in
046: *
047: *              A' * R  + D' * L   = scale *  C           (3)
048: *              R  * B' + L  * E'  = scale * -F
049: *
050: *  This case is used to compute an estimate of Dif[(A, D), (B, E)] =
051: *  = sigma_min(Z) using reverse communicaton with ZLACON.
052: *
053: *  ZTGSY2 also (IJOB >= 1) contributes to the computation in ZTGSYL
054: *  of an upper bound on the separation between to matrix pairs. Then
055: *  the input (A, D), (B, E) are sub-pencils of two matrix pairs in
056: *  ZTGSYL.
057: *
058: *  Arguments
059: *  =========
060: *
061: *  TRANS   (input) CHARACTER*1
062: *          = 'N', solve the generalized Sylvester equation (1).
063: *          = 'T': solve the 'transposed' system (3).
064: *
065: *  IJOB    (input) INTEGER
066: *          Specifies what kind of functionality to be performed.
067: *          =0: solve (1) only.
068: *          =1: A contribution from this subsystem to a Frobenius
069: *              norm-based estimate of the separation between two matrix
070: *              pairs is computed. (look ahead strategy is used).
071: *          =2: A contribution from this subsystem to a Frobenius
072: *              norm-based estimate of the separation between two matrix
073: *              pairs is computed. (DGECON on sub-systems is used.)
074: *          Not referenced if TRANS = 'T'.
075: *
076: *  M       (input) INTEGER
077: *          On entry, M specifies the order of A and D, and the row
078: *          dimension of C, F, R and L.
079: *
080: *  N       (input) INTEGER
081: *          On entry, N specifies the order of B and E, and the column
082: *          dimension of C, F, R and L.
083: *
084: *  A       (input) COMPLEX*16 array, dimension (LDA, M)
085: *          On entry, A contains an upper triangular matrix.
086: *
087: *  LDA     (input) INTEGER
088: *          The leading dimension of the matrix A. LDA >= max(1, M).
089: *
090: *  B       (input) COMPLEX*16 array, dimension (LDB, N)
091: *          On entry, B contains an upper triangular matrix.
092: *
093: *  LDB     (input) INTEGER
094: *          The leading dimension of the matrix B. LDB >= max(1, N).
095: *
096: *  C       (input/output) COMPLEX*16 array, dimension (LDC, N)
097: *          On entry, C contains the right-hand-side of the first matrix
098: *          equation in (1).
099: *          On exit, if IJOB = 0, C has been overwritten by the solution
100: *          R.
101: *
102: *  LDC     (input) INTEGER
103: *          The leading dimension of the matrix C. LDC >= max(1, M).
104: *
105: *  D       (input) COMPLEX*16 array, dimension (LDD, M)
106: *          On entry, D contains an upper triangular matrix.
107: *
108: *  LDD     (input) INTEGER
109: *          The leading dimension of the matrix D. LDD >= max(1, M).
110: *
111: *  E       (input) COMPLEX*16 array, dimension (LDE, N)
112: *          On entry, E contains an upper triangular matrix.
113: *
114: *  LDE     (input) INTEGER
115: *          The leading dimension of the matrix E. LDE >= max(1, N).
116: *
117: *  F       (input/output) COMPLEX*16 array, dimension (LDF, N)
118: *          On entry, F contains the right-hand-side of the second matrix
119: *          equation in (1).
120: *          On exit, if IJOB = 0, F has been overwritten by the solution
121: *          L.
122: *
123: *  LDF     (input) INTEGER
124: *          The leading dimension of the matrix F. LDF >= max(1, M).
125: *
126: *  SCALE   (output) DOUBLE PRECISION
127: *          On exit, 0 <= SCALE <= 1. If 0 < SCALE < 1, the solutions
128: *          R and L (C and F on entry) will hold the solutions to a
129: *          slightly perturbed system but the input matrices A, B, D and
130: *          E have not been changed. If SCALE = 0, R and L will hold the
131: *          solutions to the homogeneous system with C = F = 0.
132: *          Normally, SCALE = 1.
133: *
134: *  RDSUM   (input/output) DOUBLE PRECISION
135: *          On entry, the sum of squares of computed contributions to
136: *          the Dif-estimate under computation by ZTGSYL, where the
137: *          scaling factor RDSCAL (see below) has been factored out.
138: *          On exit, the corresponding sum of squares updated with the
139: *          contributions from the current sub-system.
140: *          If TRANS = 'T' RDSUM is not touched.
141: *          NOTE: RDSUM only makes sense when ZTGSY2 is called by
142: *          ZTGSYL.
143: *
144: *  RDSCAL  (input/output) DOUBLE PRECISION
145: *          On entry, scaling factor used to prevent overflow in RDSUM.
146: *          On exit, RDSCAL is updated w.r.t. the current contributions
147: *          in RDSUM.
148: *          If TRANS = 'T', RDSCAL is not touched.
149: *          NOTE: RDSCAL only makes sense when ZTGSY2 is called by
150: *          ZTGSYL.
151: *
152: *  INFO    (output) INTEGER
153: *          On exit, if INFO is set to
154: *            =0: Successful exit
155: *            <0: If INFO = -i, input argument number i is illegal.
156: *            >0: The matrix pairs (A, D) and (B, E) have common or very
157: *                close eigenvalues.
158: *
159: *  Further Details
160: *  ===============
161: *
162: *  Based on contributions by
163: *     Bo Kagstrom and Peter Poromaa, Department of Computing Science,
164: *     Umea University, S-901 87 Umea, Sweden.
165: *
166: *  =====================================================================
167: *
168: *     .. Parameters ..
169:       DOUBLE PRECISION   ZERO, ONE
170:       INTEGER            LDZ
171:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, LDZ = 2 )
172: *     ..
173: *     .. Local Scalars ..
174:       LOGICAL            NOTRAN
175:       INTEGER            I, IERR, J, K
176:       DOUBLE PRECISION   SCALOC
177:       COMPLEX*16         ALPHA
178: *     ..
179: *     .. Local Arrays ..
180:       INTEGER            IPIV( LDZ ), JPIV( LDZ )
181:       COMPLEX*16         RHS( LDZ ), Z( LDZ, LDZ )
182: *     ..
183: *     .. External Functions ..
184:       LOGICAL            LSAME
185:       EXTERNAL           LSAME
186: *     ..
187: *     .. External Subroutines ..
188:       EXTERNAL           XERBLA, ZAXPY, ZGESC2, ZGETC2, ZLATDF, ZSCAL
189: *     ..
190: *     .. Intrinsic Functions ..
191:       INTRINSIC          DCMPLX, DCONJG, MAX
192: *     ..
193: *     .. Executable Statements ..
194: *
195: *     Decode and test input parameters
196: *
197:       INFO = 0
198:       IERR = 0
199:       NOTRAN = LSAME( TRANS, 'N' )
200:       IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
201:          INFO = -1
202:       ELSE IF( NOTRAN ) THEN
203:          IF( ( IJOB.LT.0 ) .OR. ( IJOB.GT.2 ) ) THEN
204:             INFO = -2
205:          END IF
206:       END IF
207:       IF( INFO.EQ.0 ) THEN
208:          IF( M.LE.0 ) THEN
209:             INFO = -3
210:          ELSE IF( N.LE.0 ) THEN
211:             INFO = -4
212:          ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
213:             INFO = -5
214:          ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
215:             INFO = -8
216:          ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
217:             INFO = -10
218:          ELSE IF( LDD.LT.MAX( 1, M ) ) THEN
219:             INFO = -12
220:          ELSE IF( LDE.LT.MAX( 1, N ) ) THEN
221:             INFO = -14
222:          ELSE IF( LDF.LT.MAX( 1, M ) ) THEN
223:             INFO = -16
224:          END IF
225:       END IF
226:       IF( INFO.NE.0 ) THEN
227:          CALL XERBLA( 'ZTGSY2', -INFO )
228:          RETURN
229:       END IF
230: *
231:       IF( NOTRAN ) THEN
232: *
233: *        Solve (I, J) - system
234: *           A(I, I) * R(I, J) - L(I, J) * B(J, J) = C(I, J)
235: *           D(I, I) * R(I, J) - L(I, J) * E(J, J) = F(I, J)
236: *        for I = M, M - 1, ..., 1; J = 1, 2, ..., N
237: *
238:          SCALE = ONE
239:          SCALOC = ONE
240:          DO 30 J = 1, N
241:             DO 20 I = M, 1, -1
242: *
243: *              Build 2 by 2 system
244: *
245:                Z( 1, 1 ) = A( I, I )
246:                Z( 2, 1 ) = D( I, I )
247:                Z( 1, 2 ) = -B( J, J )
248:                Z( 2, 2 ) = -E( J, J )
249: *
250: *              Set up right hand side(s)
251: *
252:                RHS( 1 ) = C( I, J )
253:                RHS( 2 ) = F( I, J )
254: *
255: *              Solve Z * x = RHS
256: *
257:                CALL ZGETC2( LDZ, Z, LDZ, IPIV, JPIV, IERR )
258:                IF( IERR.GT.0 )
259:      $            INFO = IERR
260:                IF( IJOB.EQ.0 ) THEN
261:                   CALL ZGESC2( LDZ, Z, LDZ, RHS, IPIV, JPIV, SCALOC )
262:                   IF( SCALOC.NE.ONE ) THEN
263:                      DO 10 K = 1, N
264:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
265:      $                              C( 1, K ), 1 )
266:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
267:      $                              F( 1, K ), 1 )
268:    10                CONTINUE
269:                      SCALE = SCALE*SCALOC
270:                   END IF
271:                ELSE
272:                   CALL ZLATDF( IJOB, LDZ, Z, LDZ, RHS, RDSUM, RDSCAL,
273:      $                         IPIV, JPIV )
274:                END IF
275: *
276: *              Unpack solution vector(s)
277: *
278:                C( I, J ) = RHS( 1 )
279:                F( I, J ) = RHS( 2 )
280: *
281: *              Substitute R(I, J) and L(I, J) into remaining equation.
282: *
283:                IF( I.GT.1 ) THEN
284:                   ALPHA = -RHS( 1 )
285:                   CALL ZAXPY( I-1, ALPHA, A( 1, I ), 1, C( 1, J ), 1 )
286:                   CALL ZAXPY( I-1, ALPHA, D( 1, I ), 1, F( 1, J ), 1 )
287:                END IF
288:                IF( J.LT.N ) THEN
289:                   CALL ZAXPY( N-J, RHS( 2 ), B( J, J+1 ), LDB,
290:      $                        C( I, J+1 ), LDC )
291:                   CALL ZAXPY( N-J, RHS( 2 ), E( J, J+1 ), LDE,
292:      $                        F( I, J+1 ), LDF )
293:                END IF
294: *
295:    20       CONTINUE
296:    30    CONTINUE
297:       ELSE
298: *
299: *        Solve transposed (I, J) - system:
300: *           A(I, I)' * R(I, J) + D(I, I)' * L(J, J) = C(I, J)
301: *           R(I, I) * B(J, J) + L(I, J) * E(J, J)   = -F(I, J)
302: *        for I = 1, 2, ..., M, J = N, N - 1, ..., 1
303: *
304:          SCALE = ONE
305:          SCALOC = ONE
306:          DO 80 I = 1, M
307:             DO 70 J = N, 1, -1
308: *
309: *              Build 2 by 2 system Z'
310: *
311:                Z( 1, 1 ) = DCONJG( A( I, I ) )
312:                Z( 2, 1 ) = -DCONJG( B( J, J ) )
313:                Z( 1, 2 ) = DCONJG( D( I, I ) )
314:                Z( 2, 2 ) = -DCONJG( E( J, J ) )
315: *
316: *
317: *              Set up right hand side(s)
318: *
319:                RHS( 1 ) = C( I, J )
320:                RHS( 2 ) = F( I, J )
321: *
322: *              Solve Z' * x = RHS
323: *
324:                CALL ZGETC2( LDZ, Z, LDZ, IPIV, JPIV, IERR )
325:                IF( IERR.GT.0 )
326:      $            INFO = IERR
327:                CALL ZGESC2( LDZ, Z, LDZ, RHS, IPIV, JPIV, SCALOC )
328:                IF( SCALOC.NE.ONE ) THEN
329:                   DO 40 K = 1, N
330:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), C( 1, K ),
331:      $                           1 )
332:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), F( 1, K ),
333:      $                           1 )
334:    40             CONTINUE
335:                   SCALE = SCALE*SCALOC
336:                END IF
337: *
338: *              Unpack solution vector(s)
339: *
340:                C( I, J ) = RHS( 1 )
341:                F( I, J ) = RHS( 2 )
342: *
343: *              Substitute R(I, J) and L(I, J) into remaining equation.
344: *
345:                DO 50 K = 1, J - 1
346:                   F( I, K ) = F( I, K ) + RHS( 1 )*DCONJG( B( K, J ) ) +
347:      $                        RHS( 2 )*DCONJG( E( K, J ) )
348:    50          CONTINUE
349:                DO 60 K = I + 1, M
350:                   C( K, J ) = C( K, J ) - DCONJG( A( I, K ) )*RHS( 1 ) -
351:      $                        DCONJG( D( I, K ) )*RHS( 2 )
352:    60          CONTINUE
353: *
354:    70       CONTINUE
355:    80    CONTINUE
356:       END IF
357:       RETURN
358: *
359: *     End of ZTGSY2
360: *
361:       END
362: