File:  [local] / rpl / lapack / lapack / dgemlq.f
Revision 1.5: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:49 2023 UTC (9 months, 1 week 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 DGEMLQ
    2: *
    3: *  Definition:
    4: *  ===========
    5: *
    6: *      SUBROUTINE DGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T,
    7: *     $                   TSIZE, C, LDC, WORK, LWORK, INFO )
    8: *
    9: *
   10: *     .. Scalar Arguments ..
   11: *      CHARACTER          SIDE, TRANS
   12: *      INTEGER            INFO, LDA, M, N, K, LDT, TSIZE, LWORK, LDC
   13: *     ..
   14: *     .. Array Arguments ..
   15: *      DOUBLE PRECISION   A( LDA, * ), T( * ), C(LDC, * ), WORK( * )
   16: *     ..
   17: *
   18: *> \par Purpose:
   19: *  =============
   20: *>
   21: *> \verbatim
   22: *>
   23: *>     DGEMLQ overwrites the general real M-by-N matrix C with
   24: *>
   25: *>                    SIDE = 'L'     SIDE = 'R'
   26: *>    TRANS = 'N':      Q * C          C * Q
   27: *>    TRANS = 'T':      Q**T * C       C * Q**T
   28: *>    where Q is a real orthogonal matrix defined as the product
   29: *>    of blocked elementary reflectors computed by short wide LQ
   30: *>    factorization (DGELQ)
   31: *>
   32: *> \endverbatim
   33: *
   34: *  Arguments:
   35: *  ==========
   36: *
   37: *> \param[in] SIDE
   38: *> \verbatim
   39: *>          SIDE is CHARACTER*1
   40: *>          = 'L': apply Q or Q**T from the Left;
   41: *>          = 'R': apply Q or Q**T from the Right.
   42: *> \endverbatim
   43: *>
   44: *> \param[in] TRANS
   45: *> \verbatim
   46: *>          TRANS is CHARACTER*1
   47: *>          = 'N':  No transpose, apply Q;
   48: *>          = 'T':  Transpose, apply Q**T.
   49: *> \endverbatim
   50: *>
   51: *> \param[in] M
   52: *> \verbatim
   53: *>          M is INTEGER
   54: *>          The number of rows of the matrix A.  M >=0.
   55: *> \endverbatim
   56: *>
   57: *> \param[in] N
   58: *> \verbatim
   59: *>          N is INTEGER
   60: *>          The number of columns of the matrix C. N >= 0.
   61: *> \endverbatim
   62: *>
   63: *> \param[in] K
   64: *> \verbatim
   65: *>          K is INTEGER
   66: *>          The number of elementary reflectors whose product defines
   67: *>          the matrix Q.
   68: *>          If SIDE = 'L', M >= K >= 0;
   69: *>          if SIDE = 'R', N >= K >= 0.
   70: *>
   71: *> \endverbatim
   72: *>
   73: *> \param[in] A
   74: *> \verbatim
   75: *>          A is DOUBLE PRECISION array, dimension
   76: *>                               (LDA,M) if SIDE = 'L',
   77: *>                               (LDA,N) if SIDE = 'R'
   78: *>          Part of the data structure to represent Q as returned by DGELQ.
   79: *> \endverbatim
   80: *>
   81: *> \param[in] LDA
   82: *> \verbatim
   83: *>          LDA is INTEGER
   84: *>          The leading dimension of the array A. LDA >= max(1,K).
   85: *> \endverbatim
   86: *>
   87: *> \param[in] T
   88: *> \verbatim
   89: *>          T is DOUBLE PRECISION array, dimension (MAX(5,TSIZE)).
   90: *>          Part of the data structure to represent Q as returned by DGELQ.
   91: *> \endverbatim
   92: *>
   93: *> \param[in] TSIZE
   94: *> \verbatim
   95: *>          TSIZE is INTEGER
   96: *>          The dimension of the array T. TSIZE >= 5.
   97: *> \endverbatim
   98: *>
   99: *> \param[in,out] C
  100: *> \verbatim
  101: *>          C is DOUBLE PRECISION array, dimension (LDC,N)
  102: *>          On entry, the M-by-N matrix C.
  103: *>          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
  104: *> \endverbatim
  105: *>
  106: *> \param[in] LDC
  107: *> \verbatim
  108: *>          LDC is INTEGER
  109: *>          The leading dimension of the array C. LDC >= max(1,M).
  110: *> \endverbatim
  111: *>
  112: *> \param[out] WORK
  113: *> \verbatim
  114: *>         (workspace) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
  115: *> \endverbatim
  116: *>
  117: *> \param[in] LWORK
  118: *> \verbatim
  119: *>          LWORK is INTEGER
  120: *>          The dimension of the array WORK.
  121: *>          If LWORK = -1, then a workspace query is assumed. The routine
  122: *>          only calculates the size of the WORK array, returns this
  123: *>          value as WORK(1), and no error message related to WORK 
  124: *>          is issued by XERBLA.
  125: *> \endverbatim
  126: *>
  127: *> \param[out] INFO
  128: *> \verbatim
  129: *>          INFO is INTEGER
  130: *>          = 0:  successful exit
  131: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
  132: *> \endverbatim
  133: *
  134: *  Authors:
  135: *  ========
  136: *
  137: *> \author Univ. of Tennessee
  138: *> \author Univ. of California Berkeley
  139: *> \author Univ. of Colorado Denver
  140: *> \author NAG Ltd.
  141: *
  142: *> \par Further Details
  143: *  ====================
  144: *>
  145: *> \verbatim
  146: *>
  147: *> These details are particular for this LAPACK implementation. Users should not 
  148: *> take them for granted. These details may change in the future, and are not likely
  149: *> true for another LAPACK implementation. These details are relevant if one wants
  150: *> to try to understand the code. They are not part of the interface.
  151: *>
  152: *> In this version,
  153: *>
  154: *>          T(2): row block size (MB)
  155: *>          T(3): column block size (NB)
  156: *>          T(6:TSIZE): data structure needed for Q, computed by
  157: *>                           DLASWLQ or DGELQT
  158: *>
  159: *>  Depending on the matrix dimensions M and N, and row and column
  160: *>  block sizes MB and NB returned by ILAENV, DGELQ will use either
  161: *>  DLASWLQ (if the matrix is wide-and-short) or DGELQT to compute
  162: *>  the LQ factorization.
  163: *>  This version of DGEMLQ will use either DLAMSWLQ or DGEMLQT to 
  164: *>  multiply matrix Q by another matrix.
  165: *>  Further Details in DLAMSWLQ or DGEMLQT.
  166: *> \endverbatim
  167: *>
  168: *  =====================================================================
  169:       SUBROUTINE DGEMLQ( SIDE, TRANS, M, N, K, A, LDA, T, TSIZE,
  170:      $                   C, LDC, WORK, LWORK, INFO )
  171: *
  172: *  -- LAPACK computational routine --
  173: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  174: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  175: *
  176: *     .. Scalar Arguments ..
  177:       CHARACTER          SIDE, TRANS
  178:       INTEGER            INFO, LDA, M, N, K, TSIZE, LWORK, LDC
  179: *     ..
  180: *     .. Array Arguments ..
  181:       DOUBLE PRECISION   A( LDA, * ), T( * ), C( LDC, * ), WORK( * )
  182: *     ..
  183: *
  184: * =====================================================================
  185: *
  186: *     ..
  187: *     .. Local Scalars ..
  188:       LOGICAL            LEFT, RIGHT, TRAN, NOTRAN, LQUERY
  189:       INTEGER            MB, NB, LW, NBLCKS, MN
  190: *     ..
  191: *     .. External Functions ..
  192:       LOGICAL            LSAME
  193:       EXTERNAL           LSAME
  194: *     ..
  195: *     .. External Subroutines ..
  196:       EXTERNAL           DLAMSWLQ, DGEMLQT, XERBLA
  197: *     ..
  198: *     .. Intrinsic Functions ..
  199:       INTRINSIC          INT, MAX, MIN, MOD
  200: *     ..
  201: *     .. Executable Statements ..
  202: *
  203: *     Test the input arguments
  204: *
  205:       LQUERY  = LWORK.EQ.-1
  206:       NOTRAN  = LSAME( TRANS, 'N' )
  207:       TRAN    = LSAME( TRANS, 'T' )
  208:       LEFT    = LSAME( SIDE, 'L' )
  209:       RIGHT   = LSAME( SIDE, 'R' )
  210: *
  211:       MB = INT( T( 2 ) )
  212:       NB = INT( T( 3 ) )
  213:       IF( LEFT ) THEN
  214:         LW = N * MB
  215:         MN = M
  216:       ELSE
  217:         LW = M * MB
  218:         MN = N
  219:       END IF
  220: *
  221:       IF( ( NB.GT.K ) .AND. ( MN.GT.K ) ) THEN
  222:         IF( MOD( MN - K, NB - K ) .EQ. 0 ) THEN
  223:           NBLCKS = ( MN - K ) / ( NB - K )
  224:         ELSE
  225:           NBLCKS = ( MN - K ) / ( NB - K ) + 1
  226:         END IF
  227:       ELSE
  228:         NBLCKS = 1
  229:       END IF
  230: *
  231:       INFO = 0
  232:       IF( .NOT.LEFT .AND. .NOT.RIGHT ) THEN
  233:         INFO = -1
  234:       ELSE IF( .NOT.TRAN .AND. .NOT.NOTRAN ) THEN
  235:         INFO = -2
  236:       ELSE IF( M.LT.0 ) THEN
  237:         INFO = -3
  238:       ELSE IF( N.LT.0 ) THEN
  239:         INFO = -4
  240:       ELSE IF( K.LT.0 .OR. K.GT.MN ) THEN
  241:         INFO = -5
  242:       ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
  243:         INFO = -7
  244:       ELSE IF( TSIZE.LT.5 ) THEN
  245:         INFO = -9
  246:       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
  247:         INFO = -11
  248:       ELSE IF( ( LWORK.LT.MAX( 1, LW ) ) .AND. ( .NOT.LQUERY ) ) THEN
  249:         INFO = -13
  250:       END IF
  251: *
  252:       IF( INFO.EQ.0 ) THEN
  253:         WORK( 1 ) = LW
  254:       END IF
  255: *
  256:       IF( INFO.NE.0 ) THEN
  257:         CALL XERBLA( 'DGEMLQ', -INFO )
  258:         RETURN
  259:       ELSE IF( LQUERY ) THEN
  260:         RETURN
  261:       END IF
  262: *
  263: *     Quick return if possible
  264: *
  265:       IF( MIN( M, N, K ).EQ.0 ) THEN
  266:         RETURN
  267:       END IF
  268: *
  269:       IF( ( LEFT .AND. M.LE.K ) .OR. ( RIGHT .AND. N.LE.K )
  270:      $     .OR. ( NB.LE.K ) .OR. ( NB.GE.MAX( M, N, K ) ) ) THEN
  271:         CALL DGEMLQT( SIDE, TRANS, M, N, K, MB, A, LDA,
  272:      $                T( 6 ), MB, C, LDC, WORK, INFO )
  273:       ELSE
  274:         CALL DLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T( 6 ),
  275:      $                 MB, C, LDC, WORK, LWORK, INFO )
  276:       END IF
  277: *
  278:       WORK( 1 ) = LW
  279: *
  280:       RETURN
  281: *
  282: *     End of DGEMLQ
  283: *
  284:       END

CVSweb interface <joel.bertrand@systella.fr>