Annotation of rpl/lapack/lapack/ztgsyl.f, revision 1.18

1.9       bertrand    1: *> \brief \b ZTGSYL
                      2: *
                      3: *  =========== DOCUMENTATION ===========
                      4: *
1.15      bertrand    5: * Online html documentation available at
                      6: *            http://www.netlib.org/lapack/explore-html/
1.9       bertrand    7: *
                      8: *> \htmlonly
1.15      bertrand    9: *> Download ZTGSYL + dependencies
                     10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztgsyl.f">
                     11: *> [TGZ]</a>
                     12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztgsyl.f">
                     13: *> [ZIP]</a>
                     14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgsyl.f">
1.9       bertrand   15: *> [TXT]</a>
1.15      bertrand   16: *> \endhtmlonly
1.9       bertrand   17: *
                     18: *  Definition:
                     19: *  ===========
                     20: *
                     21: *       SUBROUTINE ZTGSYL( TRANS, IJOB, M, N, A, LDA, B, LDB, C, LDC, D,
                     22: *                          LDD, E, LDE, F, LDF, SCALE, DIF, WORK, LWORK,
                     23: *                          IWORK, INFO )
1.15      bertrand   24: *
1.9       bertrand   25: *       .. Scalar Arguments ..
                     26: *       CHARACTER          TRANS
                     27: *       INTEGER            IJOB, INFO, LDA, LDB, LDC, LDD, LDE, LDF,
                     28: *      $                   LWORK, M, N
                     29: *       DOUBLE PRECISION   DIF, SCALE
                     30: *       ..
                     31: *       .. Array Arguments ..
                     32: *       INTEGER            IWORK( * )
                     33: *       COMPLEX*16         A( LDA, * ), B( LDB, * ), C( LDC, * ),
                     34: *      $                   D( LDD, * ), E( LDE, * ), F( LDF, * ),
                     35: *      $                   WORK( * )
                     36: *       ..
