Merge branch 'master' of https://github.com/Reference-LAPACK/lapack
[platform/upstream/lapack.git] / SRC / slamswlq.f
index c636c70..f3238b6 100644 (file)
@@ -1,8 +1,8 @@
-* 
+*
 *  Definition:
 *  ===========
 *
-*      SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T, 
+*      SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
 *     $                LDT, C, LDC, WORK, LWORK, INFO )
 *
 *
 *  =============
 *>
 *> \verbatim
-*> 
-*>    DLAMQRTS overwrites the general real M-by-N matrix C with
 *>
-*>                     
+*>    SLAMSWLQ overwrites the general real M-by-N matrix C with
+*>
+*>
 *>                    SIDE = 'L'     SIDE = 'R'
 *>    TRANS = 'N':      Q * C          C * Q
 *>    TRANS = 'T':      Q**T * C       C * Q**T
 *>    where Q is a real orthogonal matrix defined as the product of blocked
-*>    elementary reflectors computed by short wide LQ 
-*>    factorization (DLASWLQ)
+*>    elementary reflectors computed by short wide LQ
+*>    factorization (SLASWLQ)
 *> \endverbatim
 *
 *  Arguments:
 *  ==========
 *
 *> \param[in] SIDE
+*> \verbatim
 *>          SIDE is CHARACTER*1
 *>          = 'L': apply Q or Q**T from the Left;
 *>          = 'R': apply Q or Q**T from the Right.
+*> \endverbatim
 *>
 *> \param[in] TRANS
+*> \verbatim
 *>          TRANS is CHARACTER*1
 *>          = 'N':  No transpose, apply Q;
 *>          = 'T':  Transpose, apply Q**T.
+*> \endverbatim
+*>
 *> \param[in] M
 *> \verbatim
 *>          M is INTEGER
-*>          The number of rows of the matrix A.  M >=0.
+*>          The number of rows of the matrix C.  M >=0.
 *> \endverbatim
 *>
 *> \param[in] N
 *>          The number of elementary reflectors whose product defines
 *>          the matrix Q.
 *>          M >= K >= 0;
-*>          
+*>
 *> \endverbatim
 *> \param[in] MB
 *> \verbatim
 *>          MB is INTEGER
-*>          The row block size to be used in the blocked QR.  
-*>          M >= MB >= 1 
+*>          The row block size to be used in the blocked QR.
+*>          M >= MB >= 1
 *> \endverbatim
 *>
 *> \param[in] NB
 *> \verbatim
 *>          NB is INTEGER
-*>          The column block size to be used in the blocked QR.  
+*>          The column block size to be used in the blocked QR.
 *>          NB > M.
 *> \endverbatim
 *>
 *> \param[in] NB
 *> \verbatim
 *>          NB is INTEGER
-*>          The block size to be used in the blocked QR.  
+*>          The block size to be used in the blocked QR.
 *>                MB > M.
-*>         
+*>
 *> \endverbatim
 *>
-*> \param[in,out] A
+*> \param[in] A
 *> \verbatim
-*>          A is REAL array, dimension (LDA,K)
+*>          A is REAL array, dimension
+*>                               (LDA,M) if SIDE = 'L',
+*>                               (LDA,N) if SIDE = 'R'
 *>          The i-th row must contain the vector which defines the blocked
 *>          elementary reflector H(i), for i = 1,2,...,k, as returned by
-*>          DLASWLQ in the first k rows of its array argument A.
+*>          SLASWLQ in the first k rows of its array argument A.
 *> \endverbatim
 *>
 *> \param[in] LDA
 *>
 *> \param[in] T
 *> \verbatim
-*>          T is REAL array, dimension 
+*>          T is REAL array, dimension
 *>          ( M * Number of blocks(CEIL(N-K/NB-K)),
 *>          The blocked upper triangular block reflectors stored in compact form
 *>          as a sequence of upper triangular blocks.  See below
 *> \endverbatim
 *>
 *> \param[in,out] C
+*> \verbatim
 *>          C is REAL array, dimension (LDC,N)
 *>          On entry, the M-by-N matrix C.
 *>          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T 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
 *>         (workspace) REAL array, dimension (MAX(1,LWORK))
-*>        
 *> \endverbatim
+*>
 *> \param[in] LWORK
 *> \verbatim
 *>          LWORK is INTEGER
 *>          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
 *> block reflectors, stored in array T(1:LDT,(i-1)*M+1:i*M).
 *> The last Q(k) may use fewer rows.
 *> For more information see Further Details in TPQRT.
-*> 
+*>
 *> For more details of the overall algorithm, see the description of
 *> Sequential TSQR in Section 2.2 of [1].
 *>
 *> \endverbatim
 *>
 *  =====================================================================
-      SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,  
+      SUBROUTINE SLAMSWLQ( SIDE, TRANS, M, N, K, MB, NB, A, LDA, T,
      $    LDT, C, LDC, WORK, LWORK, 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,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-*     November 2013
+*     December 2016
 *
 *     .. Scalar Arguments ..
       CHARACTER         SIDE, TRANS
       END IF
 *
       IF((NB.LE.K).OR.(NB.GE.MAX(M,N,K))) THEN
-        CALL DGEMLQT( SIDE, TRANS, M, N, K, MB, A, LDA, 
-     $        T, LDT, C, LDC, WORK, INFO)  
+        CALL DGEMLQT( SIDE, TRANS, M, N, K, MB, A, LDA,
+     $        T, LDT, C, LDC, WORK, INFO)
         RETURN
       END IF
 *
          IF(II.LE.N) THEN
 *
 *       Multiply Q to the last block of C
-*  
+*
           CALL STPMLQT('R','T',M , KK, K, 0,MB, A(1,II), LDA,
      $      T(1,CTR*K+1),LDT, C(1,1), LDC,
      $      C(1,II), LDC, WORK, INFO )
 *
 *     End of SLAMSWLQ
 *
-      END
\ No newline at end of file
+      END