Diff for /rpl/lapack/lapack/zunmrz.f between versions 1.8 and 1.15

version 1.8, 2011/07/22 07:38:22 version 1.15, 2016/08/27 15:35:14
Line 1 Line 1
   *> \brief \b ZUNMRZ
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download ZUNMRZ + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunmrz.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunmrz.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunmrz.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
   *                          WORK, LWORK, INFO )
   * 
   *       .. Scalar Arguments ..
   *       CHARACTER          SIDE, TRANS
   *       INTEGER            INFO, K, L, LDA, LDC, LWORK, M, N
   *       ..
   *       .. Array Arguments ..
   *       COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> ZUNMRZ overwrites the general complex M-by-N matrix C with
   *>
   *>                 SIDE = 'L'     SIDE = 'R'
   *> TRANS = 'N':      Q * C          C * Q
   *> TRANS = 'C':      Q**H * C       C * Q**H
   *>
   *> where Q is a complex unitary matrix defined as the product of k
   *> elementary reflectors
   *>
   *>       Q = H(1) H(2) . . . H(k)
   *>
   *> as returned by ZTZRZF. Q is of order M if SIDE = 'L' and of order N
   *> if SIDE = 'R'.
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] SIDE
   *> \verbatim
   *>          SIDE is CHARACTER*1
   *>          = 'L': apply Q or Q**H from the Left;
   *>          = 'R': apply Q or Q**H from the Right.
   *> \endverbatim
   *>
   *> \param[in] TRANS
   *> \verbatim
   *>          TRANS is CHARACTER*1
   *>          = 'N':  No transpose, apply Q;
   *>          = 'C':  Conjugate transpose, apply Q**H.
   *> \endverbatim
   *>
   *> \param[in] M
   *> \verbatim
   *>          M is INTEGER
   *>          The number of rows of the matrix C. M >= 0.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>          The number of columns of the matrix C. N >= 0.
   *> \endverbatim
   *>
   *> \param[in] K
   *> \verbatim
   *>          K is INTEGER
   *>          The number of elementary reflectors whose product defines
   *>          the matrix Q.
   *>          If SIDE = 'L', M >= K >= 0;
   *>          if SIDE = 'R', N >= K >= 0.
   *> \endverbatim
   *>
   *> \param[in] L
   *> \verbatim
   *>          L is INTEGER
   *>          The number of columns of the matrix A containing
   *>          the meaningful part of the Householder reflectors.
   *>          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
   *> \endverbatim
   *>
   *> \param[in] A
   *> \verbatim
   *>          A is COMPLEX*16 array, dimension
   *>                               (LDA,M) if SIDE = 'L',
   *>                               (LDA,N) if SIDE = 'R'
   *>          The i-th row must contain the vector which defines the
   *>          elementary reflector H(i), for i = 1,2,...,k, as returned by
   *>          ZTZRZF in the last k rows of its array argument A.
   *>          A is modified by the routine but restored on exit.
   *> \endverbatim
   *>
   *> \param[in] LDA
   *> \verbatim
   *>          LDA is INTEGER
   *>          The leading dimension of the array A. LDA >= max(1,K).
   *> \endverbatim
   *>
   *> \param[in] TAU
   *> \verbatim
   *>          TAU is COMPLEX*16 array, dimension (K)
   *>          TAU(i) must contain the scalar factor of the elementary
   *>          reflector H(i), as returned by ZTZRZF.
   *> \endverbatim
   *>
   *> \param[in,out] C
   *> \verbatim
   *>          C is COMPLEX*16 array, dimension (LDC,N)
   *>          On entry, the M-by-N matrix C.
   *>          On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.
   *> \endverbatim
   *>
   *> \param[in] LDC
   *> \verbatim
   *>          LDC is INTEGER
   *>          The leading dimension of the array C. LDC >= max(1,M).
   *> \endverbatim
   *>
   *> \param[out] WORK
   *> \verbatim
   *>          WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
   *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
   *> \endverbatim
   *>
   *> \param[in] LWORK
   *> \verbatim
   *>          LWORK is INTEGER
   *>          The dimension of the array WORK.
   *>          If SIDE = 'L', LWORK >= max(1,N);
   *>          if SIDE = 'R', LWORK >= max(1,M).
   *>          For good performance, LWORK should generally be larger.
   *>
   *>          If LWORK = -1, then a workspace query is assumed; the routine
   *>          only calculates the optimal size of the WORK array, returns
   *>          this value as the first entry of the WORK array, and no error
   *>          message related to LWORK is issued by XERBLA.
   *> \endverbatim
   *>
   *> \param[out] INFO
   *> \verbatim
   *>          INFO is INTEGER
   *>          = 0:  successful exit
   *>          < 0:  if INFO = -i, the i-th argument had an illegal value
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2015
   *
   *> \ingroup complex16OTHERcomputational
   *
   *> \par Contributors:
   *  ==================
   *>
   *>    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
   *
   *> \par Further Details:
   *  =====================
   *>
   *> \verbatim
   *> \endverbatim
   *>
   *  =====================================================================
       SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,        SUBROUTINE ZUNMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC,
      $                   WORK, LWORK, INFO )       $                   WORK, LWORK, INFO )
 *  *
 *  -- LAPACK routine (version 3.3.1) --  *  -- LAPACK computational routine (version 3.6.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *  -- April 2011                                                      --  *     November 2015
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       CHARACTER          SIDE, TRANS        CHARACTER          SIDE, TRANS
Line 14 Line 200
       COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )        COMPLEX*16         A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  ZUNMRZ overwrites the general complex M-by-N matrix C with  
 *  
 *                  SIDE = 'L'     SIDE = 'R'  
 *  TRANS = 'N':      Q * C          C * Q  
 *  TRANS = 'C':      Q**H * C       C * Q**H  
 *  
 *  where Q is a complex unitary matrix defined as the product of k  
 *  elementary reflectors  
 *  
 *        Q = H(1) H(2) . . . H(k)  
 *  
 *  as returned by ZTZRZF. Q is of order M if SIDE = 'L' and of order N  
 *  if SIDE = 'R'.  
 *  
 *  Arguments  
 *  =========  
 *  
 *  SIDE    (input) CHARACTER*1  
 *          = 'L': apply Q or Q**H from the Left;  
 *          = 'R': apply Q or Q**H from the Right.  
 *  
 *  TRANS   (input) CHARACTER*1  
 *          = 'N':  No transpose, apply Q;  
 *          = 'C':  Conjugate transpose, apply Q**H.  
 *  
 *  M       (input) INTEGER  
 *          The number of rows of the matrix C. M >= 0.  
 *  
 *  N       (input) INTEGER  
 *          The number of columns of the matrix C. N >= 0.  
 *  
 *  K       (input) INTEGER  
 *          The number of elementary reflectors whose product defines  
 *          the matrix Q.  
 *          If SIDE = 'L', M >= K >= 0;  
 *          if SIDE = 'R', N >= K >= 0.  
 *  
 *  L       (input) INTEGER  
 *          The number of columns of the matrix A containing  
 *          the meaningful part of the Householder reflectors.  
 *          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.  
 *  
 *  A       (input) COMPLEX*16 array, dimension  
 *                               (LDA,M) if SIDE = 'L',  
 *                               (LDA,N) if SIDE = 'R'  
 *          The i-th row must contain the vector which defines the  
 *          elementary reflector H(i), for i = 1,2,...,k, as returned by  
 *          ZTZRZF in the last k rows of its array argument A.  
 *          A is modified by the routine but restored on exit.  
 *  
 *  LDA     (input) INTEGER  
 *          The leading dimension of the array A. LDA >= max(1,K).  
 *  
 *  TAU     (input) COMPLEX*16 array, dimension (K)  
 *          TAU(i) must contain the scalar factor of the elementary  
 *          reflector H(i), as returned by ZTZRZF.  
 *  
 *  C       (input/output) COMPLEX*16 array, dimension (LDC,N)  
 *          On entry, the M-by-N matrix C.  
 *          On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q.  
 *  
 *  LDC     (input) INTEGER  
 *          The leading dimension of the array C. LDC >= max(1,M).  
 *  
 *  WORK    (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))  
 *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.  
 *  
 *  LWORK   (input) INTEGER  
 *          The dimension of the array WORK.  
 *          If SIDE = 'L', LWORK >= max(1,N);  
 *          if SIDE = 'R', LWORK >= max(1,M).  
 *          For optimum performance LWORK >= N*NB if SIDE = 'L', and  
 *          LWORK >= M*NB if SIDE = 'R', where NB is the optimal  
 *          blocksize.  
 *  
 *          If LWORK = -1, then a workspace query is assumed; the routine  
 *          only calculates the optimal size of the WORK array, returns  
 *          this value as the first entry of the WORK array, and no error  
 *          message related to LWORK is issued by XERBLA.  
 *  
 *  INFO    (output) INTEGER  
 *          = 0:  successful exit  
 *          < 0:  if INFO = -i, the i-th argument had an illegal value  
 *  
 *  Further Details  
 *  ===============  
 *  
 *  Based on contributions by  
 *    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..
       INTEGER            NBMAX, LDT        INTEGER            NBMAX, LDT, TSIZE
       PARAMETER          ( NBMAX = 64, LDT = NBMAX+1 )        PARAMETER          ( NBMAX = 64, LDT = NBMAX+1,
        $                     TSIZE = LDT*NBMAX )
 *     ..  *     ..
 *     .. Local Scalars ..  *     .. Local Scalars ..
       LOGICAL            LEFT, LQUERY, NOTRAN        LOGICAL            LEFT, LQUERY, NOTRAN
       CHARACTER          TRANST        CHARACTER          TRANST
       INTEGER            I, I1, I2, I3, IB, IC, IINFO, IWS, JA, JC,        INTEGER            I, I1, I2, I3, IB, IC, IINFO, IWT, JA, JC,
      $                   LDWORK, LWKOPT, MI, NB, NBMIN, NI, NQ, NW       $                   LDWORK, LWKOPT, MI, NB, NBMIN, NI, NQ, NW
 *     ..  *     ..
 *     .. Local Arrays ..  
       COMPLEX*16         T( LDT, NBMAX )  
 *     ..  
 *     .. External Functions ..  *     .. External Functions ..
       LOGICAL            LSAME        LOGICAL            LSAME
       INTEGER            ILAENV        INTEGER            ILAENV
