File:  [local] / rpl / lapack / lapack / zggsvd.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:21 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief <b> ZGGSVD computes the singular value decomposition (SVD) for OTHER matrices</b>
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZGGSVD + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zggsvd.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zggsvd.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zggsvd.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZGGSVD( JOBU, JOBV, JOBQ, M, N, P, K, L, A, LDA, B,
   22: *                          LDB, ALPHA, BETA, U, LDU, V, LDV, Q, LDQ, WORK,
   23: *                          RWORK, IWORK, INFO )
   24: *
   25: *       .. Scalar Arguments ..
   26: *       CHARACTER          JOBQ, JOBU, JOBV
   27: *       INTEGER            INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
   28: *       ..
   29: *       .. Array Arguments ..
   30: *       INTEGER            IWORK( * )
   31: *       DOUBLE PRECISION   ALPHA( * ), BETA( * ), RWORK( * )
   32: *       COMPLEX*16         A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
   33: *      $                   U( LDU, * ), V( LDV, * ), WORK( * )
   34: *       ..
   35: *
   36: *
   37: *> \par Purpose:
   38: *  =============
   39: *>
   40: *> \verbatim
   41: *>
   42: *> This routine is deprecated and has been replaced by routine ZGGSVD3.
   43: *>
   44: *> ZGGSVD computes the generalized singular value decomposition (GSVD)
   45: *> of an M-by-N complex matrix A and P-by-N complex matrix B:
   46: *>
   47: *>       U**H*A*Q = D1*( 0 R ),    V**H*B*Q = D2*( 0 R )
   48: *>
   49: *> where U, V and Q are unitary matrices.
   50: *> Let K+L = the effective numerical rank of the
   51: *> matrix (A**H,B**H)**H, then R is a (K+L)-by-(K+L) nonsingular upper
   52: *> triangular matrix, D1 and D2 are M-by-(K+L) and P-by-(K+L) "diagonal"
   53: *> matrices and of the following structures, respectively:
   54: *>
   55: *> If M-K-L >= 0,
   56: *>
   57: *>                     K  L
   58: *>        D1 =     K ( I  0 )
   59: *>                 L ( 0  C )
   60: *>             M-K-L ( 0  0 )
   61: *>
   62: *>                   K  L
   63: *>        D2 =   L ( 0  S )
   64: *>             P-L ( 0  0 )
   65: *>
   66: *>                 N-K-L  K    L
   67: *>   ( 0 R ) = K (  0   R11  R12 )
   68: *>             L (  0    0   R22 )
   69: *> where
   70: *>
   71: *>   C = diag( ALPHA(K+1), ... , ALPHA(K+L) ),
   72: *>   S = diag( BETA(K+1),  ... , BETA(K+L) ),
   73: *>   C**2 + S**2 = I.
   74: *>
   75: *>   R is stored in A(1:K+L,N-K-L+1:N) on exit.
   76: *>
   77: *> If M-K-L < 0,
   78: *>
   79: *>                   K M-K K+L-M
   80: *>        D1 =   K ( I  0    0   )
   81: *>             M-K ( 0  C    0   )
   82: *>
   83: *>                     K M-K K+L-M
   84: *>        D2 =   M-K ( 0  S    0  )
   85: *>             K+L-M ( 0  0    I  )
   86: *>               P-L ( 0  0    0  )
   87: *>
   88: *>                    N-K-L  K   M-K  K+L-M
   89: *>   ( 0 R ) =     K ( 0    R11  R12  R13  )
   90: *>               M-K ( 0     0   R22  R23  )
   91: *>             K+L-M ( 0     0    0   R33  )
   92: *>
   93: *> where
   94: *>
   95: *>   C = diag( ALPHA(K+1), ... , ALPHA(M) ),
   96: *>   S = diag( BETA(K+1),  ... , BETA(M) ),
   97: *>   C**2 + S**2 = I.
   98: *>
   99: *>   (R11 R12 R13 ) is stored in A(1:M, N-K-L+1:N), and R33 is stored
  100: *>   ( 0  R22 R23 )
  101: *>   in B(M-K+1:L,N+M-K-L+1:N) on exit.
  102: *>
  103: *> The routine computes C, S, R, and optionally the unitary
  104: *> transformation matrices U, V and Q.
  105: *>
  106: *> In particular, if B is an N-by-N nonsingular matrix, then the GSVD of
  107: *> A and B implicitly gives the SVD of A*inv(B):
  108: *>                      A*inv(B) = U*(D1*inv(D2))*V**H.
  109: *> If ( A**H,B**H)**H has orthnormal columns, then the GSVD of A and B is also
  110: *> equal to the CS decomposition of A and B. Furthermore, the GSVD can
  111: *> be used to derive the solution of the eigenvalue problem:
  112: *>                      A**H*A x = lambda* B**H*B x.
  113: *> In some literature, the GSVD of A and B is presented in the form
  114: *>                  U**H*A*X = ( 0 D1 ),   V**H*B*X = ( 0 D2 )
  115: *> where U and V are orthogonal and X is nonsingular, and D1 and D2 are
  116: *> ``diagonal''.  The former GSVD form can be converted to the latter
  117: *> form by taking the nonsingular matrix X as
  118: *>
  119: *>                       X = Q*(  I   0    )
  120: *>                             (  0 inv(R) )
  121: *> \endverbatim
  122: *
  123: *  Arguments:
  124: *  ==========
  125: *
  126: *> \param[in] JOBU
  127: *> \verbatim
  128: *>          JOBU is CHARACTER*1
  129: *>          = 'U':  Unitary matrix U is computed;
  130: *>          = 'N':  U is not computed.
  131: *> \endverbatim
  132: *>
  133: *> \param[in] JOBV
  134: *> \verbatim
  135: *>          JOBV is CHARACTER*1
  136: *>          = 'V':  Unitary matrix V is computed;
  137: *>          = 'N':  V is not computed.
  138: *> \endverbatim
  139: *>
  140: *> \param[in] JOBQ
  141: *> \verbatim
  142: *>          JOBQ is CHARACTER*1
  143: *>          = 'Q':  Unitary matrix Q is computed;
  144: *>          = 'N':  Q is not computed.
  145: *> \endverbatim
  146: *>
  147: *> \param[in] M
  148: *> \verbatim
  149: *>          M is INTEGER
  150: *>          The number of rows of the matrix A.  M >= 0.
  151: *> \endverbatim
  152: *>
  153: *> \param[in] N
  154: *> \verbatim
  155: *>          N is INTEGER
  156: *>          The number of columns of the matrices A and B.  N >= 0.
  157: *> \endverbatim
  158: *>
  159: *> \param[in] P
  160: *> \verbatim
  161: *>          P is INTEGER
  162: *>          The number of rows of the matrix B.  P >= 0.
  163: *> \endverbatim
  164: *>
  165: *> \param[out] K
  166: *> \verbatim
  167: *>          K is INTEGER
  168: *> \endverbatim
  169: *>
  170: *> \param[out] L
  171: *> \verbatim
  172: *>          L is INTEGER
  173: *>
  174: *>          On exit, K and L specify the dimension of the subblocks
  175: *>          described in Purpose.
  176: *>          K + L = effective numerical rank of (A**H,B**H)**H.
  177: *> \endverbatim
  178: *>
  179: *> \param[in,out] A
  180: *> \verbatim
  181: *>          A is COMPLEX*16 array, dimension (LDA,N)
  182: *>          On entry, the M-by-N matrix A.
  183: *>          On exit, A contains the triangular matrix R, or part of R.
  184: *>          See Purpose for details.
  185: *> \endverbatim
  186: *>
  187: *> \param[in] LDA
  188: *> \verbatim
  189: *>          LDA is INTEGER
  190: *>          The leading dimension of the array A. LDA >= max(1,M).
  191: *> \endverbatim
  192: *>
  193: *> \param[in,out] B
  194: *> \verbatim
  195: *>          B is COMPLEX*16 array, dimension (LDB,N)
  196: *>          On entry, the P-by-N matrix B.
  197: *>          On exit, B contains part of the triangular matrix R if
  198: *>          M-K-L < 0.  See Purpose for details.
  199: *> \endverbatim
  200: *>
  201: *> \param[in] LDB
  202: *> \verbatim
  203: *>          LDB is INTEGER
  204: *>          The leading dimension of the array B. LDB >= max(1,P).
  205: *> \endverbatim
  206: *>
  207: *> \param[out] ALPHA
  208: *> \verbatim
  209: *>          ALPHA is DOUBLE PRECISION array, dimension (N)
  210: *> \endverbatim
  211: *>
  212: *> \param[out] BETA
  213: *> \verbatim
  214: *>          BETA is DOUBLE PRECISION array, dimension (N)
  215: *>
  216: *>          On exit, ALPHA and BETA contain the generalized singular
  217: *>          value pairs of A and B;
  218: *>            ALPHA(1:K) = 1,
  219: *>            BETA(1:K)  = 0,
  220: *>          and if M-K-L >= 0,
  221: *>            ALPHA(K+1:K+L) = C,
  222: *>            BETA(K+1:K+L)  = S,
  223: *>          or if M-K-L < 0,
  224: *>            ALPHA(K+1:M)=C, ALPHA(M+1:K+L)=0
  225: *>            BETA(K+1:M) =S, BETA(M+1:K+L) =1
  226: *>          and
  227: *>            ALPHA(K+L+1:N) = 0
  228: *>            BETA(K+L+1:N)  = 0
  229: *> \endverbatim
  230: *>
  231: *> \param[out] U
  232: *> \verbatim
  233: *>          U is COMPLEX*16 array, dimension (LDU,M)
  234: *>          If JOBU = 'U', U contains the M-by-M unitary matrix U.
  235: *>          If JOBU = 'N', U is not referenced.
  236: *> \endverbatim
  237: *>
  238: *> \param[in] LDU
  239: *> \verbatim
  240: *>          LDU is INTEGER
  241: *>          The leading dimension of the array U. LDU >= max(1,M) if
  242: *>          JOBU = 'U'; LDU >= 1 otherwise.
  243: *> \endverbatim
  244: *>
  245: *> \param[out] V
  246: *> \verbatim
  247: *>          V is COMPLEX*16 array, dimension (LDV,P)
  248: *>          If JOBV = 'V', V contains the P-by-P unitary matrix V.
  249: *>          If JOBV = 'N', V is not referenced.
  250: *> \endverbatim
  251: *>
  252: *> \param[in] LDV
  253: *> \verbatim
  254: *>          LDV is INTEGER
  255: *>          The leading dimension of the array V. LDV >= max(1,P) if
  256: *>          JOBV = 'V'; LDV >= 1 otherwise.
  257: *> \endverbatim
  258: *>
  259: *> \param[out] Q
  260: *> \verbatim
  261: *>          Q is COMPLEX*16 array, dimension (LDQ,N)
  262: *>          If JOBQ = 'Q', Q contains the N-by-N unitary matrix Q.
  263: *>          If JOBQ = 'N', Q is not referenced.
  264: *> \endverbatim
  265: *>
  266: *> \param[in] LDQ
  267: *> \verbatim
  268: *>          LDQ is INTEGER
  269: *>          The leading dimension of the array Q. LDQ >= max(1,N) if
  270: *>          JOBQ = 'Q'; LDQ >= 1 otherwise.
  271: *> \endverbatim
  272: *>
  273: *> \param[out] WORK
  274: *> \verbatim
  275: *>          WORK is COMPLEX*16 array, dimension (max(3*N,M,P)+N)
  276: *> \endverbatim
  277: *>
  278: *> \param[out] RWORK
  279: *> \verbatim
  280: *>          RWORK is DOUBLE PRECISION array, dimension (2*N)
  281: *> \endverbatim
  282: *>
  283: *> \param[out] IWORK
  284: *> \verbatim
  285: *>          IWORK is INTEGER array, dimension (N)
  286: *>          On exit, IWORK stores the sorting information. More
  287: *>          precisely, the following loop will sort ALPHA
  288: *>             for I = K+1, min(M,K+L)
  289: *>                 swap ALPHA(I) and ALPHA(IWORK(I))
  290: *>             endfor
  291: *>          such that ALPHA(1) >= ALPHA(2) >= ... >= ALPHA(N).
  292: *> \endverbatim
  293: *>
  294: *> \param[out] INFO
  295: *> \verbatim
  296: *>          INFO is INTEGER
  297: *>          = 0:  successful exit.
  298: *>          < 0:  if INFO = -i, the i-th argument had an illegal value.
  299: *>          > 0:  if INFO = 1, the Jacobi-type procedure failed to
  300: *>                converge.  For further details, see subroutine ZTGSJA.
  301: *> \endverbatim
  302: *
  303: *> \par Internal Parameters:
  304: *  =========================
  305: *>
  306: *> \verbatim
  307: *>  TOLA    DOUBLE PRECISION
  308: *>  TOLB    DOUBLE PRECISION
  309: *>          TOLA and TOLB are the thresholds to determine the effective
  310: *>          rank of (A**H,B**H)**H. Generally, they are set to
  311: *>                   TOLA = MAX(M,N)*norm(A)*MAZHEPS,
  312: *>                   TOLB = MAX(P,N)*norm(B)*MAZHEPS.
  313: *>          The size of TOLA and TOLB may affect the size of backward
  314: *>          errors of the decomposition.
  315: *> \endverbatim
  316: *
  317: *  Authors:
  318: *  ========
  319: *
  320: *> \author Univ. of Tennessee
  321: *> \author Univ. of California Berkeley
  322: *> \author Univ. of Colorado Denver
  323: *> \author NAG Ltd.
  324: *
  325: *> \ingroup complex16OTHERsing
  326: *
  327: *> \par Contributors:
  328: *  ==================
  329: *>
  330: *>     Ming Gu and Huan Ren, Computer Science Division, University of
  331: *>     California at Berkeley, USA
  332: *>
  333: *  =====================================================================
  334:       SUBROUTINE ZGGSVD( JOBU, JOBV, JOBQ, M, N, P, K, L, A, LDA, B,
  335:      $                   LDB, ALPHA, BETA, U, LDU, V, LDV, Q, LDQ, WORK,
  336:      $                   RWORK, IWORK, INFO )
  337: *
  338: *  -- LAPACK driver routine --
  339: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  340: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  341: *
  342: *     .. Scalar Arguments ..
  343:       CHARACTER          JOBQ, JOBU, JOBV
  344:       INTEGER            INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
  345: *     ..
  346: *     .. Array Arguments ..
  347:       INTEGER            IWORK( * )
  348:       DOUBLE PRECISION   ALPHA( * ), BETA( * ), RWORK( * )
  349:       COMPLEX*16         A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
  350:      $                   U( LDU, * ), V( LDV, * ), WORK( * )
  351: *     ..
  352: *
  353: *  =====================================================================
  354: *
  355: *     .. Local Scalars ..
  356:       LOGICAL            WANTQ, WANTU, WANTV
  357:       INTEGER            I, IBND, ISUB, J, NCYCLE
  358:       DOUBLE PRECISION   ANORM, BNORM, SMAX, TEMP, TOLA, TOLB, ULP, UNFL
  359: *     ..
  360: *     .. External Functions ..
  361:       LOGICAL            LSAME
  362:       DOUBLE PRECISION   DLAMCH, ZLANGE
  363:       EXTERNAL           LSAME, DLAMCH, ZLANGE
  364: *     ..
  365: *     .. External Subroutines ..
  366:       EXTERNAL           DCOPY, XERBLA, ZGGSVP, ZTGSJA
  367: *     ..
  368: *     .. Intrinsic Functions ..
  369:       INTRINSIC          MAX, MIN
  370: *     ..
  371: *     .. Executable Statements ..
  372: *
  373: *     Decode and test the input parameters
  374: *
  375:       WANTU = LSAME( JOBU, 'U' )
  376:       WANTV = LSAME( JOBV, 'V' )
  377:       WANTQ = LSAME( JOBQ, 'Q' )
  378: *
  379:       INFO = 0
  380:       IF( .NOT.( WANTU .OR. LSAME( JOBU, 'N' ) ) ) THEN
  381:          INFO = -1
  382:       ELSE IF( .NOT.( WANTV .OR. LSAME( JOBV, 'N' ) ) ) THEN
  383:          INFO = -2
  384:       ELSE IF( .NOT.( WANTQ .OR. LSAME( JOBQ, 'N' ) ) ) THEN
  385:          INFO = -3
  386:       ELSE IF( M.LT.0 ) THEN
  387:          INFO = -4
  388:       ELSE IF( N.LT.0 ) THEN
  389:          INFO = -5
  390:       ELSE IF( P.LT.0 ) THEN
  391:          INFO = -6
  392:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
  393:          INFO = -10
  394:       ELSE IF( LDB.LT.MAX( 1, P ) ) THEN
  395:          INFO = -12
  396:       ELSE IF( LDU.LT.1 .OR. ( WANTU .AND. LDU.LT.M ) ) THEN
  397:          INFO = -16
  398:       ELSE IF( LDV.LT.1 .OR. ( WANTV .AND. LDV.LT.P ) ) THEN
  399:          INFO = -18
  400:       ELSE IF( LDQ.LT.1 .OR. ( WANTQ .AND. LDQ.LT.N ) ) THEN
  401:          INFO = -20
  402:       END IF
  403:       IF( INFO.NE.0 ) THEN
  404:          CALL XERBLA( 'ZGGSVD', -INFO )
  405:          RETURN
  406:       END IF
  407: *
  408: *     Compute the Frobenius norm of matrices A and B
  409: *
  410:       ANORM = ZLANGE( '1', M, N, A, LDA, RWORK )
  411:       BNORM = ZLANGE( '1', P, N, B, LDB, RWORK )
  412: *
  413: *     Get machine precision and set up threshold for determining
  414: *     the effective numerical rank of the matrices A and B.
  415: *
  416:       ULP = DLAMCH( 'Precision' )
  417:       UNFL = DLAMCH( 'Safe Minimum' )
  418:       TOLA = MAX( M, N )*MAX( ANORM, UNFL )*ULP
  419:       TOLB = MAX( P, N )*MAX( BNORM, UNFL )*ULP
  420: *
  421:       CALL ZGGSVP( JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB, TOLA,
  422:      $             TOLB, K, L, U, LDU, V, LDV, Q, LDQ, IWORK, RWORK,
  423:      $             WORK, WORK( N+1 ), INFO )
  424: *
  425: *     Compute the GSVD of two upper "triangular" matrices
  426: *
  427:       CALL ZTGSJA( JOBU, JOBV, JOBQ, M, P, N, K, L, A, LDA, B, LDB,
  428:      $             TOLA, TOLB, ALPHA, BETA, U, LDU, V, LDV, Q, LDQ,
  429:      $             WORK, NCYCLE, INFO )
  430: *
  431: *     Sort the singular values and store the pivot indices in IWORK
  432: *     Copy ALPHA to RWORK, then sort ALPHA in RWORK
  433: *
  434:       CALL DCOPY( N, ALPHA, 1, RWORK, 1 )
  435:       IBND = MIN( L, M-K )
  436:       DO 20 I = 1, IBND
  437: *
  438: *        Scan for largest ALPHA(K+I)
  439: *
  440:          ISUB = I
  441:          SMAX = RWORK( K+I )
  442:          DO 10 J = I + 1, IBND
  443:             TEMP = RWORK( K+J )
  444:             IF( TEMP.GT.SMAX ) THEN
  445:                ISUB = J
  446:                SMAX = TEMP
  447:             END IF
  448:    10    CONTINUE
  449:          IF( ISUB.NE.I ) THEN
  450:             RWORK( K+ISUB ) = RWORK( K+I )
  451:             RWORK( K+I ) = SMAX
  452:             IWORK( K+I ) = K + ISUB
  453:          ELSE
  454:             IWORK( K+I ) = K + I
  455:          END IF
  456:    20 CONTINUE
  457: *
  458:       RETURN
  459: *
  460: *     End of ZGGSVD
  461: *
  462:       END

CVSweb interface <joel.bertrand@systella.fr>