Annotation of rpl/lapack/lapack/zunbdb4.f, revision 1.9

1.1       bertrand    1: *> \brief \b ZUNBDB4
                      2: *
                      3: *  =========== DOCUMENTATION ===========
                      4: *
1.5       bertrand    5: * Online html documentation available at
                      6: *            http://www.netlib.org/lapack/explore-html/
1.1       bertrand    7: *
                      8: *> \htmlonly
                      9: *> Download ZUNBDB4 + dependencies
                     10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunbdb4.f">
                     11: *> [TGZ]</a>
                     12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunbdb4.f">
                     13: *> [ZIP]</a>
                     14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunbdb4.f">
                     15: *> [TXT]</a>
                     16: *> \endhtmlonly
                     17: *
                     18: *  Definition:
                     19: *  ===========
                     20: *
                     21: *       SUBROUTINE ZUNBDB4( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
                     22: *                           TAUP1, TAUP2, TAUQ1, PHANTOM, WORK, LWORK,
                     23: *                           INFO )
1.5       bertrand   24: *
1.1       bertrand   25: *       .. Scalar Arguments ..
                     26: *       INTEGER            INFO, LWORK, M, P, Q, LDX11, LDX21
                     27: *       ..
                     28: *       .. Array Arguments ..
                     29: *       DOUBLE PRECISION   PHI(*), THETA(*)
                     30: *       COMPLEX*16         PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
                     31: *      $                   WORK(*), X11(LDX11,*), X21(LDX21,*)
                     32: *       ..
1.5       bertrand   33: *
                     34: *
1.1       bertrand   35: *> \par Purpose:
1.7       bertrand   36: *  =============
1.1       bertrand   37: *>
                     38: *>\verbatim
                     39: *>
                     40: *> ZUNBDB4 simultaneously bidiagonalizes the blocks of a tall and skinny
                     41: *> matrix X with orthonomal columns:
                     42: *>
                     43: *>                            [ B11 ]
                     44: *>      [ X11 ]   [ P1 |    ] [  0  ]
                     45: *>      [-----] = [---------] [-----] Q1**T .
                     46: *>      [ X21 ]   [    | P2 ] [ B21 ]
                     47: *>                            [  0  ]
                     48: *>
                     49: *> X11 is P-by-Q, and X21 is (M-P)-by-Q. M-Q must be no larger than P,
                     50: *> M-P, or Q. Routines ZUNBDB1, ZUNBDB2, and ZUNBDB3 handle cases in
                     51: *> which M-Q is not the minimum dimension.
                     52: *>
                     53: *> The unitary matrices P1, P2, and Q1 are P-by-P, (M-P)-by-(M-P),
                     54: *> and (M-Q)-by-(M-Q), respectively. They are represented implicitly by
                     55: *> Householder vectors.
                     56: *>
                     57: *> B11 and B12 are (M-Q)-by-(M-Q) bidiagonal matrices represented
                     58: *> implicitly by angles THETA, PHI.
                     59: *>
                     60: *>\endverbatim
                     61: *
                     62: *  Arguments:
                     63: *  ==========
                     64: *
                     65: *> \param[in] M
                     66: *> \verbatim
                     67: *>          M is INTEGER
                     68: *>           The number of rows X11 plus the number of rows in X21.
                     69: *> \endverbatim
                     70: *>
                     71: *> \param[in] P
                     72: *> \verbatim
                     73: *>          P is INTEGER
                     74: *>           The number of rows in X11. 0 <= P <= M.
                     75: *> \endverbatim
                     76: *>
                     77: *> \param[in] Q
                     78: *> \verbatim
                     79: *>          Q is INTEGER
                     80: *>           The number of columns in X11 and X21. 0 <= Q <= M and
                     81: *>           M-Q <= min(P,M-P,Q).
                     82: *> \endverbatim
                     83: *>
                     84: *> \param[in,out] X11
                     85: *> \verbatim
                     86: *>          X11 is COMPLEX*16 array, dimension (LDX11,Q)
                     87: *>           On entry, the top block of the matrix X to be reduced. On
                     88: *>           exit, the columns of tril(X11) specify reflectors for P1 and
                     89: *>           the rows of triu(X11,1) specify reflectors for Q1.
                     90: *> \endverbatim
                     91: *>
                     92: *> \param[in] LDX11
                     93: *> \verbatim
                     94: *>          LDX11 is INTEGER
                     95: *>           The leading dimension of X11. LDX11 >= P.
                     96: *> \endverbatim
                     97: *>
                     98: *> \param[in,out] X21
                     99: *> \verbatim
                    100: *>          X21 is COMPLEX*16 array, dimension (LDX21,Q)
                    101: *>           On entry, the bottom block of the matrix X to be reduced. On
                    102: *>           exit, the columns of tril(X21) specify reflectors for P2.
                    103: *> \endverbatim
                    104: *>
                    105: *> \param[in] LDX21
                    106: *> \verbatim
                    107: *>          LDX21 is INTEGER
                    108: *>           The leading dimension of X21. LDX21 >= M-P.
                    109: *> \endverbatim
                    110: *>
                    111: *> \param[out] THETA
                    112: *> \verbatim
                    113: *>          THETA is DOUBLE PRECISION array, dimension (Q)
                    114: *>           The entries of the bidiagonal blocks B11, B21 are defined by
                    115: *>           THETA and PHI. See Further Details.
                    116: *> \endverbatim
                    117: *>
                    118: *> \param[out] PHI
                    119: *> \verbatim
                    120: *>          PHI is DOUBLE PRECISION array, dimension (Q-1)
                    121: *>           The entries of the bidiagonal blocks B11, B21 are defined by
                    122: *>           THETA and PHI. See Further Details.
                    123: *> \endverbatim
                    124: *>
                    125: *> \param[out] TAUP1
                    126: *> \verbatim