Line 168 Line 259
          INFO = -8           INFO = -8
       ELSE IF( LDC.LT.MAX( 1, M ) ) THEN        ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
          INFO = -11           INFO = -11
         ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
            INFO = -13
       END IF        END IF
 *  *
       IF( INFO.EQ.0 ) THEN        IF( INFO.EQ.0 ) THEN
   *
   *        Compute the workspace requirements
   *
          IF( M.EQ.0 .OR. N.EQ.0 ) THEN           IF( M.EQ.0 .OR. N.EQ.0 ) THEN
             LWKOPT = 1              LWKOPT = 1
          ELSE           ELSE
 *  
 *           Determine the block size.  NB may be at most NBMAX, where  
 *           NBMAX is used to define the local array T.  
 *  
             NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N,              NB = MIN( NBMAX, ILAENV( 1, 'ZUNMRQ', SIDE // TRANS, M, N,
      $                               K, -1 ) )       $                               K, -1 ) )
             LWKOPT = NW*NB              LWKOPT = NW*NB + TSIZE
          END IF           END IF
          WORK( 1 ) = LWKOPT           WORK( 1 ) = LWKOPT
 *  
          IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN  
             INFO = -13  
          END IF  
       END IF        END IF
 *  *
       IF( INFO.NE.0 ) THEN        IF( INFO.NE.0 ) THEN
