Diff for /rpl/lapack/lapack/dtpqrt.f between versions 1.6 and 1.7

version 1.6, 2016/08/27 15:34:41 version 1.7, 2017/06/17 10:54:06
Line 2 Line 2
 *  *
 *  =========== DOCUMENTATION ===========  *  =========== DOCUMENTATION ===========
 *  *
 * Online html documentation available at   * Online html documentation available at
 *            http://www.netlib.org/lapack/explore-html/   *            http://www.netlib.org/lapack/explore-html/
 *  *
 *> \htmlonly  *> \htmlonly
 *> Download DTPQRT + dependencies   *> Download DTPQRT + dependencies
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtpqrt.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtpqrt.f">
 *> [TGZ]</a>   *> [TGZ]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtpqrt.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtpqrt.f">
 *> [ZIP]</a>   *> [ZIP]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtpqrt.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtpqrt.f">
 *> [TXT]</a>  *> [TXT]</a>
 *> \endhtmlonly   *> \endhtmlonly
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE DTPQRT( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,  *       SUBROUTINE DTPQRT( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,
 *                          INFO )  *                          INFO )
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       INTEGER INFO, LDA, LDB, LDT, N, M, L, NB  *       INTEGER INFO, LDA, LDB, LDT, N, M, L, NB
 *       ..  *       ..
 *       .. Array Arguments ..  *       .. Array Arguments ..
 *       DOUBLE PRECISION A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )  *       DOUBLE PRECISION A( LDA, * ), B( LDB, * ), T( LDT, * ), WORK( * )
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
 *>  *>
 *> \verbatim  *> \verbatim
 *>  *>
 *> DTPQRT computes a blocked QR factorization of a real   *> DTPQRT computes a blocked QR factorization of a real
 *> "triangular-pentagonal" matrix C, which is composed of a   *> "triangular-pentagonal" matrix C, which is composed of a
 *> triangular block A and pentagonal block B, using the compact   *> triangular block A and pentagonal block B, using the compact
 *> WY representation for Q.  *> WY representation for Q.
 *> \endverbatim  *> \endverbatim
 *  *
Line 46 Line 46
 *> \param[in] M  *> \param[in] M
 *> \verbatim  *> \verbatim
 *>          M is INTEGER  *>          M is INTEGER
 *>          The number of rows of the matrix B.    *>          The number of rows of the matrix B.
 *>          M >= 0.  *>          M >= 0.
 *> \endverbatim  *> \endverbatim
 *>  *>
Line 88 Line 88
 *> \param[in,out] B  *> \param[in,out] B
 *> \verbatim  *> \verbatim
 *>          B is DOUBLE PRECISION array, dimension (LDB,N)  *>          B is DOUBLE PRECISION array, dimension (LDB,N)
 *>          On entry, the pentagonal M-by-N matrix B.  The first M-L rows   *>          On entry, the pentagonal M-by-N matrix B.  The first M-L rows
 *>          are rectangular, and the last L rows are upper trapezoidal.  *>          are rectangular, and the last L rows are upper trapezoidal.
 *>          On exit, B contains the pentagonal matrix V.  See Further Details.  *>          On exit, B contains the pentagonal matrix V.  See Further Details.
 *> \endverbatim  *> \endverbatim
Line 105 Line 105
 *>          The upper triangular block reflectors stored in compact form  *>          The upper triangular block reflectors stored in compact form
 *>          as a sequence of upper triangular blocks.  See Further Details.  *>          as a sequence of upper triangular blocks.  See Further Details.
 *> \endverbatim  *> \endverbatim
 *>            *>
 *> \param[in] LDT  *> \param[in] LDT
 *> \verbatim  *> \verbatim
 *>          LDT is INTEGER  *>          LDT is INTEGER
Line 127 Line 127
 *  Authors:  *  Authors:
 *  ========  *  ========
 *  *
 *> \author Univ. of Tennessee   *> \author Univ. of Tennessee
 *> \author Univ. of California Berkeley   *> \author Univ. of California Berkeley
 *> \author Univ. of Colorado Denver   *> \author Univ. of Colorado Denver
 *> \author NAG Ltd.   *> \author NAG Ltd.
 *  *
 *> \date November 2013  *> \date December 2016
 *  *
 *> \ingroup doubleOTHERcomputational  *> \ingroup doubleOTHERcomputational
 *  *
Line 141 Line 141
 *>  *>
 *> \verbatim  *> \verbatim
 *>  *>
 *>  The input matrix C is a (N+M)-by-N matrix    *>  The input matrix C is a (N+M)-by-N matrix
 *>  *>
 *>               C = [ A ]  *>               C = [ A ]
 *>                   [ B ]          *>                   [ B ]
 *>  *>
 *>  where A is an upper triangular N-by-N matrix, and B is M-by-N pentagonal  *>  where A is an upper triangular N-by-N matrix, and B is M-by-N pentagonal
 *>  matrix consisting of a (M-L)-by-N rectangular matrix B1 on top of a L-by-N  *>  matrix consisting of a (M-L)-by-N rectangular matrix B1 on top of a L-by-N
