5 * SUBROUTINE CGELQ( M, N, A, LDA, WORK1, LWORK1, WORK2, LWORK2,
8 * .. Scalar Arguments ..
9 * INTEGER INFO, LDA, M, N, LWORK1, LWORK2
11 * .. Array Arguments ..
12 * COMPLEX*16 A( LDA, * ), WORK1( * ), WORK2( * )
21 *> ZGELQ computes an LQ factorization of an M-by-N matrix A,
22 *> using ZLASWLQ when A is short and wide
23 *> (N sufficiently greater than M), and otherwise ZGELQT:
33 *> The number of rows of the matrix A. M >= 0.
39 *> The number of columns of the matrix A. N >= 0.
44 *> A is COMPLEX*16 array, dimension (LDA,N)
45 *> On entry, the M-by-N matrix A.
46 *> On exit, the elements on and below the diagonal of the array
47 *> contain the M-by-min(M,N) lower trapezoidal matrix L
48 *> (L is lower triangular if M <= N);
49 *> the elements above the diagonal are the rows of
50 *> blocked V representing Q (see Further Details).
56 *> The leading dimension of the array A. LDA >= max(1,M).
61 *> WORK1 is COMPLEX*16 array, dimension (MAX(1,LWORK1))
62 *> WORK1 contains part of the data structure used to store Q.
63 *> WORK1(1): algorithm type = 1, to indicate output from
65 *> WORK1(2): optimum size of WORK1
66 *> WORK1(3): minimum size of WORK1
67 *> WORK1(4): horizontal block size
68 *> WORK1(5): vertical block size
69 *> WORK1(6:LWORK1): data structure needed for Q, computed by
76 *> The dimension of the array WORK1.
77 *> If LWORK1 = -1, then a query is assumed. In this case the
78 *> routine calculates the optimal size of WORK1 and
79 *> returns this value in WORK1(2), and calculates the minimum
80 *> size of WORK1 and returns this value in WORK1(3).
81 *> No error message related to LWORK1 is issued by XERBLA when
87 *> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK2))
93 *> The dimension of the array WORK2.
94 *> If LWORK2 = -1, then a query is assumed. In this case the
95 *> routine calculates the optimal size of WORK2 and
96 *> returns this value in WORK2(1), and calculates the minimum
97 *> size of WORK2 and returns this value in WORK2(2).
98 *> No error message related to LWORK2 is issued by XERBLA when
105 *> = 0: successful exit
106 *> < 0: if INFO = -i, the i-th argument had an illegal value
112 *> \author Univ. of Tennessee
113 *> \author Univ. of California Berkeley
114 *> \author Univ. of Colorado Denver
117 *> \par Further Details:
118 * =====================
121 *> Depending on the matrix dimensions M and N, and row and column
122 *> block sizes MB and NB returned by ILAENV, GELQ will use either
123 *> LASWLQ(if the matrix is short-and-wide) or GELQT to compute
124 *> the LQ decomposition.
125 *> The output of LASWLQ or GELQT representing Q is stored in A and in
126 *> array WORK1(6:LWORK1) for later use.
127 *> WORK1(2:5) contains the matrix dimensions M,N and block sizes MB, NB
128 *> which are needed to interpret A and WORK1(6:LWORK1) for later use.
129 *> WORK1(1)=1 indicates that the code needed to take WORK1(2:5) and
130 *> decide whether LASWLQ or GELQT was used is the same as used below in
131 *> GELQ. For a detailed description of A and WORK1(6:LWORK1), see
132 *> Further Details in LASWLQ or GELQT.
135 * =====================================================================
136 SUBROUTINE ZGELQ( M, N, A, LDA, WORK1, LWORK1, WORK2, LWORK2,
139 * -- LAPACK computational routine (version 3.5.0) --
140 * -- LAPACK is a software package provided by Univ. of Tennessee, --
141 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. --
144 * .. Scalar Arguments ..
145 INTEGER INFO, LDA, M, N, LWORK1, LWORK2
147 * .. Array Arguments ..
148 COMPLEX*16 A( LDA, * ), WORK1( * ), WORK2( * )
151 * =====================================================================
154 * .. Local Scalars ..
155 LOGICAL LQUERY, LMINWS
156 INTEGER MB, NB, I, II, KK, MINLW1, NBLCKS
158 * .. EXTERNAL FUNCTIONS ..
161 * .. EXTERNAL SUBROUTINES ..
162 EXTERNAL ZGELQT, ZLASWLQ, XERBLA
163 * .. INTRINSIC FUNCTIONS ..
164 INTRINSIC MAX, MIN, MOD
166 * .. EXTERNAL FUNCTIONS ..
170 * .. EXECUTABLE STATEMENTS ..
172 * TEST THE INPUT ARGUMENTS
176 LQUERY = ( LWORK1.EQ.-1 .OR. LWORK2.EQ.-1 )
178 * Determine the block size
180 IF ( MIN(M,N).GT.0 ) THEN
181 MB = ILAENV( 1, 'ZGELQ ', ' ', M, N, 1, -1)
182 NB = ILAENV( 1, 'ZGELQ ', ' ', M, N, 2, -1)
187 IF( MB.GT.MIN(M,N).OR.MB.LT.1) MB = 1
188 IF( NB.GT.N.OR.NB.LE.M) NB = N
190 IF ((NB.GT.M).AND.(N.GT.M)) THEN
191 IF(MOD(N-M, NB-M).EQ.0) THEN
192 NBLCKS = (N-M)/(NB-M)
194 NBLCKS = (N-M)/(NB-M) + 1
200 * Determine if the workspace size satisfies minimum size
203 IF((LWORK1.LT.MAX(1,MB*M*NBLCKS+5)
204 $ .OR.(LWORK2.LT.MB*M)).AND.(LWORK2.GE.M).AND.(LWORK1.GE.M+5)
205 $ .AND.(.NOT.LQUERY)) THEN
206 IF (LWORK1.LT.MAX(1,MB*M*NBLCKS+5)) THEN
210 IF (LWORK1.LT.MAX(1,M*NBLCKS+5)) THEN
214 IF (LWORK2.LT.MB*M) THEN
222 ELSE IF( N.LT.0 ) THEN
224 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
226 ELSE IF( LWORK1.LT.MAX( 1, MB*M*NBLCKS+5 )
227 $ .AND.(.NOT.LQUERY).AND. (.NOT.LMINWS)) THEN
229 ELSE IF( (LWORK2.LT.MAX(1,M*MB)).AND.(.NOT.LQUERY)
230 $ .AND.(.NOT.LMINWS) ) THEN
236 WORK1(2) = MB*M*NBLCKS+5
244 CALL XERBLA( 'ZGELQ', -INFO )
246 ELSE IF (LQUERY) THEN
250 * Quick return if possible
252 IF( MIN(M,N).EQ.0 ) THEN
256 * The LQ Decomposition
258 IF((N.LE.M).OR.(NB.LE.M).OR.(NB.GE.N)) THEN
259 CALL ZGELQT( M, N, MB, A, LDA, WORK1(6), MB, WORK2, INFO)
261 CALL ZLASWLQ( M, N, MB, NB, A, LDA, WORK1(6), MB, WORK2,