1.9     ! bertrand  127: *>          TAUP1 is COMPLEX*16 array, dimension (M-Q)
1.1       bertrand  128: *>           The scalar factors of the elementary reflectors that define
                    129: *>           P1.
                    130: *> \endverbatim
                    131: *>
                    132: *> \param[out] TAUP2
                    133: *> \verbatim
1.9     ! bertrand  134: *>          TAUP2 is COMPLEX*16 array, dimension (M-Q)
1.1       bertrand  135: *>           The scalar factors of the elementary reflectors that define
                    136: *>           P2.
                    137: *> \endverbatim
                    138: *>
                    139: *> \param[out] TAUQ1
                    140: *> \verbatim
                    141: *>          TAUQ1 is COMPLEX*16 array, dimension (Q)
                    142: *>           The scalar factors of the elementary reflectors that define
                    143: *>           Q1.
                    144: *> \endverbatim
                    145: *>
                    146: *> \param[out] PHANTOM
                    147: *> \verbatim
                    148: *>          PHANTOM is COMPLEX*16 array, dimension (M)
                    149: *>           The routine computes an M-by-1 column vector Y that is
                    150: *>           orthogonal to the columns of [ X11; X21 ]. PHANTOM(1:P) and
                    151: *>           PHANTOM(P+1:M) contain Householder vectors for Y(1:P) and
                    152: *>           Y(P+1:M), respectively.
                    153: *> \endverbatim
                    154: *>
                    155: *> \param[out] WORK
                    156: *> \verbatim
                    157: *>          WORK is COMPLEX*16 array, dimension (LWORK)
                    158: *> \endverbatim
                    159: *>
                    160: *> \param[in] LWORK
                    161: *> \verbatim
                    162: *>          LWORK is INTEGER
                    163: *>           The dimension of the array WORK. LWORK >= M-Q.
1.5       bertrand  164: *>
1.1       bertrand  165: *>           If LWORK = -1, then a workspace query is assumed; the routine
                    166: *>           only calculates the optimal size of the WORK array, returns
                    167: *>           this value as the first entry of the WORK array, and no error
                    168: *>           message related to LWORK is issued by XERBLA.
                    169: *> \endverbatim
                    170: *>
                    171: *> \param[out] INFO
                    172: *> \verbatim
                    173: *>          INFO is INTEGER
                    174: *>           = 0:  successful exit.
                    175: *>           < 0:  if INFO = -i, the i-th argument had an illegal value.
                    176: *> \endverbatim
                    177: *
                    178: *  Authors:
                    179: *  ========
                    180: *
