3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CGEQRT + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgeqrt.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgeqrt.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgeqrt.f">
21 * SUBROUTINE CGEQRT( M, N, NB, A, LDA, T, LDT, WORK, INFO )
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, LDT, M, N, NB
26 * .. Array Arguments ..
27 * COMPLEX A( LDA, * ), T( LDT, * ), WORK( * )
36 *> CGEQRT computes a blocked QR factorization of a complex M-by-N matrix A
37 *> using the compact WY representation of Q.
46 *> The number of rows of the matrix A. M >= 0.
52 *> The number of columns of the matrix A. N >= 0.
58 *> The block size to be used in the blocked QR. MIN(M,N) >= NB >= 1.
63 *> A is COMPLEX array, dimension (LDA,N)
64 *> On entry, the M-by-N matrix A.
65 *> On exit, the elements on and above the diagonal of the array
66 *> contain the min(M,N)-by-N upper trapezoidal matrix R (R is
67 *> upper triangular if M >= N); the elements below the diagonal
68 *> are the columns of V.
74 *> The leading dimension of the array A. LDA >= max(1,M).
79 *> T is COMPLEX array, dimension (LDT,MIN(M,N))
80 *> The upper triangular block reflectors stored in compact form
81 *> as a sequence of upper triangular blocks. See below
82 *> for further details.
88 *> The leading dimension of the array T. LDT >= NB.
93 *> WORK is COMPLEX array, dimension (NB*N)
99 *> = 0: successful exit
100 *> < 0: if INFO = -i, the i-th argument had an illegal value
106 *> \author Univ. of Tennessee
107 *> \author Univ. of California Berkeley
108 *> \author Univ. of Colorado Denver
111 *> \date November 2013
113 *> \ingroup complexGEcomputational
115 *> \par Further Details:
116 * =====================
120 *> The matrix V stores the elementary reflectors H(i) in the i-th column
121 *> below the diagonal. For example, if M=5 and N=3, the matrix V is
129 *> where the vi's represent the vectors which define H(i), which are returned
130 *> in the matrix A. The 1's along the diagonal of V are not stored in A.
132 *> Let K=MIN(M,N). The number of blocks is B = ceiling(K/NB), where each
133 *> block is of order NB except for the last block, which is of order
134 *> IB = K - (B-1)*NB. For each of the B blocks, a upper triangular block
135 *> reflector factor is computed: T1, T2, ..., TB. The NB-by-NB (and IB-by-IB
136 *> for the last block) T's are stored in the NB-by-N matrix T as
138 *> T = (T1 T2 ... TB).
141 * =====================================================================
142 SUBROUTINE CGEQRT( M, N, NB, A, LDA, T, LDT, WORK, INFO )
144 * -- LAPACK computational routine (version 3.5.0) --
145 * -- LAPACK is a software package provided by Univ. of Tennessee, --
146 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149 * .. Scalar Arguments ..
150 INTEGER INFO, LDA, LDT, M, N, NB
152 * .. Array Arguments ..
153 COMPLEX A( LDA, * ), T( LDT, * ), WORK( * )
156 * =====================================================================
159 * .. Local Scalars ..
160 INTEGER I, IB, IINFO, K
161 LOGICAL USE_RECURSIVE_QR
162 PARAMETER( USE_RECURSIVE_QR=.TRUE. )
164 * .. External Subroutines ..
165 EXTERNAL CGEQRT2, CGEQRT3, CLARFB, XERBLA
167 * .. Executable Statements ..
169 * Test the input arguments
174 ELSE IF( N.LT.0 ) THEN
176 ELSE IF( NB.LT.1 .OR. ( NB.GT.MIN(M,N) .AND. MIN(M,N).GT.0 ) )THEN
178 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
180 ELSE IF( LDT.LT.NB ) THEN
184 CALL XERBLA( 'CGEQRT', -INFO )
188 * Quick return if possible
193 * Blocked loop of length K
196 IB = MIN( K-I+1, NB )
198 * Compute the QR factorization of the current block A(I:M,I:I+IB-1)
200 IF( USE_RECURSIVE_QR ) THEN
201 CALL CGEQRT3( M-I+1, IB, A(I,I), LDA, T(1,I), LDT, IINFO )
203 CALL CGEQRT2( M-I+1, IB, A(I,I), LDA, T(1,I), LDT, IINFO )
207 * Update by applying H**H to A(I:M,I+IB:N) from the left
209 CALL CLARFB( 'L', 'C', 'F', 'C', M-I+1, N-I-IB+1, IB,
210 $ A( I, I ), LDA, T( 1, I ), LDT,
211 $ A( I, I+IB ), LDA, WORK , N-I-IB+1 )