Annotation of rpl/lapack/lapack/zggbak.f, revision 1.6

1.1       bertrand    1:       SUBROUTINE ZGGBAK( JOB, SIDE, N, ILO, IHI, LSCALE, RSCALE, M, V,
                      2:      $                   LDV, INFO )
                      3: *
                      4: *  -- LAPACK routine (version 3.2) --
                      5: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                      6: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
                      7: *     November 2006
                      8: *
                      9: *     .. Scalar Arguments ..
                     10:       CHARACTER          JOB, SIDE
                     11:       INTEGER            IHI, ILO, INFO, LDV, M, N
                     12: *     ..
                     13: *     .. Array Arguments ..
                     14:       DOUBLE PRECISION   LSCALE( * ), RSCALE( * )
                     15:       COMPLEX*16         V( LDV, * )
                     16: *     ..
                     17: *
                     18: *  Purpose
                     19: *  =======
                     20: *
                     21: *  ZGGBAK forms the right or left eigenvectors of a complex generalized
                     22: *  eigenvalue problem A*x = lambda*B*x, by backward transformation on
                     23: *  the computed eigenvectors of the balanced pair of matrices output by
                     24: *  ZGGBAL.
                     25: *
                     26: *  Arguments
                     27: *  =========
                     28: *
                     29: *  JOB     (input) CHARACTER*1
                     30: *          Specifies the type of backward transformation required:
                     31: *          = 'N':  do nothing, return immediately;
                     32: *          = 'P':  do backward transformation for permutation only;
                     33: *          = 'S':  do backward transformation for scaling only;
                     34: *          = 'B':  do backward transformations for both permutation and
                     35: *                  scaling.
                     36: *          JOB must be the same as the argument JOB supplied to ZGGBAL.
                     37: *
                     38: *  SIDE    (input) CHARACTER*1
                     39: *          = 'R':  V contains right eigenvectors;
                     40: *          = 'L':  V contains left eigenvectors.
                     41: *
                     42: *  N       (input) INTEGER
                     43: *          The number of rows of the matrix V.  N >= 0.
                     44: *
                     45: *  ILO     (input) INTEGER
                     46: *  IHI     (input) INTEGER
                     47: *          The integers ILO and IHI determined by ZGGBAL.
                     48: *          1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.
                     49: *
                     50: *  LSCALE  (input) DOUBLE PRECISION array, dimension (N)
                     51: *          Details of the permutations and/or scaling factors applied
                     52: *          to the left side of A and B, as returned by ZGGBAL.
                     53: *
                     54: *  RSCALE  (input) DOUBLE PRECISION array, dimension (N)
                     55: *          Details of the permutations and/or scaling factors applied
                     56: *          to the right side of A and B, as returned by ZGGBAL.
                     57: *
                     58: *  M       (input) INTEGER
                     59: *          The number of columns of the matrix V.  M >= 0.
                     60: *
                     61: *  V       (input/output) COMPLEX*16 array, dimension (LDV,M)
                     62: *          On entry, the matrix of right or left eigenvectors to be
                     63: *          transformed, as returned by ZTGEVC.
                     64: *          On exit, V is overwritten by the transformed eigenvectors.
                     65: *
                     66: *  LDV     (input) INTEGER
                     67: *          The leading dimension of the matrix V. LDV >= max(1,N).
                     68: *
                     69: *  INFO    (output) INTEGER
                     70: *          = 0:  successful exit.
                     71: *          < 0:  if INFO = -i, the i-th argument had an illegal value.
                     72: *
                     73: *  Further Details
                     74: *  ===============
                     75: *
                     76: *  See R.C. Ward, Balancing the generalized eigenvalue problem,
                     77: *                 SIAM J. Sci. Stat. Comp. 2 (1981), 141-152.
                     78: *
                     79: *  =====================================================================
                     80: *
                     81: *     .. Local Scalars ..
                     82:       LOGICAL            LEFTV, RIGHTV
                     83:       INTEGER            I, K
                     84: *     ..
                     85: *     .. External Functions ..
                     86:       LOGICAL            LSAME
                     87:       EXTERNAL           LSAME
                     88: *     ..
                     89: *     .. External Subroutines ..
                     90:       EXTERNAL           XERBLA, ZDSCAL, ZSWAP
                     91: *     ..
                     92: *     .. Intrinsic Functions ..
                     93:       INTRINSIC          MAX
                     94: *     ..
                     95: *     .. Executable Statements ..
                     96: *
                     97: *     Test the input parameters
                     98: *
                     99:       RIGHTV = LSAME( SIDE, 'R' )
                    100:       LEFTV = LSAME( SIDE, 'L' )
                    101: *
                    102:       INFO = 0
                    103:       IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
                    104:      $    .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
                    105:          INFO = -1
                    106:       ELSE IF( .NOT.RIGHTV .AND. .NOT.LEFTV ) THEN
                    107:          INFO = -2
                    108:       ELSE IF( N.LT.0 ) THEN
                    109:          INFO = -3
                    110:       ELSE IF( ILO.LT.1 ) THEN
                    111:          INFO = -4
                    112:       ELSE IF( N.EQ.0 .AND. IHI.EQ.0 .AND. ILO.NE.1 ) THEN
                    113:          INFO = -4
                    114:       ELSE IF( N.GT.0 .AND. ( IHI.LT.ILO .OR. IHI.GT.MAX( 1, N ) ) )
                    115:      $   THEN
                    116:          INFO = -5
                    117:       ELSE IF( N.EQ.0 .AND. ILO.EQ.1 .AND. IHI.NE.0 ) THEN
                    118:          INFO = -5
                    119:       ELSE IF( M.LT.0 ) THEN
                    120:          INFO = -8
                    121:       ELSE IF( LDV.LT.MAX( 1, N ) ) THEN
                    122:          INFO = -10
                    123:       END IF
                    124:       IF( INFO.NE.0 ) THEN
                    125:          CALL XERBLA( 'ZGGBAK', -INFO )
                    126:          RETURN
                    127:       END IF
                    128: *
                    129: *     Quick return if possible
                    130: *
                    131:       IF( N.EQ.0 )
                    132:      $   RETURN
                    133:       IF( M.EQ.0 )
                    134:      $   RETURN
                    135:       IF( LSAME( JOB, 'N' ) )
                    136:      $   RETURN
                    137: *
                    138:       IF( ILO.EQ.IHI )
                    139:      $   GO TO 30
                    140: *
                    141: *     Backward balance
                    142: *
                    143:       IF( LSAME( JOB, 'S' ) .OR. LSAME( JOB, 'B' ) ) THEN
                    144: *
                    145: *        Backward transformation on right eigenvectors
                    146: *
                    147:          IF( RIGHTV ) THEN
                    148:             DO 10 I = ILO, IHI
                    149:                CALL ZDSCAL( M, RSCALE( I ), V( I, 1 ), LDV )
                    150:    10       CONTINUE
                    151:          END IF
                    152: *
                    153: *        Backward transformation on left eigenvectors
                    154: *
                    155:          IF( LEFTV ) THEN
                    156:             DO 20 I = ILO, IHI
                    157:                CALL ZDSCAL( M, LSCALE( I ), V( I, 1 ), LDV )
                    158:    20       CONTINUE
                    159:          END IF
                    160:       END IF
                    161: *
                    162: *     Backward permutation
                    163: *
                    164:    30 CONTINUE
                    165:       IF( LSAME( JOB, 'P' ) .OR. LSAME( JOB, 'B' ) ) THEN
                    166: *
                    167: *        Backward permutation on right eigenvectors
                    168: *
                    169:          IF( RIGHTV ) THEN
                    170:             IF( ILO.EQ.1 )
                    171:      $         GO TO 50
                    172:             DO 40 I = ILO - 1, 1, -1
                    173:                K = RSCALE( I )
                    174:                IF( K.EQ.I )
                    175:      $            GO TO 40
                    176:                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
                    177:    40       CONTINUE
                    178: *
                    179:    50       CONTINUE
                    180:             IF( IHI.EQ.N )
                    181:      $         GO TO 70
                    182:             DO 60 I = IHI + 1, N
                    183:                K = RSCALE( I )
                    184:                IF( K.EQ.I )
                    185:      $            GO TO 60
                    186:                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
                    187:    60       CONTINUE
                    188:          END IF
                    189: *
                    190: *        Backward permutation on left eigenvectors
                    191: *
                    192:    70    CONTINUE
                    193:          IF( LEFTV ) THEN
                    194:             IF( ILO.EQ.1 )
                    195:      $         GO TO 90
                    196:             DO 80 I = ILO - 1, 1, -1
                    197:                K = LSCALE( I )
                    198:                IF( K.EQ.I )
                    199:      $            GO TO 80
                    200:                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
                    201:    80       CONTINUE
                    202: *
                    203:    90       CONTINUE
                    204:             IF( IHI.EQ.N )
                    205:      $         GO TO 110
                    206:             DO 100 I = IHI + 1, N
                    207:                K = LSCALE( I )
                    208:                IF( K.EQ.I )
                    209:      $            GO TO 100
                    210:                CALL ZSWAP( M, V( I, 1 ), LDV, V( K, 1 ), LDV )
                    211:   100       CONTINUE
                    212:          END IF
                    213:       END IF
                    214: *
                    215:   110 CONTINUE
                    216: *
                    217:       RETURN
                    218: *
                    219: *     End of ZGGBAK
                    220: *
                    221:       END

CVSweb interface <joel.bertrand@systella.fr>