File:  [local] / rpl / lapack / lapack / ztplqt.f
Revision 1.5: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:41 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 ZTPLQT
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZTPLQT + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztplqt.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztplqt.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztplqt.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZTPLQT( M, N, L, MB, A, LDA, B, LDB, T, LDT, WORK,
   22: *                          INFO )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       INTEGER         INFO, LDA, LDB, LDT, N, M, L, MB
   26: *       ..
   27: *       .. Array Arguments ..
   28: *       COMPLEX*16      A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
   29: *       ..
   30: *
   31: *
   32: *> \par Purpose:
   33: *  =============
   34: *>
   35: *> \verbatim
   36: *>
   37: *> ZTPLQT computes a blocked LQ factorization of a complex
   38: *> "triangular-pentagonal" matrix C, which is composed of a
   39: *> triangular block A and pentagonal block B, using the compact
   40: *> WY representation for Q.
   41: *> \endverbatim
   42: *
   43: *  Arguments:
   44: *  ==========
   45: *
   46: *> \param[in] M
   47: *> \verbatim
   48: *>          M is INTEGER
   49: *>          The number of rows of the matrix B, and the order of the
   50: *>          triangular matrix A.
   51: *>          M >= 0.
   52: *> \endverbatim
   53: *>
   54: *> \param[in] N
   55: *> \verbatim
   56: *>          N is INTEGER
   57: *>          The number of columns of the matrix B.
   58: *>          N >= 0.
   59: *> \endverbatim
   60: *>
   61: *> \param[in] L
   62: *> \verbatim
   63: *>          L is INTEGER
   64: *>          The number of rows of the lower trapezoidal part of B.
   65: *>          MIN(M,N) >= L >= 0.  See Further Details.
   66: *> \endverbatim
   67: *>
   68: *> \param[in] MB
   69: *> \verbatim
   70: *>          MB is INTEGER
   71: *>          The block size to be used in the blocked QR.  M >= MB >= 1.
   72: *> \endverbatim
   73: *>
   74: *> \param[in,out] A
   75: *> \verbatim
   76: *>          A is COMPLEX*16 array, dimension (LDA,M)
   77: *>          On entry, the lower triangular M-by-M matrix A.
   78: *>          On exit, the elements on and below the diagonal of the array
   79: *>          contain the lower triangular matrix L.
   80: *> \endverbatim
   81: *>
   82: *> \param[in] LDA
   83: *> \verbatim
   84: *>          LDA is INTEGER
   85: *>          The leading dimension of the array A.  LDA >= max(1,M).
   86: *> \endverbatim
   87: *>
   88: *> \param[in,out] B
   89: *> \verbatim
   90: *>          B is COMPLEX*16 array, dimension (LDB,N)
   91: *>          On entry, the pentagonal M-by-N matrix B.  The first N-L columns
   92: *>          are rectangular, and the last L columns are lower trapezoidal.
   93: *>          On exit, B contains the pentagonal matrix V.  See Further Details.
   94: *> \endverbatim
   95: *>
   96: *> \param[in] LDB
   97: *> \verbatim
   98: *>          LDB is INTEGER
   99: *>          The leading dimension of the array B.  LDB >= max(1,M).
  100: *> \endverbatim
  101: *>
  102: *> \param[out] T
  103: *> \verbatim
  104: *>          T is COMPLEX*16 array, dimension (LDT,N)
  105: *>          The lower triangular block reflectors stored in compact form
  106: *>          as a sequence of upper triangular blocks.  See Further Details.
  107: *> \endverbatim
  108: *>
  109: *> \param[in] LDT
  110: *> \verbatim
  111: *>          LDT is INTEGER
  112: *>          The leading dimension of the array T.  LDT >= MB.
  113: *> \endverbatim
  114: *>
  115: *> \param[out] WORK
  116: *> \verbatim
  117: *>          WORK is COMPLEX*16 array, dimension (MB*M)
  118: *> \endverbatim
  119: *>
  120: *> \param[out] INFO
  121: *> \verbatim
  122: *>          INFO is INTEGER
  123: *>          = 0:  successful exit
  124: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
  125: *> \endverbatim
  126: *
  127: *  Authors:
  128: *  ========
  129: *
  130: *> \author Univ. of Tennessee
  131: *> \author Univ. of California Berkeley
  132: *> \author Univ. of Colorado Denver
  133: *> \author NAG Ltd.
  134: *
  135: *> \ingroup doubleOTHERcomputational
  136: *
  137: *> \par Further Details:
  138: *  =====================
  139: *>
  140: *> \verbatim
  141: *>
  142: *>  The input matrix C is a M-by-(M+N) matrix
  143: *>
  144: *>               C = [ A ] [ B ]
  145: *>
  146: *>
  147: *>  where A is an lower triangular M-by-M matrix, and B is M-by-N pentagonal
  148: *>  matrix consisting of a M-by-(N-L) rectangular matrix B1 on left of a M-by-L
  149: *>  upper trapezoidal matrix B2:
  150: *>          [ B ] = [ B1 ] [ B2 ]
  151: *>                   [ B1 ]  <- M-by-(N-L) rectangular
  152: *>                   [ B2 ]  <-     M-by-L lower trapezoidal.
  153: *>
  154: *>  The lower trapezoidal matrix B2 consists of the first L columns of a
  155: *>  M-by-M lower triangular matrix, where 0 <= L <= MIN(M,N).  If L=0,
  156: *>  B is rectangular M-by-N; if M=L=N, B is lower triangular.
  157: *>
  158: *>  The matrix W stores the elementary reflectors H(i) in the i-th row
  159: *>  above the diagonal (of A) in the M-by-(M+N) input matrix C
  160: *>            [ C ] = [ A ] [ B ]
  161: *>                   [ A ]  <- lower triangular M-by-M
  162: *>                   [ B ]  <- M-by-N pentagonal
  163: *>
  164: *>  so that W can be represented as
  165: *>            [ W ] = [ I ] [ V ]
  166: *>                   [ I ]  <- identity, M-by-M
  167: *>                   [ V ]  <- M-by-N, same form as B.
  168: *>
  169: *>  Thus, all of information needed for W is contained on exit in B, which
  170: *>  we call V above.  Note that V has the same form as B; that is,
  171: *>            [ V ] = [ V1 ] [ V2 ]
  172: *>                   [ V1 ] <- M-by-(N-L) rectangular
  173: *>                   [ V2 ] <-     M-by-L lower trapezoidal.
  174: *>
  175: *>  The rows of V represent the vectors which define the H(i)'s.
  176: *>
  177: *>  The number of blocks is B = ceiling(M/MB), where each
  178: *>  block is of order MB except for the last block, which is of order
  179: *>  IB = M - (M-1)*MB.  For each of the B blocks, a upper triangular block
  180: *>  reflector factor is computed: T1, T2, ..., TB.  The MB-by-MB (and IB-by-IB
  181: *>  for the last block) T's are stored in the MB-by-N matrix T as
  182: *>
  183: *>               T = [T1 T2 ... TB].
  184: *> \endverbatim
  185: *>
  186: *  =====================================================================
  187:       SUBROUTINE ZTPLQT( M, N, L, MB, A, LDA, B, LDB, T, LDT, WORK,
  188:      $                   INFO )
  189: *
  190: *  -- LAPACK computational routine --
  191: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  192: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  193: *
  194: *     .. Scalar Arguments ..
  195:       INTEGER     INFO, LDA, LDB, LDT, N, M, L, MB
  196: *     ..
  197: *     .. Array Arguments ..
  198:       COMPLEX*16  A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
  199: *     ..
  200: *
  201: * =====================================================================
  202: *
  203: *     ..
  204: *     .. Local Scalars ..
  205:       INTEGER    I, IB, LB, NB, IINFO
  206: *     ..
  207: *     .. External Subroutines ..
  208:       EXTERNAL   ZTPLQT2, ZTPRFB, XERBLA
  209: *     ..
  210: *     .. Executable Statements ..
  211: *
  212: *     Test the input arguments
  213: *
  214:       INFO = 0
  215:       IF( M.LT.0 ) THEN
  216:          INFO = -1
  217:       ELSE IF( N.LT.0 ) THEN
  218:          INFO = -2
  219:       ELSE IF( L.LT.0 .OR. (L.GT.MIN(M,N) .AND. MIN(M,N).GE.0)) THEN
  220:          INFO = -3
  221:       ELSE IF( MB.LT.1 .OR. (MB.GT.M .AND. M.GT.0)) THEN
  222:          INFO = -4
  223:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
  224:          INFO = -6
  225:       ELSE IF( LDB.LT.MAX( 1, M ) ) THEN
  226:          INFO = -8
  227:       ELSE IF( LDT.LT.MB ) THEN
  228:          INFO = -10
  229:       END IF
  230:       IF( INFO.NE.0 ) THEN
  231:          CALL XERBLA( 'ZTPLQT', -INFO )
  232:          RETURN
  233:       END IF
  234: *
  235: *     Quick return if possible
  236: *
  237:       IF( M.EQ.0 .OR. N.EQ.0 ) RETURN
  238: *
  239:       DO I = 1, M, MB
  240: *
  241: *     Compute the QR factorization of the current block
  242: *
  243:          IB = MIN( M-I+1, MB )
  244:          NB = MIN( N-L+I+IB-1, N )
  245:          IF( I.GE.L ) THEN
  246:             LB = 0
  247:          ELSE
  248:             LB = NB-N+L-I+1
  249:          END IF
  250: *
  251:          CALL ZTPLQT2( IB, NB, LB, A(I,I), LDA, B( I, 1 ), LDB,
  252:      $                 T(1, I ), LDT, IINFO )
  253: *
  254: *     Update by applying H**T to B(I+IB:M,:) from the right
  255: *
  256:          IF( I+IB.LE.M ) THEN
  257:             CALL ZTPRFB( 'R', 'N', 'F', 'R', M-I-IB+1, NB, IB, LB,
  258:      $                    B( I, 1 ), LDB, T( 1, I ), LDT,
  259:      $                    A( I+IB, I ), LDA, B( I+IB, 1 ), LDB,
  260:      $                    WORK, M-I-IB+1)
  261:          END IF
  262:       END DO
  263:       RETURN
  264: *
  265: *     End of ZTPLQT
  266: *
  267:       END

CVSweb interface <joel.bertrand@systella.fr>