File:  [local] / rpl / lapack / lapack / zunmrz.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:45 2023 UTC (9 months 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 ZUNMRZ
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZUNMRZ + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunmrz.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunmrz.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmrz.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
   22: *                          WORK, LWORK, INFO )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       CHARACTER          SIDE, TRANS
   26: *       INTEGER            INFO, K, L, LDA, LDC, LWORK, M, N
   27: *       ..
   28: *       .. Array Arguments ..
   29: *       COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
   30: *       ..
   31: *
   32: *
   33: *> \par Purpose:
   34: *  =============
   35: *>
   36: *> \verbatim
   37: *>
   38: *> ZUNMRZ overwrites the general complex M-by-N matrix C with
   39: *>
   40: *>                 SIDE = 'L'     SIDE = 'R'
   41: *> TRANS = 'N':      Q * C          C * Q
   42: *> TRANS = 'C':      Q**H * C       C * Q**H
   43: *>
   44: *> where Q is a complex unitary matrix defined as the product of k
   45: *> elementary reflectors
   46: *>
   47: *>       Q = H(1) H(2) . . . H(k)
   48: *>
   49: *> as returned by ZTZRZF. Q is of order M if SIDE = 'L' and of order N
   50: *> if SIDE = 'R'.
   51: *> \endverbatim
   52: *
   53: *  Arguments:
   54: *  ==========
   55: *
   56: *> \param[in] SIDE
   57: *> \verbatim
   58: *>          SIDE is CHARACTER*1
   59: *>          = 'L': apply Q or Q**H from the Left;
   60: *>          = 'R': apply Q or Q**H from the Right.
   61: *> \endverbatim
   62: *>
   63: *> \param[in] TRANS
   64: *> \verbatim
   65: *>          TRANS is CHARACTER*1
   66: *>          = 'N':  No transpose, apply Q;
   67: *>          = 'C':  Conjugate transpose, apply Q**H.
   68: *> \endverbatim
   69: *>
   70: *> \param[in] M
   71: *> \verbatim
   72: *>          M is INTEGER
   73: *>          The number of rows of the matrix C. M >= 0.
   74: *> \endverbatim
   75: *>
   76: *> \param[in] N
   77: *> \verbatim
   78: *>          N is INTEGER
   79: *>          The number of columns of the matrix C. N >= 0.
   80: *> \endverbatim
   81: *>
   82: *> \param[in] K
   83: *> \verbatim
   84: *>          K is INTEGER
   85: *>          The number of elementary reflectors whose product defines
   86: *>          the matrix Q.
   87: *>          If SIDE = 'L', M >= K >= 0;
   88: *>          if SIDE = 'R', N >= K >= 0.
   89: *> \endverbatim
   90: *>
   91: *> \param[in] L
   92: *> \verbatim
   93: *>          L is INTEGER
   94: *>          The number of columns of the matrix A containing
   95: *>          the meaningful part of the Householder reflectors.
   96: *>          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
   97: *> \endverbatim
   98: *>
   99: *> \param[in] A
  100: *> \verbatim
  101: *>          A is COMPLEX*16 array, dimension
  102: *>                               (LDA,M) if SIDE = 'L',
  103: *>                               (LDA,N) if SIDE = 'R'
  104: *>          The i-th row must contain the vector which defines the
  105: *>          elementary reflector H(i), for i = 1,2,...,k, as returned by
  106: *>          ZTZRZF in the last k rows of its array argument A.
  107: *>          A is modified by the routine but restored on exit.
  108: *> \endverbatim
  109: *>
  110: *> \param[in] LDA
  111: *> \verbatim
  112: *>          LDA is INTEGER
  113: *>          The leading dimension of the array A. LDA >= max(1,K).
  114: *> \endverbatim
  115: *>
  116: *> \param[in] TAU
  117: *> \verbatim
  118: *>          TAU is COMPLEX*16 array, dimension (K)
  119: *>          TAU(i) must contain the scalar factor of the elementary
  120: *>          reflector H(i), as returned by ZTZRZF.
  121: *> \endverbatim
  122: *>
  123: *> \param[in,out] C
  124: *> \verbatim
  125: *>          C is COMPLEX*16 array, dimension (LDC,N)
  126: *>          On entry, the M-by-N matrix C.
  127: *>          On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
  128: *> \endverbatim
  129: *>
  130: *> \param[in] LDC
  131: *> \verbatim
  132: *>          LDC is INTEGER
  133: *>          The leading dimension of the array C. LDC >= max(1,M).
  134: *> \endverbatim
  135: *>
  136: *> \param[out] WORK
  137: *> \verbatim
  138: *>          WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
  139: *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  140: *> \endverbatim
  141: *>
  142: *> \param[in] LWORK
  143: *> \verbatim
  144: *>          LWORK is INTEGER
  145: *>          The dimension of the array WORK.
  146: *>          If SIDE = 'L', LWORK >= max(1,N);
  147: *>          if SIDE = 'R', LWORK >= max(1,M).
  148: *>          For good performance, LWORK should generally be larger.
  149: *>
  150: *>          If LWORK = -1, then a workspace query is assumed; the routine
  151: *>          only calculates the optimal size of the WORK array, returns
  152: *>          this value as the first entry of the WORK array, and no error
  153: *>          message related to LWORK is issued by XERBLA.
  154: *> \endverbatim
  155: *>
  156: *> \param[out] INFO
  157: *> \verbatim
  158: *>          INFO is INTEGER
  159: *>          = 0:  successful exit
  160: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
  161: *> \endverbatim
  162: *
  163: *  Authors:
  164: *  ========
  165: *
  166: *> \author Univ. of Tennessee
  167: *> \author Univ. of California Berkeley
  168: *> \author Univ. of Colorado Denver
  169: *> \author NAG Ltd.
  170: *
  171: *> \ingroup complex16OTHERcomputational
  172: *
  173: *> \par Contributors:
  174: *  ==================
  175: *>
  176: *>    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
  177: *
  178: *> \par Further Details:
  179: *  =====================
  180: *>
  181: *> \verbatim
  182: *> \endverbatim
  183: *>
  184: *  =====================================================================
  185:       SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
  186:      $                   WORK, LWORK, INFO )
  187: *
  188: *  -- LAPACK computational routine --
  189: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  190: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  191: *
  192: *     .. Scalar Arguments ..
  193:       CHARACTER          SIDE, TRANS
  194:       INTEGER            INFO, K, L, LDA, LDC, LWORK, M, N
  195: *     ..
  196: *     .. Array Arguments ..
  197:       COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
  198: *     ..
  199: *
  200: *  =====================================================================
  201: *
  202: *     .. Parameters ..
  203:       INTEGER            NBMAX, LDT, TSIZE
  204:       PARAMETER          ( NBMAX = 64, LDT = NBMAX+1,
  205:      $                     TSIZE = LDT*NBMAX )
  206: *     ..
  207: *     .. Local Scalars ..
  208:       LOGICAL            LEFT, LQUERY, NOTRAN
  209:       CHARACTER          TRANST
  210:       INTEGER            I, I1, I2, I3, IB, IC, IINFO, IWT, JA, JC,
  211:      $                   LDWORK, LWKOPT, MI, NB, NBMIN, NI, NQ, NW
  212: *     ..
  213: *     .. External Functions ..
  214:       LOGICAL            LSAME
  215:       INTEGER            ILAENV
  216:       EXTERNAL           LSAME, ILAENV
  217: *     ..
  218: *     .. External Subroutines ..
  219:       EXTERNAL           XERBLA, ZLARZB, ZLARZT, ZUNMR3
  220: *     ..
  221: *     .. Intrinsic Functions ..
  222:       INTRINSIC          MAX, MIN
  223: *     ..
  224: *     .. Executable Statements ..
  225: *
  226: *     Test the input arguments
  227: *
  228:       INFO = 0
  229:       LEFT = LSAME( SIDE, 'L' )
  230:       NOTRAN = LSAME( TRANS, 'N' )
  231:       LQUERY = ( LWORK.EQ.-1 )
  232: *
  233: *     NQ is the order of Q and NW is the minimum dimension of WORK
  234: *
  235:       IF( LEFT ) THEN
  236:          NQ = M
  237:          NW = MAX( 1, N )
  238:       ELSE
  239:          NQ = N
  240:          NW = MAX( 1, M )
  241:       END IF
  242:       IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
  243:          INFO = -1
  244:       ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
  245:          INFO = -2
  246:       ELSE IF( M.LT.0 ) THEN
  247:          INFO = -3
  248:       ELSE IF( N.LT.0 ) THEN
  249:          INFO = -4
  250:       ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
  251:          INFO = -5
  252:       ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
  253:      $         ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
  254:          INFO = -6
  255:       ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
  256:          INFO = -8
  257:       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
  258:          INFO = -11
  259:       ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
  260:          INFO = -13
  261:       END IF
  262: *
  263:       IF( INFO.EQ.0 ) THEN
  264: *
  265: *        Compute the workspace requirements
  266: *
  267:          IF( M.EQ.0 .OR. N.EQ.0 ) THEN
  268:             LWKOPT = 1
  269:          ELSE
  270:             NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N,
  271:      $                               K, -1 ) )
  272:             LWKOPT = NW*NB + TSIZE
  273:          END IF
  274:          WORK( 1 ) = LWKOPT
  275:       END IF
  276: *
  277:       IF( INFO.NE.0 ) THEN
  278:          CALL XERBLA( 'ZUNMRZ', -INFO )
  279:          RETURN
  280:       ELSE IF( LQUERY ) THEN
  281:          RETURN
  282:       END IF
  283: *
  284: *     Quick return if possible
  285: *
  286:       IF( M.EQ.0 .OR. N.EQ.0 ) THEN
  287:          RETURN
  288:       END IF
  289: *
  290: *     Determine the block size.  NB may be at most NBMAX, where NBMAX
  291: *     is used to define the local array T.
  292: *
  293:       NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N, K,
  294:      $     -1 ) )
  295:       NBMIN = 2
  296:       LDWORK = NW
  297:       IF( NB.GT.1 .AND. NB.LT.K ) THEN
  298:          IF( LWORK.LT.LWKOPT ) THEN
  299:             NB = (LWORK-TSIZE) / LDWORK
  300:             NBMIN = MAX( 2, ILAENV( 2, 'ZUNMRQ', SIDE // TRANS, M, N, K,
  301:      $              -1 ) )
  302:          END IF
  303:       END IF
  304: *
  305:       IF( NB.LT.NBMIN .OR. NB.GE.K ) THEN
  306: *
  307: *        Use unblocked code
  308: *
  309:          CALL ZUNMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
  310:      $                WORK, IINFO )
  311:       ELSE
  312: *
  313: *        Use blocked code
  314: *
  315:          IWT = 1 + NW*NB
  316:          IF( ( LEFT .AND. .NOT.NOTRAN ) .OR.
  317:      $       ( .NOT.LEFT .AND. NOTRAN ) ) THEN
  318:             I1 = 1
  319:             I2 = K
  320:             I3 = NB
  321:          ELSE
  322:             I1 = ( ( K-1 ) / NB )*NB + 1
  323:             I2 = 1
  324:             I3 = -NB
  325:          END IF
  326: *
  327:          IF( LEFT ) THEN
  328:             NI = N
  329:             JC = 1
  330:             JA = M - L + 1
  331:          ELSE
  332:             MI = M
  333:             IC = 1
  334:             JA = N - L + 1
  335:          END IF
  336: *
  337:          IF( NOTRAN ) THEN
  338:             TRANST = 'C'
  339:          ELSE
  340:             TRANST = 'N'
  341:          END IF
  342: *
  343:          DO 10 I = I1, I2, I3
  344:             IB = MIN( NB, K-I+1 )
  345: *
  346: *           Form the triangular factor of the block reflector
  347: *           H = H(i+ib-1) . . . H(i+1) H(i)
  348: *
  349:             CALL ZLARZT( 'Backward', 'Rowwise', L, IB, A( I, JA ), LDA,
  350:      $                   TAU( I ), WORK( IWT ), LDT )
  351: *
  352:             IF( LEFT ) THEN
  353: *
  354: *              H or H**H is applied to C(i:m,1:n)
  355: *
  356:                MI = M - I + 1
  357:                IC = I
  358:             ELSE
  359: *
  360: *              H or H**H is applied to C(1:m,i:n)
  361: *
  362:                NI = N - I + 1
  363:                JC = I
  364:             END IF
  365: *
  366: *           Apply H or H**H
  367: *
  368:             CALL ZLARZB( SIDE, TRANST, 'Backward', 'Rowwise', MI, NI,
  369:      $                   IB, L, A( I, JA ), LDA, WORK( IWT ), LDT,
  370:      $                   C( IC, JC ), LDC, WORK, LDWORK )
  371:    10    CONTINUE
  372: *
  373:       END IF
  374: *
  375:       WORK( 1 ) = LWKOPT
  376: *
  377:       RETURN
  378: *
  379: *     End of ZUNMRZ
  380: *
  381:       END

CVSweb interface <joel.bertrand@systella.fr>