1.15      bertrand   37: *
1.9       bertrand   38: *
                     39: *> \par Purpose:
                     40: *  =============
                     41: *>
                     42: *> \verbatim
                     43: *>
                     44: *> ZTGSYL solves the generalized Sylvester equation:
                     45: *>
                     46: *>             A * R - L * B = scale * C            (1)
                     47: *>             D * R - L * E = scale * F
                     48: *>
                     49: *> where R and L are unknown m-by-n matrices, (A, D), (B, E) and
                     50: *> (C, F) are given matrix pairs of size m-by-m, n-by-n and m-by-n,
                     51: *> respectively, with complex entries. A, B, D and E are upper
                     52: *> triangular (i.e., (A,D) and (B,E) in generalized Schur form).
                     53: *>
                     54: *> The solution (R, L) overwrites (C, F). 0 <= SCALE <= 1
                     55: *> is an output scaling factor chosen to avoid overflow.
                     56: *>
                     57: *> In matrix notation (1) is equivalent to solve Zx = scale*b, where Z
                     58: *> is defined as
                     59: *>
                     60: *>        Z = [ kron(In, A)  -kron(B**H, Im) ]        (2)
                     61: *>            [ kron(In, D)  -kron(E**H, Im) ],
                     62: *>
                     63: *> Here Ix is the identity matrix of size x and X**H is the conjugate
                     64: *> transpose of X. Kron(X, Y) is the Kronecker product between the
                     65: *> matrices X and Y.
                     66: *>
                     67: *> If TRANS = 'C', y in the conjugate transposed system Z**H *y = scale*b
                     68: *> is solved for, which is equivalent to solve for R and L in
                     69: *>
                     70: *>             A**H * R + D**H * L = scale * C           (3)
                     71: *>             R * B**H + L * E**H = scale * -F
                     72: *>
                     73: *> This case (TRANS = 'C') is used to compute an one-norm-based estimate
                     74: *> of Dif[(A,D), (B,E)], the separation between the matrix pairs (A,D)
                     75: *> and (B,E), using ZLACON.
                     76: *>
                     77: *> If IJOB >= 1, ZTGSYL computes a Frobenius norm-based estimate of
                     78: *> Dif[(A,D),(B,E)]. That is, the reciprocal of a lower bound on the
                     79: *> reciprocal of the smallest singular value of Z.
                     80: *>
                     81: *> This is a level-3 BLAS algorithm.
                     82: *> \endverbatim
                     83: *
                     84: *  Arguments:
                     85: *  ==========
                     86: *
                     87: *> \param[in] TRANS
                     88: *> \verbatim
                     89: *>          TRANS is CHARACTER*1
                     90: *>          = 'N': solve the generalized sylvester equation (1).
                     91: *>          = 'C': solve the "conjugate transposed" system (3).
                     92: *> \endverbatim
                     93: *>
                     94: *> \param[in] IJOB
                     95: *> \verbatim
                     96: *>          IJOB is INTEGER
                     97: *>          Specifies what kind of functionality to be performed.
                     98: *>          =0: solve (1) only.
                     99: *>          =1: The functionality of 0 and 3.
                    100: *>          =2: The functionality of 0 and 4.
                    101: *>          =3: Only an estimate of Dif[(A,D), (B,E)] is computed.
                    102: *>              (look ahead strategy is used).
                    103: *>          =4: Only an estimate of Dif[(A,D), (B,E)] is computed.
                    104: *>              (ZGECON on sub-systems is used).
                    105: *>          Not referenced if TRANS = 'C'.
                    106: *> \endverbatim
                    107: *>
                    108: *> \param[in] M
                    109: *> \verbatim
                    110: *>          M is INTEGER
                    111: *>          The order of the matrices A and D, and the row dimension of
                    112: *>          the matrices C, F, R and L.
                    113: *> \endverbatim
                    114: *>
                    115: *> \param[in] N
                    116: *> \verbatim
                    117: *>          N is INTEGER
                    118: *>          The order of the matrices B and E, and the column dimension
                    119: *>          of the matrices C, F, R and L.
                    120: *> \endverbatim
                    121: *>
                    122: *> \param[in] A
                    123: *> \verbatim
                    124: *>          A is COMPLEX*16 array, dimension (LDA, M)
                    125: *>          The upper triangular matrix A.
                    126: *> \endverbatim
                    127: *>
                    128: *> \param[in] LDA
                    129: *> \verbatim
                    130: *>          LDA is INTEGER
                    131: *>          The leading dimension of the array A. LDA >= max(1, M).
                    132: *> \endverbatim
                    133: *>
                    134: *> \param[in] B
                    135: *> \verbatim
                    136: *>          B is COMPLEX*16 array, dimension (LDB, N)
                    137: *>          The upper triangular matrix B.
                    138: *> \endverbatim
                    139: *>
                    140: *> \param[in] LDB
                    141: *> \verbatim
                    142: *>          LDB is INTEGER
                    143: *>          The leading dimension of the array B. LDB >= max(1, N).
                    144: *> \endverbatim
                    145: *>
                    146: *> \param[in,out] C
                    147: *> \verbatim
                    148: *>          C is COMPLEX*16 array, dimension (LDC, N)
                    149: *>          On entry, C contains the right-hand-side of the first matrix
                    150: *>          equation in (1) or (3).
                    151: *>          On exit, if IJOB = 0, 1 or 2, C has been overwritten by
                    152: *>          the solution R. If IJOB = 3 or 4 and TRANS = 'N', C holds R,
                    153: *>          the solution achieved during the computation of the
                    154: *>          Dif-estimate.
                    155: *> \endverbatim
                    156: *>
                    157: *> \param[in] LDC
                    158: *> \verbatim
                    159: *>          LDC is INTEGER
                    160: *>          The leading dimension of the array C. LDC >= max(1, M).
                    161: *> \endverbatim
                    162: *>
                    163: *> \param[in] D
                    164: *> \verbatim
                    165: *>          D is COMPLEX*16 array, dimension (LDD, M)
                    166: *>          The upper triangular matrix D.
                    167: *> \endverbatim
                    168: *>
                    169: *> \param[in] LDD
                    170: *> \verbatim
                    171: *>          LDD is INTEGER
                    172: *>          The leading dimension of the array D. LDD >= max(1, M).
                    173: *> \endverbatim
                    174: *>
                    175: *> \param[in] E
                    176: *> \verbatim
                    177: *>          E is COMPLEX*16 array, dimension (LDE, N)
                    178: *>          The upper triangular matrix E.
                    179: *> \endverbatim
                    180: *>
                    181: *> \param[in] LDE
                    182: *> \verbatim
                    183: *>          LDE is INTEGER
                    184: *>          The leading dimension of the array E. LDE >= max(1, N).
                    185: *> \endverbatim
                    186: *>
                    187: *> \param[in,out] F
                    188: *> \verbatim
                    189: *>          F is COMPLEX*16 array, dimension (LDF, N)
                    190: *>          On entry, F contains the right-hand-side of the second matrix
                    191: *>          equation in (1) or (3).
                    192: *>          On exit, if IJOB = 0, 1 or 2, F has been overwritten by
                    193: *>          the solution L. If IJOB = 3 or 4 and TRANS = 'N', F holds L,
                    194: *>          the solution achieved during the computation of the
                    195: *>          Dif-estimate.
                    196: *> \endverbatim
                    197: *>
                    198: *> \param[in] LDF
                    199: *> \verbatim
                    200: *>          LDF is INTEGER
                    201: *>          The leading dimension of the array F. LDF >= max(1, M).
                    202: *> \endverbatim
                    203: *>
                    204: *> \param[out] DIF
                    205: *> \verbatim
                    206: *>          DIF is DOUBLE PRECISION
                    207: *>          On exit DIF is the reciprocal of a lower bound of the
                    208: *>          reciprocal of the Dif-function, i.e. DIF is an upper bound of
                    209: *>          Dif[(A,D), (B,E)] = sigma-min(Z), where Z as in (2).
                    210: *>          IF IJOB = 0 or TRANS = 'C', DIF is not referenced.
                    211: *> \endverbatim
                    212: *>
                    213: *> \param[out] SCALE
                    214: *> \verbatim
                    215: *>          SCALE is DOUBLE PRECISION
                    216: *>          On exit SCALE is the scaling factor in (1) or (3).
                    217: *>          If 0 < SCALE < 1, C and F hold the solutions R and L, resp.,
                    218: *>          to a slightly perturbed system but the input matrices A, B,
                    219: *>          D and E have not been changed. If SCALE = 0, R and L will