1.5       bertrand  181: *> \author Univ. of Tennessee
                    182: *> \author Univ. of California Berkeley
                    183: *> \author Univ. of Colorado Denver
                    184: *> \author NAG Ltd.
1.1       bertrand  185: *
                    186: *> \ingroup complex16OTHERcomputational
                    187: *
                    188: *> \par Further Details:
                    189: *  =====================
                    190: *>
                    191: *> \verbatim
                    192: *>
                    193: *>  The upper-bidiagonal blocks B11, B21 are represented implicitly by
                    194: *>  angles THETA(1), ..., THETA(Q) and PHI(1), ..., PHI(Q-1). Every entry
                    195: *>  in each bidiagonal band is a product of a sine or cosine of a THETA
                    196: *>  with a sine or cosine of a PHI. See [1] or ZUNCSD for details.
                    197: *>
                    198: *>  P1, P2, and Q1 are represented as products of elementary reflectors.
                    199: *>  See ZUNCSD2BY1 for details on generating P1, P2, and Q1 using ZUNGQR
                    200: *>  and ZUNGLQ.
                    201: *> \endverbatim
                    202: *
                    203: *> \par References:
                    204: *  ================
                    205: *>
                    206: *>  [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
                    207: *>      Algorithms, 50(1):33-65, 2009.
                    208: *>
                    209: *  =====================================================================
                    210:       SUBROUTINE ZUNBDB4( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
                    211:      $                    TAUP1, TAUP2, TAUQ1, PHANTOM, WORK, LWORK,
                    212:      $                    INFO )
                    213: *
1.9     ! bertrand  214: *  -- LAPACK computational routine --
1.1       bertrand  215: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    216: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
                    217: *
                    218: *     .. Scalar Arguments ..
                    219:       INTEGER            INFO, LWORK, M, P, Q, LDX11, LDX21
                    220: *     ..
                    221: *     .. Array Arguments ..
                    222:       DOUBLE PRECISION   PHI(*), THETA(*)
                    223:       COMPLEX*16         PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
                    224:      $                   WORK(*), X11(LDX11,*), X21(LDX21,*)
                    225: *     ..
                    226: *
                    227: *  ====================================================================
                    228: *
                    229: *     .. Parameters ..
                    230:       COMPLEX*16         NEGONE, ONE, ZERO
                    231:       PARAMETER          ( NEGONE = (-1.0D0,0.0D0), ONE = (1.0D0,0.0D0),
                    232:      $                     ZERO = (0.0D0,0.0D0) )
                    233: *     ..
                    234: *     .. Local Scalars ..
                    235:       DOUBLE PRECISION   C, S
                    236:       INTEGER            CHILDINFO, I, ILARF, IORBDB5, J, LLARF,
                    237:      $                   LORBDB5, LWORKMIN, LWORKOPT
                    238:       LOGICAL            LQUERY
                    239: *     ..
                    240: *     .. External Subroutines ..
1.7       bertrand  241:       EXTERNAL           ZLARF, ZLARFGP, ZUNBDB5, ZDROT, ZSCAL, ZLACGV,
                    242:      $                   XERBLA
1.1       bertrand  243: *     ..
                    244: *     .. External Functions ..
                    245:       DOUBLE PRECISION   DZNRM2
                    246:       EXTERNAL           DZNRM2
                    247: *     ..
                    248: *     .. Intrinsic Function ..
                    249:       INTRINSIC          ATAN2, COS, MAX, SIN, SQRT
                    250: *     ..
                    251: *     .. Executable Statements ..
                    252: *
                    253: *     Test input arguments
                    254: *
                    255:       INFO = 0
                    256:       LQUERY = LWORK .EQ. -1
                    257: *
                    258:       IF( M .LT. 0 ) THEN
                    259:          INFO = -1
                    260:       ELSE IF( P .LT. M-Q .OR. M-P .LT. M-Q ) THEN
                    261:          INFO = -2
                    262:       ELSE IF( Q .LT. M-Q .OR. Q .GT. M ) THEN
                    263:          INFO = -3
                    264:       ELSE IF( LDX11 .LT. MAX( 1, P ) ) THEN
                    265:          INFO = -5
                    266:       ELSE IF( LDX21 .LT. MAX( 1, M-P ) ) THEN
                    267:          INFO = -7
                    268:       END IF
                    269: *
                    270: *     Compute workspace
                    271: *
                    272:       IF( INFO .EQ. 0 ) THEN
                    273:          ILARF = 2
                    274:          LLARF = MAX( Q-1, P-1, M-P-1 )
                    275:          IORBDB5 = 2
                    276:          LORBDB5 = Q
                    277:          LWORKOPT = ILARF + LLARF - 1
                    278:          LWORKOPT = MAX( LWORKOPT, IORBDB5 + LORBDB5 - 1 )
                    279:          LWORKMIN = LWORKOPT
                    280:          WORK(1) = LWORKOPT
                    281:          IF( LWORK .LT. LWORKMIN .AND. .NOT.LQUERY ) THEN
                    282:            INFO = -14
                    283:          END IF
                    284:       END IF
                    285:       IF( INFO .NE. 0 ) THEN
                    286:          CALL XERBLA( 'ZUNBDB4', -INFO )
                    287:          RETURN
                    288:       ELSE IF( LQUERY ) THEN
                    289:          RETURN
                    290:       END IF
                    291: *
                    292: *     Reduce columns 1, ..., M-Q of X11 and X21
                    293: *
                    294:       DO I = 1, M-Q
                    295: *
                    296:          IF( I .EQ. 1 ) THEN
                    297:             DO J = 1, M
                    298:                PHANTOM(J) = ZERO
                    299:             END DO
                    300:             CALL ZUNBDB5( P, M-P, Q, PHANTOM(1), 1, PHANTOM(P+1), 1,
                    301:      $                    X11, LDX11, X21, LDX21, WORK(IORBDB5),
                    302:      $                    LORBDB5, CHILDINFO )
                    303:             CALL ZSCAL( P, NEGONE, PHANTOM(1), 1 )
                    304:             CALL ZLARFGP( P, PHANTOM(1), PHANTOM(2), 1, TAUP1(1) )
                    305:             CALL ZLARFGP( M-P, PHANTOM(P+1), PHANTOM(P+2), 1, TAUP2(1) )
                    306:             THETA(I) = ATAN2( DBLE( PHANTOM(1) ), DBLE( PHANTOM(P+1) ) )
                    307:             C = COS( THETA(I) )
                    308:             S = SIN( THETA(I) )
                    309:             PHANTOM(1) = ONE
                    310:             PHANTOM(P+1) = ONE
                    311:             CALL ZLARF( 'L', P, Q, PHANTOM(1), 1, DCONJG(TAUP1(1)), X11,
                    312:      $                  LDX11, WORK(ILARF) )
                    313:             CALL ZLARF( 'L', M-P, Q, PHANTOM(P+1), 1, DCONJG(TAUP2(1)),
                    314:      $                  X21, LDX21, WORK(ILARF) )
                    315:          ELSE
                    316:             CALL ZUNBDB5( P-I+1, M-P-I+1, Q-I+1, X11(I,I-1), 1,
                    317:      $                    X21(I,I-1), 1, X11(I,I), LDX11, X21(I,I),
                    318:      $                    LDX21, WORK(IORBDB5), LORBDB5, CHILDINFO )
                    319:             CALL ZSCAL( P-I+1, NEGONE, X11(I,I-1), 1 )
                    320:             CALL ZLARFGP( P-I+1, X11(I,I-1), X11(I+1,I-1), 1, TAUP1(I) )
                    321:             CALL ZLARFGP( M-P-I+1, X21(I,I-1), X21(I+1,I-1), 1,
                    322:      $                    TAUP2(I) )
                    323:             THETA(I) = ATAN2( DBLE( X11(I,I-1) ), DBLE( X21(I,I-1) ) )
                    324:             C = COS( THETA(I) )
                    325:             S = SIN( THETA(I) )
                    326:             X11(I,I-1) = ONE
                    327:             X21(I,I-1) = ONE
                    328:             CALL ZLARF( 'L', P-I+1, Q-I+1, X11(I,I-1), 1,
                    329:      $                  DCONJG(TAUP1(I)), X11(I,I), LDX11, WORK(ILARF) )
                    330:             CALL ZLARF( 'L', M-P-I+1, Q-I+1, X21(I,I-1), 1,
                    331:      $                  DCONJG(TAUP2(I)), X21(I,I), LDX21, WORK(ILARF) )
                    332:          END IF
                    333: *
                    334:          CALL ZDROT( Q-I+1, X11(I,I), LDX11, X21(I,I), LDX21, S, -C )
                    335:          CALL ZLACGV( Q-I+1, X21(I,I), LDX21 )
                    336:          CALL ZLARFGP( Q-I+1, X21(I,I), X21(I,I+1), LDX21, TAUQ1(I) )
                    337:          C = DBLE( X21(I,I) )
                    338:          X21(I,I) = ONE
                    339:          CALL ZLARF( 'R', P-I, Q-I+1, X21(I,I), LDX21, TAUQ1(I),
                    340:      $               X11(I+1,I), LDX11, WORK(ILARF) )
                    341:          CALL ZLARF( 'R', M-P-I, Q-I+1, X21(I,I), LDX21, TAUQ1(I),
                    342:      $               X21(I+1,I), LDX21, WORK(ILARF) )
                    343:          CALL ZLACGV( Q-I+1, X21(I,I), LDX21 )
                    344:          IF( I .LT. M-Q ) THEN
1.3       bertrand  345:             S = SQRT( DZNRM2( P-I, X11(I+1,I), 1 )**2
                    346:      $              + DZNRM2( M-P-I, X21(I+1,I), 1 )**2 )
1.1       bertrand  347:             PHI(I) = ATAN2( S, C )
                    348:          END IF
                    349: *
                    350:       END DO
                    351: *
                    352: *     Reduce the bottom-right portion of X11 to [ I 0 ]
                    353: *
                    354:       DO I = M - Q + 1, P
                    355:          CALL ZLACGV( Q-I+1, X11(I,I), LDX11 )
                    356:          CALL ZLARFGP( Q-I+1, X11(I,I), X11(I,I+1), LDX11, TAUQ1(I) )
                    357:          X11(I,I) = ONE
                    358:          CALL ZLARF( 'R', P-I, Q-I+1, X11(I,I), LDX11, TAUQ1(I),
                    359:      $               X11(I+1,I), LDX11, WORK(ILARF) )
                    360:          CALL ZLARF( 'R', Q-P, Q-I+1, X11(I,I), LDX11, TAUQ1(I),
                    361:      $               X21(M-Q+1,I), LDX21, WORK(ILARF) )
                    362:          CALL ZLACGV( Q-I+1, X11(I,I), LDX11 )
                    363:       END DO
                    364: *
                    365: *     Reduce the bottom-right portion of X21 to [ 0 I ]
                    366: *
                    367:       DO I = P + 1, Q
                    368:          CALL ZLACGV( Q-I+1, X21(M-Q+I-P,I), LDX21 )
                    369:          CALL ZLARFGP( Q-I+1, X21(M-Q+I-P,I), X21(M-Q+I-P,I+1), LDX21,
                    370:      $                 TAUQ1(I) )
                    371:          X21(M-Q+I-P,I) = ONE
                    372:          CALL ZLARF( 'R', Q-I, Q-I+1, X21(M-Q+I-P,I), LDX21, TAUQ1(I),
                    373:      $               X21(M-Q+I-P+1,I), LDX21, WORK(ILARF) )
                    374:          CALL ZLACGV( Q-I+1, X21(M-Q+I-P,I), LDX21 )
                    375:       END DO
                    376: *
                    377:       RETURN
                    378: *
                    379: *     End of ZUNBDB4
                    380: *
                    381:       END
                    382: 

CVSweb interface <joel.bertrand@systella.fr>