1 *> \brief <b> ZGELS solves overdetermined or underdetermined systems for GE matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZGELS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgels.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgels.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgels.f">
21 * SUBROUTINE ZGELS( TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK,
24 * .. Scalar Arguments ..
26 * INTEGER INFO, LDA, LDB, LWORK, M, N, NRHS
28 * .. Array Arguments ..
29 * COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
38 *> ZGELS solves overdetermined or underdetermined complex linear systems
39 *> involving an M-by-N matrix A, or its conjugate-transpose, using a QR
40 *> or LQ factorization of A. It is assumed that A has full rank.
42 *> The following options are provided:
44 *> 1. If TRANS = 'N' and m >= n: find the least squares solution of
45 *> an overdetermined system, i.e., solve the least squares problem
46 *> minimize || B - A*X ||.
48 *> 2. If TRANS = 'N' and m < n: find the minimum norm solution of
49 *> an underdetermined system A * X = B.
51 *> 3. If TRANS = 'C' and m >= n: find the minimum norm solution of
52 *> an undetermined system A**H * X = B.
54 *> 4. If TRANS = 'C' and m < n: find the least squares solution of
55 *> an overdetermined system, i.e., solve the least squares problem
56 *> minimize || B - A**H * X ||.
58 *> Several right hand side vectors b and solution vectors x can be
59 *> handled in a single call; they are stored as the columns of the
60 *> M-by-NRHS right hand side matrix B and the N-by-NRHS solution
69 *> TRANS is CHARACTER*1
70 *> = 'N': the linear system involves A;
71 *> = 'C': the linear system involves A**H.
77 *> The number of rows of the matrix A. M >= 0.
83 *> The number of columns of the matrix A. N >= 0.
89 *> The number of right hand sides, i.e., the number of
90 *> columns of the matrices B and X. NRHS >= 0.
95 *> A is COMPLEX*16 array, dimension (LDA,N)
96 *> On entry, the M-by-N matrix A.
97 *> if M >= N, A is overwritten by details of its QR
98 *> factorization as returned by ZGEQRF;
99 *> if M < N, A is overwritten by details of its LQ
100 *> factorization as returned by ZGELQF.
106 *> The leading dimension of the array A. LDA >= max(1,M).
111 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
112 *> On entry, the matrix B of right hand side vectors, stored
113 *> columnwise; B is M-by-NRHS if TRANS = 'N', or N-by-NRHS
115 *> On exit, if INFO = 0, B is overwritten by the solution
116 *> vectors, stored columnwise:
117 *> if TRANS = 'N' and m >= n, rows 1 to n of B contain the least
118 *> squares solution vectors; the residual sum of squares for the
119 *> solution in each column is given by the sum of squares of the
120 *> modulus of elements N+1 to M in that column;
121 *> if TRANS = 'N' and m < n, rows 1 to N of B contain the
122 *> minimum norm solution vectors;
123 *> if TRANS = 'C' and m >= n, rows 1 to M of B contain the
124 *> minimum norm solution vectors;
125 *> if TRANS = 'C' and m < n, rows 1 to M of B contain the
126 *> least squares solution vectors; the residual sum of squares
127 *> for the solution in each column is given by the sum of
128 *> squares of the modulus of elements M+1 to N in that column.
134 *> The leading dimension of the array B. LDB >= MAX(1,M,N).
139 *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
140 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
146 *> The dimension of the array WORK.
147 *> LWORK >= max( 1, MN + max( MN, NRHS ) ).
148 *> For optimal performance,
149 *> LWORK >= max( 1, MN + max( MN, NRHS )*NB ).
150 *> where MN = min(M,N) and NB is the optimum block size.
152 *> If LWORK = -1, then a workspace query is assumed; the routine
153 *> only calculates the optimal size of the WORK array, returns
154 *> this value as the first entry of the WORK array, and no error
155 *> message related to LWORK is issued by XERBLA.
161 *> = 0: successful exit
162 *> < 0: if INFO = -i, the i-th argument had an illegal value
163 *> > 0: if INFO = i, the i-th diagonal element of the
164 *> triangular factor of A is zero, so that A does not have
165 *> full rank; the least squares solution could not be
172 *> \author Univ. of Tennessee
173 *> \author Univ. of California Berkeley
174 *> \author Univ. of Colorado Denver
177 *> \date November 2011
179 *> \ingroup complex16GEsolve
181 * =====================================================================
182 SUBROUTINE ZGELS( TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK,
185 * -- LAPACK driver routine (version 3.4.0) --
186 * -- LAPACK is a software package provided by Univ. of Tennessee, --
187 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
190 * .. Scalar Arguments ..
192 INTEGER INFO, LDA, LDB, LWORK, M, N, NRHS
194 * .. Array Arguments ..
195 COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
198 * =====================================================================
201 DOUBLE PRECISION ZERO, ONE
202 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
204 PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ) )
206 * .. Local Scalars ..
208 INTEGER BROW, I, IASCL, IBSCL, J, MN, NB, SCLLEN, WSIZE
209 DOUBLE PRECISION ANRM, BIGNUM, BNRM, SMLNUM
212 DOUBLE PRECISION RWORK( 1 )
214 * .. External Functions ..
217 DOUBLE PRECISION DLAMCH, ZLANGE
218 EXTERNAL LSAME, ILAENV, DLAMCH, ZLANGE
220 * .. External Subroutines ..
221 EXTERNAL DLABAD, XERBLA, ZGELQF, ZGEQRF, ZLASCL, ZLASET,
222 $ ZTRTRS, ZUNMLQ, ZUNMQR
224 * .. Intrinsic Functions ..
225 INTRINSIC DBLE, MAX, MIN
227 * .. Executable Statements ..
229 * Test the input arguments.
233 LQUERY = ( LWORK.EQ.-1 )
234 IF( .NOT.( LSAME( TRANS, 'N' ) .OR. LSAME( TRANS, 'C' ) ) ) THEN
236 ELSE IF( M.LT.0 ) THEN
238 ELSE IF( N.LT.0 ) THEN
240 ELSE IF( NRHS.LT.0 ) THEN
242 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
244 ELSE IF( LDB.LT.MAX( 1, M, N ) ) THEN
246 ELSE IF( LWORK.LT.MAX( 1, MN+MAX( MN, NRHS ) ) .AND. .NOT.LQUERY )
251 * Figure out optimal block size
253 IF( INFO.EQ.0 .OR. INFO.EQ.-10 ) THEN
256 IF( LSAME( TRANS, 'N' ) )
260 NB = ILAENV( 1, 'ZGEQRF', ' ', M, N, -1, -1 )
262 NB = MAX( NB, ILAENV( 1, 'ZUNMQR', 'LN', M, NRHS, N,
265 NB = MAX( NB, ILAENV( 1, 'ZUNMQR', 'LC', M, NRHS, N,
269 NB = ILAENV( 1, 'ZGELQF', ' ', M, N, -1, -1 )
271 NB = MAX( NB, ILAENV( 1, 'ZUNMLQ', 'LC', N, NRHS, M,
274 NB = MAX( NB, ILAENV( 1, 'ZUNMLQ', 'LN', N, NRHS, M,
279 WSIZE = MAX( 1, MN+MAX( MN, NRHS )*NB )
280 WORK( 1 ) = DBLE( WSIZE )
285 CALL XERBLA( 'ZGELS ', -INFO )
287 ELSE IF( LQUERY ) THEN
291 * Quick return if possible
293 IF( MIN( M, N, NRHS ).EQ.0 ) THEN
294 CALL ZLASET( 'Full', MAX( M, N ), NRHS, CZERO, CZERO, B, LDB )
298 * Get machine parameters
300 SMLNUM = DLAMCH( 'S' ) / DLAMCH( 'P' )
301 BIGNUM = ONE / SMLNUM
302 CALL DLABAD( SMLNUM, BIGNUM )
304 * Scale A, B if max element outside range [SMLNUM,BIGNUM]
306 ANRM = ZLANGE( 'M', M, N, A, LDA, RWORK )
308 IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
310 * Scale matrix norm up to SMLNUM
312 CALL ZLASCL( 'G', 0, 0, ANRM, SMLNUM, M, N, A, LDA, INFO )
314 ELSE IF( ANRM.GT.BIGNUM ) THEN
316 * Scale matrix norm down to BIGNUM
318 CALL ZLASCL( 'G', 0, 0, ANRM, BIGNUM, M, N, A, LDA, INFO )
320 ELSE IF( ANRM.EQ.ZERO ) THEN
322 * Matrix all zero. Return zero solution.
324 CALL ZLASET( 'F', MAX( M, N ), NRHS, CZERO, CZERO, B, LDB )
331 BNRM = ZLANGE( 'M', BROW, NRHS, B, LDB, RWORK )
333 IF( BNRM.GT.ZERO .AND. BNRM.LT.SMLNUM ) THEN
335 * Scale matrix norm up to SMLNUM
337 CALL ZLASCL( 'G', 0, 0, BNRM, SMLNUM, BROW, NRHS, B, LDB,
340 ELSE IF( BNRM.GT.BIGNUM ) THEN
342 * Scale matrix norm down to BIGNUM
344 CALL ZLASCL( 'G', 0, 0, BNRM, BIGNUM, BROW, NRHS, B, LDB,
351 * compute QR factorization of A
353 CALL ZGEQRF( M, N, A, LDA, WORK( 1 ), WORK( MN+1 ), LWORK-MN,
356 * workspace at least N, optimally N*NB
360 * Least-Squares Problem min || A * X - B ||
362 * B(1:M,1:NRHS) := Q**H * B(1:M,1:NRHS)
364 CALL ZUNMQR( 'Left', 'Conjugate transpose', M, NRHS, N, A,
365 $ LDA, WORK( 1 ), B, LDB, WORK( MN+1 ), LWORK-MN,
368 * workspace at least NRHS, optimally NRHS*NB
370 * B(1:N,1:NRHS) := inv(R) * B(1:N,1:NRHS)
372 CALL ZTRTRS( 'Upper', 'No transpose', 'Non-unit', N, NRHS,
373 $ A, LDA, B, LDB, INFO )
383 * Overdetermined system of equations A**H * X = B
385 * B(1:N,1:NRHS) := inv(R**H) * B(1:N,1:NRHS)
387 CALL ZTRTRS( 'Upper', 'Conjugate transpose','Non-unit',
388 $ N, NRHS, A, LDA, B, LDB, INFO )
394 * B(N+1:M,1:NRHS) = ZERO
402 * B(1:M,1:NRHS) := Q(1:N,:) * B(1:N,1:NRHS)
404 CALL ZUNMQR( 'Left', 'No transpose', M, NRHS, N, A, LDA,
405 $ WORK( 1 ), B, LDB, WORK( MN+1 ), LWORK-MN,
408 * workspace at least NRHS, optimally NRHS*NB
416 * Compute LQ factorization of A
418 CALL ZGELQF( M, N, A, LDA, WORK( 1 ), WORK( MN+1 ), LWORK-MN,
421 * workspace at least M, optimally M*NB.
425 * underdetermined system of equations A * X = B
427 * B(1:M,1:NRHS) := inv(L) * B(1:M,1:NRHS)
429 CALL ZTRTRS( 'Lower', 'No transpose', 'Non-unit', M, NRHS,
430 $ A, LDA, B, LDB, INFO )
436 * B(M+1:N,1:NRHS) = 0
444 * B(1:N,1:NRHS) := Q(1:N,:)**H * B(1:M,1:NRHS)
446 CALL ZUNMLQ( 'Left', 'Conjugate transpose', N, NRHS, M, A,
447 $ LDA, WORK( 1 ), B, LDB, WORK( MN+1 ), LWORK-MN,
450 * workspace at least NRHS, optimally NRHS*NB
456 * overdetermined system min || A**H * X - B ||
458 * B(1:N,1:NRHS) := Q * B(1:N,1:NRHS)
460 CALL ZUNMLQ( 'Left', 'No transpose', N, NRHS, M, A, LDA,
461 $ WORK( 1 ), B, LDB, WORK( MN+1 ), LWORK-MN,
464 * workspace at least NRHS, optimally NRHS*NB
466 * B(1:M,1:NRHS) := inv(L**H) * B(1:M,1:NRHS)
468 CALL ZTRTRS( 'Lower', 'Conjugate transpose', 'Non-unit',
469 $ M, NRHS, A, LDA, B, LDB, INFO )
483 IF( IASCL.EQ.1 ) THEN
484 CALL ZLASCL( 'G', 0, 0, ANRM, SMLNUM, SCLLEN, NRHS, B, LDB,
486 ELSE IF( IASCL.EQ.2 ) THEN
487 CALL ZLASCL( 'G', 0, 0, ANRM, BIGNUM, SCLLEN, NRHS, B, LDB,
490 IF( IBSCL.EQ.1 ) THEN
491 CALL ZLASCL( 'G', 0, 0, SMLNUM, BNRM, SCLLEN, NRHS, B, LDB,
493 ELSE IF( IBSCL.EQ.2 ) THEN
494 CALL ZLASCL( 'G', 0, 0, BIGNUM, BNRM, SCLLEN, NRHS, B, LDB,
499 WORK( 1 ) = DBLE( WSIZE )