File:  [local] / rpl / lapack / lapack / zunmrz.f
Revision 1.16: download - view: text, annotated - select for diffs - revision graph
Sat Jun 17 10:54:34 2017 UTC (6 years, 10 months ago) by bertrand
Branches: MAIN
CVS tags: HEAD
Mise à jour de lapack.

    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: *> \date December 2016
  172: *
  173: *> \ingroup complex16OTHERcomputational
  174: *
  175: *> \par Contributors:
  176: *  ==================
  177: *>
  178: *>    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
  179: *
  180: *> \par Further Details:
  181: *  =====================
  182: *>
  183: *> \verbatim
  184: *> \endverbatim
  185: *>
  186: *  =====================================================================
  187:       SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
  188:      $                   WORK, LWORK, INFO )
  189: *
  190: *  -- LAPACK computational routine (version 3.7.0) --
  191: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  192: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  193: *     December 2016
  194: *
  195: *     .. Scalar Arguments ..
  196:       CHARACTER          SIDE, TRANS
  197:       INTEGER            INFO, K, L, LDA, LDC, LWORK, M, N
  198: *     ..
  199: *     .. Array Arguments ..
  200:       COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
  201: *     ..
  202: *
  203: *  =====================================================================
  204: *
  205: *     .. Parameters ..
  206:       INTEGER            NBMAX, LDT, TSIZE
  207:       PARAMETER          ( NBMAX = 64, LDT = NBMAX+1,
  208:      $                     TSIZE = LDT*NBMAX )
  209: *     ..
  210: *     .. Local Scalars ..
  211:       LOGICAL            LEFT, LQUERY, NOTRAN
  212:       CHARACTER          TRANST
  213:       INTEGER            I, I1, I2, I3, IB, IC, IINFO, IWT, JA, JC,
  214:      $                   LDWORK, LWKOPT, MI, NB, NBMIN, NI, NQ, NW
  215: *     ..
  216: *     .. External Functions ..
  217:       LOGICAL            LSAME
  218:       INTEGER            ILAENV
  219:       EXTERNAL           LSAME, ILAENV
  220: *     ..
  221: *     .. External Subroutines ..
  222:       EXTERNAL           XERBLA, ZLARZB, ZLARZT, ZUNMR3
  223: *     ..
  224: *     .. Intrinsic Functions ..
  225:       INTRINSIC          MAX, MIN
  226: *     ..
  227: *     .. Executable Statements ..
  228: *
  229: *     Test the input arguments
  230: *
  231:       INFO = 0
  232:       LEFT = LSAME( SIDE, 'L' )
  233:       NOTRAN = LSAME( TRANS, 'N' )
  234:       LQUERY = ( LWORK.EQ.-1 )
  235: *
  236: *     NQ is the order of Q and NW is the minimum dimension of WORK
  237: *
  238:       IF( LEFT ) THEN
  239:          NQ = M
  240:          NW = MAX( 1, N )
  241:       ELSE
  242:          NQ = N
  243:          NW = MAX( 1, M )
  244:       END IF
  245:       IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
  246:          INFO = -1
  247:       ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
  248:          INFO = -2
  249:       ELSE IF( M.LT.0 ) THEN
  250:          INFO = -3
  251:       ELSE IF( N.LT.0 ) THEN
  252:          INFO = -4
  253:       ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN
  254:          INFO = -5
  255:       ELSE IF( L.LT.0 .OR. ( LEFT .AND. ( L.GT.M ) ) .OR.
  256:      $         ( .NOT.LEFT .AND. ( L.GT.N ) ) ) THEN
  257:          INFO = -6
  258:       ELSE IF( LDA.LT.MAX( 1, K ) ) THEN
  259:          INFO = -8
  260:       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
  261:          INFO = -11
  262:       ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
  263:          INFO = -13
  264:       END IF
  265: *
  266:       IF( INFO.EQ.0 ) THEN
  267: *
  268: *        Compute the workspace requirements
  269: *
  270:          IF( M.EQ.0 .OR. N.EQ.0 ) THEN
  271:             LWKOPT = 1
  272:          ELSE
  273:             NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N,
  274:      $                               K, -1 ) )
  275:             LWKOPT = NW*NB + TSIZE
  276:          END IF
  277:          WORK( 1 ) = LWKOPT
  278:       END IF
  279: *
  280:       IF( INFO.NE.0 ) THEN
  281:          CALL XERBLA( 'ZUNMRZ', -INFO )
  282:          RETURN
  283:       ELSE IF( LQUERY ) THEN
  284:          RETURN
  285:       END IF
  286: *
  287: *     Quick return if possible
  288: *
  289:       IF( M.EQ.0 .OR. N.EQ.0 ) THEN
  290:          RETURN
  291:       END IF
  292: *
  293: *     Determine the block size.  NB may be at most NBMAX, where NBMAX
  294: *     is used to define the local array T.
  295: *
  296:       NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N, K,
  297:      $     -1 ) )
  298:       NBMIN = 2
  299:       LDWORK = NW
  300:       IF( NB.GT.1 .AND. NB.LT.K ) THEN
  301:          IF( LWORK.LT.NW*NB+TSIZE ) THEN
  302:             NB = (LWORK-TSIZE) / LDWORK
  303:             NBMIN = MAX( 2, ILAENV( 2, 'ZUNMRQ', SIDE // TRANS, M, N, K,
  304:      $              -1 ) )
  305:          END IF
  306:       END IF
  307: *
  308:       IF( NB.LT.NBMIN .OR. NB.GE.K ) THEN
  309: *
  310: *        Use unblocked code
  311: *
  312:          CALL ZUNMR3( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
  313:      $                WORK, IINFO )
  314:       ELSE
  315: *
  316: *        Use blocked code
  317: *
  318:          IWT = 1 + NW*NB
  319:          IF( ( LEFT .AND. .NOT.NOTRAN ) .OR.
  320:      $       ( .NOT.LEFT .AND. NOTRAN ) ) THEN
  321:             I1 = 1
  322:             I2 = K
  323:             I3 = NB
  324:          ELSE
  325:             I1 = ( ( K-1 ) / NB )*NB + 1
  326:             I2 = 1
  327:             I3 = -NB
  328:          END IF
  329: *
  330:          IF( LEFT ) THEN
  331:             NI = N
  332:             JC = 1
  333:             JA = M - L + 1
  334:          ELSE
  335:             MI = M
  336:             IC = 1
  337:             JA = N - L + 1
  338:          END IF
  339: *
  340:          IF( NOTRAN ) THEN
  341:             TRANST = 'C'
  342:          ELSE
  343:             TRANST = 'N'
  344:          END IF
  345: *
  346:          DO 10 I = I1, I2, I3
  347:             IB = MIN( NB, K-I+1 )
  348: *
  349: *           Form the triangular factor of the block reflector
  350: *           H = H(i+ib-1) . . . H(i+1) H(i)
  351: *
  352:             CALL ZLARZT( 'Backward', 'Rowwise', L, IB, A( I, JA ), LDA,
  353:      $                   TAU( I ), WORK( IWT ), LDT )
  354: *
  355:             IF( LEFT ) THEN
  356: *
  357: *              H or H**H is applied to C(i:m,1:n)
  358: *
  359:                MI = M - I + 1
  360:                IC = I
  361:             ELSE
  362: *
  363: *              H or H**H is applied to C(1:m,i:n)
  364: *
  365:                NI = N - I + 1
  366:                JC = I
  367:             END IF
  368: *
  369: *           Apply H or H**H
  370: *
  371:             CALL ZLARZB( SIDE, TRANST, 'Backward', 'Rowwise', MI, NI,
  372:      $                   IB, L, A( I, JA ), LDA, WORK( IWT ), LDT,
  373:      $                   C( IC, JC ), LDC, WORK, LDWORK )
  374:    10    CONTINUE
  375: *
  376:       END IF
  377: *
  378:       WORK( 1 ) = LWKOPT
  379: *
  380:       RETURN
  381: *
  382: *     End of ZUNMRZ
  383: *
  384:       END

CVSweb interface <joel.bertrand@systella.fr>