1*> \brief \b CLASWLQ 2* 3* Definition: 4* =========== 5* 6* SUBROUTINE CLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, 7* LWORK, INFO) 8* 9* .. Scalar Arguments .. 10* INTEGER INFO, LDA, M, N, MB, NB, LDT, LWORK 11* .. 12* .. Array Arguments .. 13* COMPLEX A( LDA, * ), T( LDT, * ), WORK( * ) 14* .. 15* 16* 17*> \par Purpose: 18* ============= 19*> 20*> \verbatim 21*> 22*> CLASWLQ computes a blocked Tall-Skinny LQ factorization of 23*> a complex M-by-N matrix A for M <= N: 24*> 25*> A = ( L 0 ) * Q, 26*> 27*> where: 28*> 29*> Q is a n-by-N orthogonal matrix, stored on exit in an implicit 30*> form in the elements above the diagonal of the array A and in 31*> the elements of the array T; 32*> L is a lower-triangular M-by-M matrix stored on exit in 33*> the elements on and below the diagonal of the array A. 34*> 0 is a M-by-(N-M) zero matrix, if M < N, and is not stored. 35*> 36*> \endverbatim 37* 38* Arguments: 39* ========== 40* 41*> \param[in] M 42*> \verbatim 43*> M is INTEGER 44*> The number of rows of the matrix A. M >= 0. 45*> \endverbatim 46*> 47*> \param[in] N 48*> \verbatim 49*> N is INTEGER 50*> The number of columns of the matrix A. N >= M >= 0. 51*> \endverbatim 52*> 53*> \param[in] MB 54*> \verbatim 55*> MB is INTEGER 56*> The row block size to be used in the blocked QR. 57*> M >= MB >= 1 58*> \endverbatim 59*> \param[in] NB 60*> \verbatim 61*> NB is INTEGER 62*> The column block size to be used in the blocked QR. 63*> NB > M. 64*> \endverbatim 65*> 66*> \param[in,out] A 67*> \verbatim 68*> A is COMPLEX array, dimension (LDA,N) 69*> On entry, the M-by-N matrix A. 70*> On exit, the elements on and below the diagonal 71*> of the array contain the N-by-N lower triangular matrix L; 72*> the elements above the diagonal represent Q by the rows 73*> of blocked V (see Further Details). 74*> 75*> \endverbatim 76*> 77*> \param[in] LDA 78*> \verbatim 79*> LDA is INTEGER 80*> The leading dimension of the array A. LDA >= max(1,M). 81*> \endverbatim 82*> 83*> \param[out] T 84*> \verbatim 85*> T is COMPLEX array, 86*> dimension (LDT, N * Number_of_row_blocks) 87*> where Number_of_row_blocks = CEIL((N-M)/(NB-M)) 88*> The blocked upper triangular block reflectors stored in compact form 89*> as a sequence of upper triangular blocks. 90*> See Further Details below. 91*> \endverbatim 92*> 93*> \param[in] LDT 94*> \verbatim 95*> LDT is INTEGER 96*> The leading dimension of the array T. LDT >= MB. 97*> \endverbatim 98*> 99*> 100*> \param[out] WORK 101*> \verbatim 102*> (workspace) COMPLEX array, dimension (MAX(1,LWORK)) 103*> 104*> \endverbatim 105*> \param[in] LWORK 106*> \verbatim 107*> The dimension of the array WORK. LWORK >= MB*M. 108*> If LWORK = -1, then a workspace query is assumed; the routine 109*> only calculates the optimal size of the WORK array, returns 110*> this value as the first entry of the WORK array, and no error 111*> message related to LWORK is issued by XERBLA. 112*> 113*> \endverbatim 114*> \param[out] INFO 115*> \verbatim 116*> INFO is INTEGER 117*> = 0: successful exit 118*> < 0: if INFO = -i, the i-th argument had an illegal value 119*> \endverbatim 120* 121* Authors: 122* ======== 123* 124*> \author Univ. of Tennessee 125*> \author Univ. of California Berkeley 126*> \author Univ. of Colorado Denver 127*> \author NAG Ltd. 128* 129*> \par Further Details: 130* ===================== 131*> 132*> \verbatim 133*> Short-Wide LQ (SWLQ) performs LQ by a sequence of orthogonal transformations, 134*> representing Q as a product of other orthogonal matrices 135*> Q = Q(1) * Q(2) * . . . * Q(k) 136*> where each Q(i) zeros out upper diagonal entries of a block of NB rows of A: 137*> Q(1) zeros out the upper diagonal entries of rows 1:NB of A 138*> Q(2) zeros out the bottom MB-N rows of rows [1:M,NB+1:2*NB-M] of A 139*> Q(3) zeros out the bottom MB-N rows of rows [1:M,2*NB-M+1:3*NB-2*M] of A 140*> . . . 141*> 142*> Q(1) is computed by GELQT, which represents Q(1) by Householder vectors 143*> stored under the diagonal of rows 1:MB of A, and by upper triangular 144*> block reflectors, stored in array T(1:LDT,1:N). 145*> For more information see Further Details in GELQT. 146*> 147*> Q(i) for i>1 is computed by TPLQT, which represents Q(i) by Householder vectors 148*> stored in columns [(i-1)*(NB-M)+M+1:i*(NB-M)+M] of A, and by upper triangular 149*> block reflectors, stored in array T(1:LDT,(i-1)*M+1:i*M). 150*> The last Q(k) may use fewer rows. 151*> For more information see Further Details in TPQRT. 152*> 153*> For more details of the overall algorithm, see the description of 154*> Sequential TSQR in Section 2.2 of [1]. 155*> 156*> [1] “Communication-Optimal Parallel and Sequential QR and LU Factorizations,” 157*> J. Demmel, L. Grigori, M. Hoemmen, J. Langou, 158*> SIAM J. Sci. Comput, vol. 34, no. 1, 2012 159*> \endverbatim 160*> 161* ===================================================================== 162 SUBROUTINE CLASWLQ( M, N, MB, NB, A, LDA, T, LDT, WORK, LWORK, 163 $ INFO) 164* 165* -- LAPACK computational routine -- 166* -- LAPACK is a software package provided by Univ. of Tennessee, -- 167* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. -- 168* 169* .. Scalar Arguments .. 170 INTEGER INFO, LDA, M, N, MB, NB, LWORK, LDT 171* .. 172* .. Array Arguments .. 173 COMPLEX A( LDA, * ), WORK( * ), T( LDT, *) 174* .. 175* 176* ===================================================================== 177* 178* .. 179* .. Local Scalars .. 180 LOGICAL LQUERY 181 INTEGER I, II, KK, CTR 182* .. 183* .. EXTERNAL FUNCTIONS .. 184 LOGICAL LSAME 185 EXTERNAL LSAME 186* .. EXTERNAL SUBROUTINES .. 187 EXTERNAL CGELQT, CTPLQT, XERBLA 188* .. INTRINSIC FUNCTIONS .. 189 INTRINSIC MAX, MIN, MOD 190* .. 191* .. EXTERNAL FUNCTIONS .. 192 INTEGER ILAENV 193 EXTERNAL ILAENV 194* .. 195* .. EXECUTABLE STATEMENTS .. 196* 197* TEST THE INPUT ARGUMENTS 198* 199 INFO = 0 200* 201 LQUERY = ( LWORK.EQ.-1 ) 202* 203 IF( M.LT.0 ) THEN 204 INFO = -1 205 ELSE IF( N.LT.0 .OR. N.LT.M ) THEN 206 INFO = -2 207 ELSE IF( MB.LT.1 .OR. ( MB.GT.M .AND. M.GT.0 )) THEN 208 INFO = -3 209 ELSE IF( NB.LE.M ) THEN 210 INFO = -4 211 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN 212 INFO = -5 213 ELSE IF( LDT.LT.MB ) THEN 214 INFO = -8 215 ELSE IF( ( LWORK.LT.M*MB) .AND. (.NOT.LQUERY) ) THEN 216 INFO = -10 217 END IF 218 IF( INFO.EQ.0) THEN 219 WORK(1) = MB*M 220 END IF 221* 222 IF( INFO.NE.0 ) THEN 223 CALL XERBLA( 'CLASWLQ', -INFO ) 224 RETURN 225 ELSE IF (LQUERY) THEN 226 RETURN 227 END IF 228* 229* Quick return if possible 230* 231 IF( MIN(M,N).EQ.0 ) THEN 232 RETURN 233 END IF 234* 235* The LQ Decomposition 236* 237 IF((M.GE.N).OR.(NB.LE.M).OR.(NB.GE.N)) THEN 238 CALL CGELQT( M, N, MB, A, LDA, T, LDT, WORK, INFO) 239 RETURN 240 END IF 241* 242 KK = MOD((N-M),(NB-M)) 243 II=N-KK+1 244* 245* Compute the LQ factorization of the first block A(1:M,1:NB) 246* 247 CALL CGELQT( M, NB, MB, A(1,1), LDA, T, LDT, WORK, INFO) 248 CTR = 1 249* 250 DO I = NB+1, II-NB+M , (NB-M) 251* 252* Compute the QR factorization of the current block A(1:M,I:I+NB-M) 253* 254 CALL CTPLQT( M, NB-M, 0, MB, A(1,1), LDA, A( 1, I ), 255 $ LDA, T(1,CTR*M+1), 256 $ LDT, WORK, INFO ) 257 CTR = CTR + 1 258 END DO 259* 260* Compute the QR factorization of the last block A(1:M,II:N) 261* 262 IF (II.LE.N) THEN 263 CALL CTPLQT( M, KK, 0, MB, A(1,1), LDA, A( 1, II ), 264 $ LDA, T(1,CTR*M+1), LDT, 265 $ WORK, INFO ) 266 END IF 267* 268 WORK( 1 ) = M * MB 269 RETURN 270* 271* End of CLASWLQ 272* 273 END 274