Line 210 Line 298
       NBMIN = 2        NBMIN = 2
       LDWORK = NW        LDWORK = NW
       IF( NB.GT.1 .AND. NB.LT.K ) THEN        IF( NB.GT.1 .AND. NB.LT.K ) THEN
          IWS = NW*NB           IF( LWORK.LT.NW*NB+TSIZE ) THEN
          IF( LWORK.LT.IWS ) THEN              NB = (LWORK-TSIZE) / LDWORK
             NB = LWORK / LDWORK  
             NBMIN = MAX( 2, ILAENV( 2, 'ZUNMRQ', SIDE // TRANS, M, N, K,              NBMIN = MAX( 2, ILAENV( 2, 'ZUNMRQ', SIDE // TRANS, M, N, K,
      $              -1 ) )       $              -1 ) )
          END IF           END IF
       ELSE  
          IWS = NW  
       END IF        END IF
 *  *
       IF( NB.LT.NBMIN .OR. NB.GE.K ) THEN        IF( NB.LT.NBMIN .OR. NB.GE.K ) THEN
Line 230 Line 315
 *  *
 *        Use blocked code  *        Use blocked code
 *  *
            IWT = 1 + NW*NB
          IF( ( LEFT .AND. .NOT.NOTRAN ) .OR.           IF( ( LEFT .AND. .NOT.NOTRAN ) .OR.
      $       ( .NOT.LEFT .AND. NOTRAN ) ) THEN       $       ( .NOT.LEFT .AND. NOTRAN ) ) THEN
             I1 = 1              I1 = 1
Line 264 Line 350
 *           H = H(i+ib-1) . . . H(i+1) H(i)  *           H = H(i+ib-1) . . . H(i+1) H(i)
 *  *
             CALL ZLARZT( 'Backward', 'Rowwise', L, IB, A( I, JA ), LDA,              CALL ZLARZT( 'Backward', 'Rowwise', L, IB, A( I, JA ), LDA,
      $                   TAU( I ), T, LDT )       $                   TAU( I ), WORK( IWT ), LDT )
 *  *
             IF( LEFT ) THEN              IF( LEFT ) THEN
 *  *
Line 283 Line 369
 *           Apply H or H**H  *           Apply H or H**H
 *  *
             CALL ZLARZB( SIDE, TRANST, 'Backward', 'Rowwise', MI, NI,              CALL ZLARZB( SIDE, TRANST, 'Backward', 'Rowwise', MI, NI,
      $                   IB, L, A( I, JA ), LDA, T, LDT, C( IC, JC ),       $                   IB, L, A( I, JA ), LDA, WORK( IWT ), LDT,
      $                   LDC, WORK, LDWORK )       $                   C( IC, JC ), LDC, WORK, LDWORK )
    10    CONTINUE     10    CONTINUE
 *  *
       END IF        END IF

Removed from v.1.8  
changed lines
  Added in v.1.15


CVSweb interface <joel.bertrand@systella.fr>