Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / zgelq.f
1 *
2 *  Definition:
3 *  ===========
4 *
5 *       SUBROUTINE CGELQ( M, N, A, LDA, WORK1, LWORK1, WORK2, LWORK2,
6 *                          INFO)
7 *
8 *       .. Scalar Arguments ..
9 *       INTEGER           INFO, LDA, M, N, LWORK1, LWORK2
10 *       ..
11 *       .. Array Arguments ..
12 *       COMPLEX*16        A( LDA, * ), WORK1( * ), WORK2( * )
13 *       ..
14 *
15 *
16 *> \par Purpose:
17 *  =============
18 *>
19 *> \verbatim
20 *>
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:
24 *> A = L * Q .
25 *> \endverbatim
26 *
27 *  Arguments:
28 *  ==========
29 *
30 *> \param[in] M
31 *> \verbatim
32 *>          M is INTEGER
33 *>          The number of rows of the matrix A.  M >= 0.
34 *> \endverbatim
35 *>
36 *> \param[in] N
37 *> \verbatim
38 *>          N is INTEGER
39 *>          The number of columns of the matrix A.  N >= 0.
40 *> \endverbatim
41 *>
42 *> \param[in,out] A
43 *> \verbatim
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).
51 *> \endverbatim
52 *>
53 *> \param[in] LDA
54 *> \verbatim
55 *>          LDA is INTEGER
56 *>          The leading dimension of the array A.  LDA >= max(1,M).
57 *> \endverbatim
58 *>
59 *> \param[out] WORK1
60 *> \verbatim
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
64 *>                    ZLASWLQ or ZGELQT
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
70 *>                           ZLASWLQ or ZGELQT
71 *> \endverbatim
72 *>
73 *> \param[in] LWORK1
74 *> \verbatim
75 *>          LWORK1 is INTEGER
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
82 *>          LWORK1 = -1.
83 *> \endverbatim
84 *>
85 *> \param[out] WORK2
86 *> \verbatim
87 *>         (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK2))
88 *>
89 *> \endverbatim
90 *> \param[in] LWORK2
91 *> \verbatim
92 *>          LWORK2 is INTEGER
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
99 *>          LWORK2 = -1.
100 *> \endverbatim
101 *>
102 *> \param[out] INFO
103 *> \verbatim
104 *>          INFO is INTEGER
105 *>          = 0:  successful exit
106 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
107 *> \endverbatim
108 *
109 *  Authors:
110 *  ========
111 *
112 *> \author Univ. of Tennessee
113 *> \author Univ. of California Berkeley
114 *> \author Univ. of Colorado Denver
115 *> \author NAG Ltd.
116 *
117 *> \par Further Details:
118 *  =====================
119 *>
120 *> \verbatim
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.
133 *> \endverbatim
134 *>
135 *  =====================================================================
136       SUBROUTINE ZGELQ( M, N, A, LDA, WORK1, LWORK1, WORK2, LWORK2,
137      $   INFO)
138 *
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. --
142 *     November 2013
143 *
144 *     .. Scalar Arguments ..
145       INTEGER           INFO, LDA, M, N, LWORK1, LWORK2
146 *     ..
147 *     .. Array Arguments ..
148       COMPLEX*16  A( LDA, * ), WORK1( * ), WORK2( * )
149 *     ..
150 *
151 *  =====================================================================
152 *
153 *     ..
154 *     .. Local Scalars ..
155       LOGICAL    LQUERY, LMINWS
156       INTEGER    MB, NB, I, II, KK, MINLW1, NBLCKS
157 *     ..
158 *     .. EXTERNAL FUNCTIONS ..
159       LOGICAL            LSAME
160       EXTERNAL           LSAME
161 *     .. EXTERNAL SUBROUTINES ..
162       EXTERNAL           ZGELQT, ZLASWLQ, XERBLA
163 *     .. INTRINSIC FUNCTIONS ..
164       INTRINSIC          MAX, MIN, MOD
165 *     ..
166 *     .. EXTERNAL FUNCTIONS ..
167       INTEGER            ILAENV
168       EXTERNAL           ILAENV
169 *     ..
170 *     .. EXECUTABLE STATEMENTS ..
171 *
172 *     TEST THE INPUT ARGUMENTS
173 *
174       INFO = 0
175 *
176       LQUERY = ( LWORK1.EQ.-1 .OR. LWORK2.EQ.-1 )
177 *
178 *     Determine the block size
179 *
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)
183       ELSE
184         MB = 1
185         NB = N
186       END IF
187       IF( MB.GT.MIN(M,N).OR.MB.LT.1) MB = 1
188       IF( NB.GT.N.OR.NB.LE.M) NB = N
189       MINLW1 = M + 5
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)
193         ELSE
194           NBLCKS = (N-M)/(NB-M) + 1
195         END IF
196       ELSE
197         NBLCKS = 1
198       END IF
199 *
200 *     Determine if the workspace size satisfies minimum size
201 *
202       LMINWS = .FALSE.
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
207             LMINWS = .TRUE.
208             MB = 1
209         END IF
210         IF (LWORK1.LT.MAX(1,M*NBLCKS+5)) THEN
211             LMINWS = .TRUE.
212             NB = N
213         END IF
214         IF (LWORK2.LT.MB*M) THEN
215             LMINWS = .TRUE.
216             MB = 1
217         END IF
218       END IF
219 *
220       IF( M.LT.0 ) THEN
221         INFO = -1
222       ELSE IF( N.LT.0 ) THEN
223         INFO = -2
224       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
225         INFO = -4
226       ELSE IF( LWORK1.LT.MAX( 1, MB*M*NBLCKS+5 )
227      $   .AND.(.NOT.LQUERY).AND. (.NOT.LMINWS)) THEN
228         INFO = -6
229       ELSE IF( (LWORK2.LT.MAX(1,M*MB)).AND.(.NOT.LQUERY)
230      $   .AND.(.NOT.LMINWS) ) THEN
231         INFO = -8
232       END IF
233 *
234       IF( INFO.EQ.0)  THEN
235         WORK1(1) = 1
236         WORK1(2) = MB*M*NBLCKS+5
237         WORK1(3) = MINLW1
238         WORK1(4) = MB
239         WORK1(5) = NB
240         WORK2(1) = MB * M
241         WORK2(2) = M
242       END IF
243       IF( INFO.NE.0 ) THEN
244         CALL XERBLA( 'ZGELQ', -INFO )
245         RETURN
246       ELSE IF (LQUERY) THEN
247        RETURN
248       END IF
249 *
250 *     Quick return if possible
251 *
252       IF( MIN(M,N).EQ.0 ) THEN
253           RETURN
254       END IF
255 *
256 *     The LQ Decomposition
257 *
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)
260       ELSE
261          CALL ZLASWLQ( M, N, MB, NB, A, LDA, WORK1(6), MB, WORK2,
262      $                    LWORK2, INFO)
263       END IF
264       RETURN
265 *
266 *     End of ZGELQ
267 *
268       END