1.18    ! bertrand  220: *>          hold the solutions to the homogeneous system with C = F = 0.
1.9       bertrand  221: *> \endverbatim
                    222: *>
                    223: *> \param[out] WORK
                    224: *> \verbatim
                    225: *>          WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
                    226: *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
                    227: *> \endverbatim
                    228: *>
                    229: *> \param[in] LWORK
                    230: *> \verbatim
                    231: *>          LWORK is INTEGER
                    232: *>          The dimension of the array WORK. LWORK > = 1.
                    233: *>          If IJOB = 1 or 2 and TRANS = 'N', LWORK >= max(1,2*M*N).
                    234: *>
                    235: *>          If LWORK = -1, then a workspace query is assumed; the routine
                    236: *>          only calculates the optimal size of the WORK array, returns
                    237: *>          this value as the first entry of the WORK array, and no error
                    238: *>          message related to LWORK is issued by XERBLA.
                    239: *> \endverbatim
                    240: *>
                    241: *> \param[out] IWORK
                    242: *> \verbatim
                    243: *>          IWORK is INTEGER array, dimension (M+N+2)
                    244: *> \endverbatim
                    245: *>
                    246: *> \param[out] INFO
                    247: *> \verbatim
                    248: *>          INFO is INTEGER
                    249: *>            =0: successful exit
                    250: *>            <0: If INFO = -i, the i-th argument had an illegal value.
                    251: *>            >0: (A, D) and (B, E) have common or very close
                    252: *>                eigenvalues.
                    253: *> \endverbatim
                    254: *
                    255: *  Authors:
                    256: *  ========
                    257: *
1.15      bertrand  258: *> \author Univ. of Tennessee
                    259: *> \author Univ. of California Berkeley
                    260: *> \author Univ. of Colorado Denver
                    261: *> \author NAG Ltd.
1.9       bertrand  262: *
                    263: *> \ingroup complex16SYcomputational
                    264: *
                    265: *> \par Contributors:
                    266: *  ==================
                    267: *>
                    268: *>     Bo Kagstrom and Peter Poromaa, Department of Computing Science,
                    269: *>     Umea University, S-901 87 Umea, Sweden.
                    270: *
                    271: *> \par References:
                    272: *  ================
                    273: *>
                    274: *>  [1] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
                    275: *>      for Solving the Generalized Sylvester Equation and Estimating the
                    276: *>      Separation between Regular Matrix Pairs, Report UMINF - 93.23,
                    277: *>      Department of Computing Science, Umea University, S-901 87 Umea,
                    278: *>      Sweden, December 1993, Revised April 1994, Also as LAPACK Working
                    279: *>      Note 75.  To appear in ACM Trans. on Math. Software, Vol 22,
                    280: *>      No 1, 1996.
                    281: *> \n
                    282: *>  [2] B. Kagstrom, A Perturbation Analysis of the Generalized Sylvester
                    283: *>      Equation (AR - LB, DR - LE ) = (C, F), SIAM J. Matrix Anal.
                    284: *>      Appl., 15(4):1045-1060, 1994.
                    285: *> \n
                    286: *>  [3] B. Kagstrom and L. Westin, Generalized Schur Methods with
                    287: *>      Condition Estimators for Solving the Generalized Sylvester
                    288: *>      Equation, IEEE Transactions on Automatic Control, Vol. 34, No. 7,
                    289: *>      July 1989, pp 745-751.
                    290: *>
                    291: *  =====================================================================
