4 * SUBROUTINE SGELQT( M, N, MB, A, LDA, T, LDT, WORK, INFO )
6 * .. Scalar Arguments ..
7 * INTEGER INFO, LDA, LDT, M, N, MB
9 * .. Array Arguments ..
10 * REAL A( LDA, * ), T( LDT, * ), WORK( * )
19 *> DGELQT computes a blocked LQ factorization of a real M-by-N matrix A
20 *> using the compact WY representation of Q.
29 *> The number of rows of the matrix A. M >= 0.
35 *> The number of columns of the matrix A. N >= 0.
41 *> The block size to be used in the blocked QR. MIN(M,N) >= MB >= 1.
46 *> A is REAL array, dimension (LDA,N)
47 *> On entry, the M-by-N matrix A.
48 *> On exit, the elements on and below the diagonal of the array
49 *> contain the M-by-MIN(M,N) lower trapezoidal matrix L (L is
50 *> lower triangular if M <= N); the elements above the diagonal
57 *> The leading dimension of the array A. LDA >= max(1,M).
62 *> T is REAL array, dimension (LDT,MIN(M,N))
63 *> The upper triangular block reflectors stored in compact form
64 *> as a sequence of upper triangular blocks. See below
65 *> for further details.
71 *> The leading dimension of the array T. LDT >= MB.
76 *> WORK is REAL array, dimension (MB*N)
82 *> = 0: successful exit
83 *> < 0: if INFO = -i, the i-th argument had an illegal value
89 *> \author Univ. of Tennessee
90 *> \author Univ. of California Berkeley
91 *> \author Univ. of Colorado Denver
94 *> \date November 2013
96 *> \ingroup doubleGEcomputational
98 *> \par Further Details:
99 * =====================
103 *> The matrix V stores the elementary reflectors H(i) in the i-th column
104 *> below the diagonal. For example, if M=5 and N=3, the matrix V is
106 *> V = ( 1 v1 v1 v1 v1 )
111 *> where the vi's represent the vectors which define H(i), which are returned
112 *> in the matrix A. The 1's along the diagonal of V are not stored in A.
113 *> Let K=MIN(M,N). The number of blocks is B = ceiling(K/NB), where each
114 *> block is of order NB except for the last block, which is of order
115 *> IB = K - (B-1)*NB. For each of the B blocks, a upper triangular block
116 *> reflector factor is computed: T1, T2, ..., TB. The NB-by-NB (and IB-by-IB
117 *> for the last block) T's are stored in the NB-by-N matrix T as
119 *> T = (T1 T2 ... TB).
122 * =====================================================================
123 SUBROUTINE SGELQT( M, N, MB, A, LDA, T, LDT, WORK, INFO )
125 * -- LAPACK computational routine (version 3.5.0) --
126 * -- LAPACK is a software package provided by Univ. of Tennessee, --
127 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * .. Scalar Arguments ..
131 INTEGER INFO, LDA, LDT, M, N, MB
133 * .. Array Arguments ..
134 REAL A( LDA, * ), T( LDT, * ), WORK( * )
137 * =====================================================================
140 * .. Local Scalars ..
141 INTEGER I, IB, IINFO, K
143 * .. External Subroutines ..
144 EXTERNAL SGEQRT2, SGEQRT3, SLARFB, XERBLA
146 * .. Executable Statements ..
148 * Test the input arguments
153 ELSE IF( N.LT.0 ) THEN
155 ELSE IF( MB.LT.1 .OR. ( MB.GT.MIN(M,N) .AND. MIN(M,N).GT.0 ) )THEN
157 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
159 ELSE IF( LDT.LT.MB ) THEN
163 CALL XERBLA( 'SGELQT', -INFO )
167 * Quick return if possible
172 * Blocked loop of length K
175 IB = MIN( K-I+1, MB )
177 * Compute the LQ factorization of the current block A(I:M,I:I+IB-1)
179 CALL SGELQT3( IB, N-I+1, A(I,I), LDA, T(1,I), LDT, IINFO )
182 * Update by applying H**T to A(I:M,I+IB:N) from the right
184 CALL SLARFB( 'R', 'N', 'F', 'R', M-I-IB+1, N-I+1, IB,
185 $ A( I, I ), LDA, T( 1, I ), LDT,
186 $ A( I+IB, I ), LDA, WORK , M-I-IB+1 )