Line 154 Line 154
 *>                   [ B2 ]  <-     L-by-N upper trapezoidal.  *>                   [ B2 ]  <-     L-by-N upper trapezoidal.
 *>  *>
 *>  The upper trapezoidal matrix B2 consists of the first L rows of a  *>  The upper trapezoidal matrix B2 consists of the first L rows of a
 *>  N-by-N upper triangular matrix, where 0 <= L <= MIN(M,N).  If L=0,   *>  N-by-N upper triangular matrix, where 0 <= L <= MIN(M,N).  If L=0,
 *>  B is rectangular M-by-N; if M=L=N, B is upper triangular.    *>  B is rectangular M-by-N; if M=L=N, B is upper triangular.
 *>  *>
 *>  The matrix W stores the elementary reflectors H(i) in the i-th column  *>  The matrix W stores the elementary reflectors H(i) in the i-th column
 *>  below the diagonal (of A) in the (N+M)-by-N input matrix C  *>  below the diagonal (of A) in the (N+M)-by-N input matrix C
Line 169 Line 169
 *>                   [ V ]  <- M-by-N, same form as B.  *>                   [ V ]  <- M-by-N, same form as B.
 *>  *>
 *>  Thus, all of information needed for W is contained on exit in B, which  *>  Thus, all of information needed for W is contained on exit in B, which
 *>  we call V above.  Note that V has the same form as B; that is,   *>  we call V above.  Note that V has the same form as B; that is,
 *>  *>
 *>               V = [ V1 ] <- (M-L)-by-N rectangular  *>               V = [ V1 ] <- (M-L)-by-N rectangular
 *>                   [ V2 ] <-     L-by-N upper trapezoidal.  *>                   [ V2 ] <-     L-by-N upper trapezoidal.
 *>  *>
 *>  The columns of V represent the vectors which define the H(i)'s.    *>  The columns of V represent the vectors which define the H(i)'s.
 *>  *>
 *>  The number of blocks is B = ceiling(N/NB), where each  *>  The number of blocks is B = ceiling(N/NB), where each
 *>  block is of order NB except for the last block, which is of order   *>  block is of order NB except for the last block, which is of order
 *>  IB = N - (B-1)*NB.  For each of the B blocks, a upper triangular block  *>  IB = N - (B-1)*NB.  For each of the B blocks, a upper triangular block
 *>  reflector factor is computed: T1, T2, ..., TB.  The NB-by-NB (and IB-by-IB   *>  reflector factor is computed: T1, T2, ..., TB.  The NB-by-NB (and IB-by-IB
 *>  for the last block) T's are stored in the NB-by-N matrix T as  *>  for the last block) T's are stored in the NB-by-N matrix T as
 *>  *>
 *>               T = [T1 T2 ... TB].  *>               T = [T1 T2 ... TB].
Line 189 Line 189
       SUBROUTINE DTPQRT( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,        SUBROUTINE DTPQRT( M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK,
      $                   INFO )       $                   INFO )
 *  *
 *  -- LAPACK computational routine (version 3.5.0) --  *  -- LAPACK computational routine (version 3.7.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..--
 *     November 2013  *     December 2016
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER INFO, LDA, LDB, LDT, N, M, L, NB        INTEGER INFO, LDA, LDB, LDT, N, M, L, NB
Line 240 Line 240
       IF( M.EQ.0 .OR. N.EQ.0 ) RETURN        IF( M.EQ.0 .OR. N.EQ.0 ) RETURN
 *  *
       DO I = 1, N, NB        DO I = 1, N, NB
 *       *
 *     Compute the QR factorization of the current block  *     Compute the QR factorization of the current block
 *  *
          IB = MIN( N-I+1, NB )           IB = MIN( N-I+1, NB )
Line 251 Line 251
             LB = MB-M+L-I+1              LB = MB-M+L-I+1
          END IF           END IF
 *  *
          CALL DTPQRT2( MB, IB, LB, A(I,I), LDA, B( 1, I ), LDB,            CALL DTPQRT2( MB, IB, LB, A(I,I), LDA, B( 1, I ), LDB,
      $                 T(1, I ), LDT, IINFO )       $                 T(1, I ), LDT, IINFO )
 *  *
 *     Update by applying H**T to B(:,I+IB:N) from the left  *     Update by applying H**T to B(:,I+IB:N) from the left
 *  *
          IF( I+IB.LE.N ) THEN           IF( I+IB.LE.N ) THEN
             CALL DTPRFB( 'L', 'T', 'F', 'C', MB, N-I-IB+1, IB, LB,              CALL DTPRFB( 'L', 'T', 'F', 'C', MB, N-I-IB+1, IB, LB,
      $                    B( 1, I ), LDB, T( 1, I ), LDT,        $                    B( 1, I ), LDB, T( 1, I ), LDT,
      $                    A( I, I+IB ), LDA, B( 1, I+IB ), LDB,        $                    A( I, I+IB ), LDA, B( 1, I+IB ), LDB,
      $                    WORK, IB )       $                    WORK, IB )
          END IF           END IF
       END DO        END DO
       RETURN        RETURN
 *       *
 *     End of DTPQRT  *     End of DTPQRT
 *  *
       END        END

Removed from v.1.6  
changed lines
  Added in v.1.7


CVSweb interface <joel.bertrand@systella.fr>