1.1       bertrand  292:       SUBROUTINE ZTGSYL( TRANS, IJOB, M, N, A, LDA, B, LDB, C, LDC, D,
                    293:      $                   LDD, E, LDE, F, LDF, SCALE, DIF, WORK, LWORK,
                    294:      $                   IWORK, INFO )
                    295: *
1.18    ! bertrand  296: *  -- LAPACK computational routine --
1.1       bertrand  297: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    298: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
                    299: *
                    300: *     .. Scalar Arguments ..
                    301:       CHARACTER          TRANS
                    302:       INTEGER            IJOB, INFO, LDA, LDB, LDC, LDD, LDE, LDF,
                    303:      $                   LWORK, M, N
                    304:       DOUBLE PRECISION   DIF, SCALE
                    305: *     ..
                    306: *     .. Array Arguments ..
                    307:       INTEGER            IWORK( * )
                    308:       COMPLEX*16         A( LDA, * ), B( LDB, * ), C( LDC, * ),
                    309:      $                   D( LDD, * ), E( LDE, * ), F( LDF, * ),
                    310:      $                   WORK( * )
                    311: *     ..
                    312: *
                    313: *  =====================================================================
                    314: *  Replaced various illegal calls to CCOPY by calls to CLASET.
                    315: *  Sven Hammarling, 1/5/02.
                    316: *
                    317: *     .. Parameters ..
                    318:       DOUBLE PRECISION   ZERO, ONE
                    319:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
                    320:       COMPLEX*16         CZERO
                    321:       PARAMETER          ( CZERO = (0.0D+0, 0.0D+0) )
                    322: *     ..
                    323: *     .. Local Scalars ..
                    324:       LOGICAL            LQUERY, NOTRAN
                    325:       INTEGER            I, IE, IFUNC, IROUND, IS, ISOLVE, J, JE, JS, K,
                    326:      $                   LINFO, LWMIN, MB, NB, P, PQ, Q
                    327:       DOUBLE PRECISION   DSCALE, DSUM, SCALE2, SCALOC
                    328: *     ..
                    329: *     .. External Functions ..
                    330:       LOGICAL            LSAME
                    331:       INTEGER            ILAENV
                    332:       EXTERNAL           LSAME, ILAENV
                    333: *     ..
                    334: *     .. External Subroutines ..
                    335:       EXTERNAL           XERBLA, ZGEMM, ZLACPY, ZLASET, ZSCAL, ZTGSY2
                    336: *     ..
                    337: *     .. Intrinsic Functions ..
                    338:       INTRINSIC          DBLE, DCMPLX, MAX, SQRT
                    339: *     ..
                    340: *     .. Executable Statements ..
                    341: *
                    342: *     Decode and test input parameters
                    343: *
                    344:       INFO = 0
                    345:       NOTRAN = LSAME( TRANS, 'N' )
                    346:       LQUERY = ( LWORK.EQ.-1 )
                    347: *
                    348:       IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
                    349:          INFO = -1
                    350:       ELSE IF( NOTRAN ) THEN
                    351:          IF( ( IJOB.LT.0 ) .OR. ( IJOB.GT.4 ) ) THEN
                    352:             INFO = -2
                    353:          END IF
                    354:       END IF
                    355:       IF( INFO.EQ.0 ) THEN
                    356:          IF( M.LE.0 ) THEN
                    357:             INFO = -3
                    358:          ELSE IF( N.LE.0 ) THEN
                    359:             INFO = -4
                    360:          ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
                    361:             INFO = -6
                    362:          ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
                    363:             INFO = -8
                    364:          ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
                    365:             INFO = -10
                    366:          ELSE IF( LDD.LT.MAX( 1, M ) ) THEN
                    367:             INFO = -12
                    368:          ELSE IF( LDE.LT.MAX( 1, N ) ) THEN
                    369:             INFO = -14
                    370:          ELSE IF( LDF.LT.MAX( 1, M ) ) THEN
                    371:             INFO = -16
                    372:          END IF
                    373:       END IF
                    374: *
                    375:       IF( INFO.EQ.0 ) THEN
                    376:          IF( NOTRAN ) THEN
                    377:             IF( IJOB.EQ.1 .OR. IJOB.EQ.2 ) THEN
                    378:                LWMIN = MAX( 1, 2*M*N )
                    379:             ELSE
                    380:                LWMIN = 1
                    381:             END IF
                    382:          ELSE
                    383:             LWMIN = 1
                    384:          END IF
                    385:          WORK( 1 ) = LWMIN
                    386: *
                    387:          IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
                    388:             INFO = -20
                    389:          END IF
                    390:       END IF
                    391: *
                    392:       IF( INFO.NE.0 ) THEN
                    393:          CALL XERBLA( 'ZTGSYL', -INFO )
                    394:          RETURN
                    395:       ELSE IF( LQUERY ) THEN
                    396:          RETURN
                    397:       END IF
                    398: *
                    399: *     Quick return if possible
                    400: *
                    401:       IF( M.EQ.0 .OR. N.EQ.0 ) THEN
                    402:          SCALE = 1
                    403:          IF( NOTRAN ) THEN
                    404:             IF( IJOB.NE.0 ) THEN
                    405:                DIF = 0
                    406:             END IF
                    407:          END IF
                    408:          RETURN
                    409:       END IF
                    410: *
                    411: *     Determine  optimal block sizes MB and NB
                    412: *
                    413:       MB = ILAENV( 2, 'ZTGSYL', TRANS, M, N, -1, -1 )
                    414:       NB = ILAENV( 5, 'ZTGSYL', TRANS, M, N, -1, -1 )
                    415: *
                    416:       ISOLVE = 1
                    417:       IFUNC = 0
                    418:       IF( NOTRAN ) THEN
                    419:          IF( IJOB.GE.3 ) THEN
                    420:             IFUNC = IJOB - 2
                    421:             CALL ZLASET( 'F', M, N, CZERO, CZERO, C, LDC )
                    422:             CALL ZLASET( 'F', M, N, CZERO, CZERO, F, LDF )
                    423:          ELSE IF( IJOB.GE.1 .AND. NOTRAN ) THEN
                    424:             ISOLVE = 2
                    425:          END IF
                    426:       END IF
                    427: *
                    428:       IF( ( MB.LE.1 .AND. NB.LE.1 ) .OR. ( MB.GE.M .AND. NB.GE.N ) )
                    429:      $     THEN
                    430: *
                    431: *        Use unblocked Level 2 solver
                    432: *
                    433:          DO 30 IROUND = 1, ISOLVE
                    434: *
                    435:             SCALE = ONE
                    436:             DSCALE = ZERO
                    437:             DSUM = ONE
                    438:             PQ = M*N
                    439:             CALL ZTGSY2( TRANS, IFUNC, M, N, A, LDA, B, LDB, C, LDC, D,
                    440:      $                   LDD, E, LDE, F, LDF, SCALE, DSUM, DSCALE,
                    441:      $                   INFO )
                    442:             IF( DSCALE.NE.ZERO ) THEN
                    443:                IF( IJOB.EQ.1 .OR. IJOB.EQ.3 ) THEN
                    444:                   DIF = SQRT( DBLE( 2*M*N ) ) / ( DSCALE*SQRT( DSUM ) )
                    445:                ELSE
                    446:                   DIF = SQRT( DBLE( PQ ) ) / ( DSCALE*SQRT( DSUM ) )
                    447:                END IF
                    448:             END IF
                    449:             IF( ISOLVE.EQ.2 .AND. IROUND.EQ.1 ) THEN
                    450:                IF( NOTRAN ) THEN
                    451:                   IFUNC = IJOB
                    452:                END IF
                    453:                SCALE2 = SCALE
                    454:                CALL ZLACPY( 'F', M, N, C, LDC, WORK, M )
                    455:                CALL ZLACPY( 'F', M, N, F, LDF, WORK( M*N+1 ), M )
                    456:                CALL ZLASET( 'F', M, N, CZERO, CZERO, C, LDC )
                    457:                CALL ZLASET( 'F', M, N, CZERO, CZERO, F, LDF )
                    458:             ELSE IF( ISOLVE.EQ.2 .AND. IROUND.EQ.2 ) THEN
                    459:                CALL ZLACPY( 'F', M, N, WORK, M, C, LDC )
                    460:                CALL ZLACPY( 'F', M, N, WORK( M*N+1 ), M, F, LDF )
                    461:                SCALE = SCALE2
                    462:             END IF
                    463:    30    CONTINUE
                    464: *
                    465:          RETURN
                    466: *
                    467:       END IF
                    468: *
                    469: *     Determine block structure of A
                    470: *
                    471:       P = 0
                    472:       I = 1
                    473:    40 CONTINUE
                    474:       IF( I.GT.M )
                    475:      $   GO TO 50
                    476:       P = P + 1
                    477:       IWORK( P ) = I
                    478:       I = I + MB
                    479:       IF( I.GE.M )
                    480:      $   GO TO 50
                    481:       GO TO 40
                    482:    50 CONTINUE
                    483:       IWORK( P+1 ) = M + 1
                    484:       IF( IWORK( P ).EQ.IWORK( P+1 ) )
                    485:      $   P = P - 1
                    486: *
                    487: *     Determine block structure of B
                    488: *
                    489:       Q = P + 1
                    490:       J = 1
                    491:    60 CONTINUE
                    492:       IF( J.GT.N )
                    493:      $   GO TO 70
                    494: *
                    495:       Q = Q + 1
                    496:       IWORK( Q ) = J
                    497:       J = J + NB
                    498:       IF( J.GE.N )
                    499:      $   GO TO 70
                    500:       GO TO 60
                    501: *
                    502:    70 CONTINUE
                    503:       IWORK( Q+1 ) = N + 1
                    504:       IF( IWORK( Q ).EQ.IWORK( Q+1 ) )
                    505:      $   Q = Q - 1
                    506: *
                    507:       IF( NOTRAN ) THEN
                    508:          DO 150 IROUND = 1, ISOLVE
                    509: *
                    510: *           Solve (I, J) - subsystem
                    511: *               A(I, I) * R(I, J) - L(I, J) * B(J, J) = C(I, J)
                    512: *               D(I, I) * R(I, J) - L(I, J) * E(J, J) = F(I, J)
                    513: *           for I = P, P - 1, ..., 1; J = 1, 2, ..., Q
                    514: *
                    515:             PQ = 0
                    516:             SCALE = ONE
                    517:             DSCALE = ZERO
                    518:             DSUM = ONE
                    519:             DO 130 J = P + 2, Q
                    520:                JS = IWORK( J )
                    521:                JE = IWORK( J+1 ) - 1
                    522:                NB = JE - JS + 1
                    523:                DO 120 I = P, 1, -1
                    524:                   IS = IWORK( I )
                    525:                   IE = IWORK( I+1 ) - 1
                    526:                   MB = IE - IS + 1
                    527:                   CALL ZTGSY2( TRANS, IFUNC, MB, NB, A( IS, IS ), LDA,
                    528:      $                         B( JS, JS ), LDB, C( IS, JS ), LDC,
                    529:      $                         D( IS, IS ), LDD, E( JS, JS ), LDE,
                    530:      $                         F( IS, JS ), LDF, SCALOC, DSUM, DSCALE,
                    531:      $                         LINFO )
                    532:                   IF( LINFO.GT.0 )
                    533:      $               INFO = LINFO
                    534:                   PQ = PQ + MB*NB
                    535:                   IF( SCALOC.NE.ONE ) THEN
                    536:                      DO 80 K = 1, JS - 1
                    537:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
                    538:      $                              C( 1, K ), 1 )
                    539:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
                    540:      $                              F( 1, K ), 1 )
                    541:    80                CONTINUE
                    542:                      DO 90 K = JS, JE
                    543:                         CALL ZSCAL( IS-1, DCMPLX( SCALOC, ZERO ),
                    544:      $                              C( 1, K ), 1 )
                    545:                         CALL ZSCAL( IS-1, DCMPLX( SCALOC, ZERO ),
                    546:      $                              F( 1, K ), 1 )
                    547:    90                CONTINUE
                    548:                      DO 100 K = JS, JE
                    549:                         CALL ZSCAL( M-IE, DCMPLX( SCALOC, ZERO ),
                    550:      $                              C( IE+1, K ), 1 )
                    551:                         CALL ZSCAL( M-IE, DCMPLX( SCALOC, ZERO ),
                    552:      $                              F( IE+1, K ), 1 )
                    553:   100                CONTINUE
                    554:                      DO 110 K = JE + 1, N
                    555:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
                    556:      $                              C( 1, K ), 1 )
                    557:                         CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ),
                    558:      $                              F( 1, K ), 1 )
                    559:   110                CONTINUE
                    560:                      SCALE = SCALE*SCALOC
                    561:                   END IF
                    562: *
                    563: *                 Substitute R(I,J) and L(I,J) into remaining equation.
                    564: *
                    565:                   IF( I.GT.1 ) THEN
                    566:                      CALL ZGEMM( 'N', 'N', IS-1, NB, MB,
                    567:      $                           DCMPLX( -ONE, ZERO ), A( 1, IS ), LDA,
                    568:      $                           C( IS, JS ), LDC, DCMPLX( ONE, ZERO ),
                    569:      $                           C( 1, JS ), LDC )
                    570:                      CALL ZGEMM( 'N', 'N', IS-1, NB, MB,
                    571:      $                           DCMPLX( -ONE, ZERO ), D( 1, IS ), LDD,
                    572:      $                           C( IS, JS ), LDC, DCMPLX( ONE, ZERO ),
                    573:      $                           F( 1, JS ), LDF )
                    574:                   END IF
                    575:                   IF( J.LT.Q ) THEN
                    576:                      CALL ZGEMM( 'N', 'N', MB, N-JE, NB,
                    577:      $                           DCMPLX( ONE, ZERO ), F( IS, JS ), LDF,
                    578:      $                           B( JS, JE+1 ), LDB,
                    579:      $                           DCMPLX( ONE, ZERO ), C( IS, JE+1 ),
                    580:      $                           LDC )
                    581:                      CALL ZGEMM( 'N', 'N', MB, N-JE, NB,
                    582:      $                           DCMPLX( ONE, ZERO ), F( IS, JS ), LDF,
                    583:      $                           E( JS, JE+1 ), LDE,
                    584:      $                           DCMPLX( ONE, ZERO ), F( IS, JE+1 ),
                    585:      $                           LDF )
                    586:                   END IF
                    587:   120          CONTINUE
                    588:   130       CONTINUE
                    589:             IF( DSCALE.NE.ZERO ) THEN
                    590:                IF( IJOB.EQ.1 .OR. IJOB.EQ.3 ) THEN
                    591:                   DIF = SQRT( DBLE( 2*M*N ) ) / ( DSCALE*SQRT( DSUM ) )
                    592:                ELSE
                    593:                   DIF = SQRT( DBLE( PQ ) ) / ( DSCALE*SQRT( DSUM ) )
                    594:                END IF
                    595:             END IF
                    596:             IF( ISOLVE.EQ.2 .AND. IROUND.EQ.1 ) THEN
                    597:                IF( NOTRAN ) THEN
                    598:                   IFUNC = IJOB
                    599:                END IF
                    600:                SCALE2 = SCALE
                    601:                CALL ZLACPY( 'F', M, N, C, LDC, WORK, M )
                    602:                CALL ZLACPY( 'F', M, N, F, LDF, WORK( M*N+1 ), M )
                    603:                CALL ZLASET( 'F', M, N, CZERO, CZERO, C, LDC )
                    604:                CALL ZLASET( 'F', M, N, CZERO, CZERO, F, LDF )
                    605:             ELSE IF( ISOLVE.EQ.2 .AND. IROUND.EQ.2 ) THEN
                    606:                CALL ZLACPY( 'F', M, N, WORK, M, C, LDC )
                    607:                CALL ZLACPY( 'F', M, N, WORK( M*N+1 ), M, F, LDF )
                    608:                SCALE = SCALE2
                    609:             END IF
                    610:   150    CONTINUE
                    611:       ELSE
                    612: *
                    613: *        Solve transposed (I, J)-subsystem
