1 *> \brief \b CGEQL2 computes the QL factorization of a general rectangular matrix using an unblocked algorithm.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CGEQL2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgeql2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgeql2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgeql2.f">
21 * SUBROUTINE CGEQL2( M, N, A, LDA, TAU, WORK, INFO )
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, M, N
26 * .. Array Arguments ..
27 * COMPLEX A( LDA, * ), TAU( * ), WORK( * )
36 *> CGEQL2 computes a QL factorization of a complex m by n matrix A:
46 *> The number of rows of the matrix A. M >= 0.
52 *> The number of columns of the matrix A. N >= 0.
57 *> A is COMPLEX array, dimension (LDA,N)
58 *> On entry, the m by n matrix A.
59 *> On exit, if m >= n, the lower triangle of the subarray
60 *> A(m-n+1:m,1:n) contains the n by n lower triangular matrix L;
61 *> if m <= n, the elements on and below the (n-m)-th
62 *> superdiagonal contain the m by n lower trapezoidal matrix L;
63 *> the remaining elements, with the array TAU, represent the
64 *> unitary matrix Q as a product of elementary reflectors
65 *> (see Further Details).
71 *> The leading dimension of the array A. LDA >= max(1,M).
76 *> TAU is COMPLEX array, dimension (min(M,N))
77 *> The scalar factors of the elementary reflectors (see Further
83 *> WORK is COMPLEX array, dimension (N)
89 *> = 0: successful exit
90 *> < 0: if INFO = -i, the i-th argument had an illegal value
96 *> \author Univ. of Tennessee
97 *> \author Univ. of California Berkeley
98 *> \author Univ. of Colorado Denver
101 *> \date September 2012
103 *> \ingroup complexGEcomputational
105 *> \par Further Details:
106 * =====================
110 *> The matrix Q is represented as a product of elementary reflectors
112 *> Q = H(k) . . . H(2) H(1), where k = min(m,n).
114 *> Each H(i) has the form
116 *> H(i) = I - tau * v * v**H
118 *> where tau is a complex scalar, and v is a complex vector with
119 *> v(m-k+i+1:m) = 0 and v(m-k+i) = 1; v(1:m-k+i-1) is stored on exit in
120 *> A(1:m-k+i-1,n-k+i), and tau in TAU(i).
123 * =====================================================================
124 SUBROUTINE CGEQL2( M, N, A, LDA, TAU, WORK, INFO )
126 * -- LAPACK computational routine (version 3.4.2) --
127 * -- LAPACK is a software package provided by Univ. of Tennessee, --
128 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * .. Scalar Arguments ..
132 INTEGER INFO, LDA, M, N
134 * .. Array Arguments ..
135 COMPLEX A( LDA, * ), TAU( * ), WORK( * )
138 * =====================================================================
142 PARAMETER ( ONE = ( 1.0E+0, 0.0E+0 ) )
144 * .. Local Scalars ..
148 * .. External Subroutines ..
149 EXTERNAL CLARF, CLARFG, XERBLA
151 * .. Intrinsic Functions ..
152 INTRINSIC CONJG, MAX, MIN
154 * .. Executable Statements ..
156 * Test the input arguments
161 ELSE IF( N.LT.0 ) THEN
163 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
167 CALL XERBLA( 'CGEQL2', -INFO )
175 * Generate elementary reflector H(i) to annihilate
178 ALPHA = A( M-K+I, N-K+I )
179 CALL CLARFG( M-K+I, ALPHA, A( 1, N-K+I ), 1, TAU( I ) )
181 * Apply H(i)**H to A(1:m-k+i,1:n-k+i-1) from the left
183 A( M-K+I, N-K+I ) = ONE
184 CALL CLARF( 'Left', M-K+I, N-K+I-1, A( 1, N-K+I ), 1,
185 $ CONJG( TAU( I ) ), A, LDA, WORK )
186 A( M-K+I, N-K+I ) = ALPHA