1.8       bertrand  614: *            A(I, I)**H * R(I, J) + D(I, I)**H * L(I, J) = C(I, J)
1.1       bertrand  615: *            R(I, J) * B(J, J)  + L(I, J) * E(J, J) = -F(I, J)
                    616: *        for I = 1,2,..., P; J = Q, Q-1,..., 1
                    617: *
                    618:          SCALE = ONE
                    619:          DO 210 I = 1, P
                    620:             IS = IWORK( I )
                    621:             IE = IWORK( I+1 ) - 1
                    622:             MB = IE - IS + 1
                    623:             DO 200 J = Q, P + 2, -1
                    624:                JS = IWORK( J )
                    625:                JE = IWORK( J+1 ) - 1
                    626:                NB = JE - JS + 1
                    627:                CALL ZTGSY2( TRANS, IFUNC, MB, NB, A( IS, IS ), LDA,
                    628:      $                      B( JS, JS ), LDB, C( IS, JS ), LDC,
                    629:      $                      D( IS, IS ), LDD, E( JS, JS ), LDE,
                    630:      $                      F( IS, JS ), LDF, SCALOC, DSUM, DSCALE,
                    631:      $                      LINFO )
                    632:                IF( LINFO.GT.0 )
                    633:      $            INFO = LINFO
                    634:                IF( SCALOC.NE.ONE ) THEN
                    635:                   DO 160 K = 1, JS - 1
                    636:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), C( 1, K ),
                    637:      $                           1 )
                    638:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), F( 1, K ),
                    639:      $                           1 )
                    640:   160             CONTINUE
                    641:                   DO 170 K = JS, JE
                    642:                      CALL ZSCAL( IS-1, DCMPLX( SCALOC, ZERO ),
                    643:      $                           C( 1, K ), 1 )
                    644:                      CALL ZSCAL( IS-1, DCMPLX( SCALOC, ZERO ),
                    645:      $                           F( 1, K ), 1 )
                    646:   170             CONTINUE
                    647:                   DO 180 K = JS, JE
                    648:                      CALL ZSCAL( M-IE, DCMPLX( SCALOC, ZERO ),
                    649:      $                           C( IE+1, K ), 1 )
                    650:                      CALL ZSCAL( M-IE, DCMPLX( SCALOC, ZERO ),
                    651:      $                           F( IE+1, K ), 1 )
                    652:   180             CONTINUE
                    653:                   DO 190 K = JE + 1, N
                    654:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), C( 1, K ),
                    655:      $                           1 )
                    656:                      CALL ZSCAL( M, DCMPLX( SCALOC, ZERO ), F( 1, K ),
                    657:      $                           1 )
                    658:   190             CONTINUE
                    659:                   SCALE = SCALE*SCALOC
                    660:                END IF
                    661: *
                    662: *              Substitute R(I,J) and L(I,J) into remaining equation.
                    663: *
                    664:                IF( J.GT.P+2 ) THEN
                    665:                   CALL ZGEMM( 'N', 'C', MB, JS-1, NB,
                    666:      $                        DCMPLX( ONE, ZERO ), C( IS, JS ), LDC,
                    667:      $                        B( 1, JS ), LDB, DCMPLX( ONE, ZERO ),
                    668:      $                        F( IS, 1 ), LDF )
                    669:                   CALL ZGEMM( 'N', 'C', MB, JS-1, NB,
                    670:      $                        DCMPLX( ONE, ZERO ), F( IS, JS ), LDF,
                    671:      $                        E( 1, JS ), LDE, DCMPLX( ONE, ZERO ),
                    672:      $                        F( IS, 1 ), LDF )
                    673:                END IF
                    674:                IF( I.LT.P ) THEN
                    675:                   CALL ZGEMM( 'C', 'N', M-IE, NB, MB,
                    676:      $                        DCMPLX( -ONE, ZERO ), A( IS, IE+1 ), LDA,
                    677:      $                        C( IS, JS ), LDC, DCMPLX( ONE, ZERO ),
                    678:      $                        C( IE+1, JS ), LDC )
                    679:                   CALL ZGEMM( 'C', 'N', M-IE, NB, MB,
                    680:      $                        DCMPLX( -ONE, ZERO ), D( IS, IE+1 ), LDD,
                    681:      $                        F( IS, JS ), LDF, DCMPLX( ONE, ZERO ),
                    682:      $                        C( IE+1, JS ), LDC )
                    683:                END IF
                    684:   200       CONTINUE
                    685:   210    CONTINUE
                    686:       END IF
                    687: *
                    688:       WORK( 1 ) = LWMIN
                    689: *
                    690:       RETURN
                    691: *
                    692: *     End of ZTGSYL
                    693: *
                    694:       END

CVSweb interface <joel.bertrand@systella.fr>