001:       SUBROUTINE CGEQL2( M, N, A, LDA, TAU, WORK, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       INTEGER            INFO, LDA, M, N
009: *     ..
010: *     .. Array Arguments ..
011:       COMPLEX            A( LDA, * ), TAU( * ), WORK( * )
012: *     ..
013: *
014: *  Purpose
015: *  =======
016: *
017: *  CGEQL2 computes a QL factorization of a complex m by n matrix A:
018: *  A = Q * L.
019: *
020: *  Arguments
021: *  =========
022: *
023: *  M       (input) INTEGER
024: *          The number of rows of the matrix A.  M >= 0.
025: *
026: *  N       (input) INTEGER
027: *          The number of columns of the matrix A.  N >= 0.
028: *
029: *  A       (input/output) COMPLEX array, dimension (LDA,N)
030: *          On entry, the m by n matrix A.
031: *          On exit, if m >= n, the lower triangle of the subarray
032: *          A(m-n+1:m,1:n) contains the n by n lower triangular matrix L;
033: *          if m <= n, the elements on and below the (n-m)-th
034: *          superdiagonal contain the m by n lower trapezoidal matrix L;
035: *          the remaining elements, with the array TAU, represent the
036: *          unitary matrix Q as a product of elementary reflectors
037: *          (see Further Details).
038: *
039: *  LDA     (input) INTEGER
040: *          The leading dimension of the array A.  LDA >= max(1,M).
041: *
042: *  TAU     (output) COMPLEX array, dimension (min(M,N))
043: *          The scalar factors of the elementary reflectors (see Further
044: *          Details).
045: *
046: *  WORK    (workspace) COMPLEX array, dimension (N)
047: *
048: *  INFO    (output) INTEGER
049: *          = 0: successful exit
050: *          < 0: if INFO = -i, the i-th argument had an illegal value
051: *
052: *  Further Details
053: *  ===============
054: *
055: *  The matrix Q is represented as a product of elementary reflectors
056: *
057: *     Q = H(k) . . . H(2) H(1), where k = min(m,n).
058: *
059: *  Each H(i) has the form
060: *
061: *     H(i) = I - tau * v * v'
062: *
063: *  where tau is a complex scalar, and v is a complex vector with
064: *  v(m-k+i+1:m) = 0 and v(m-k+i) = 1; v(1:m-k+i-1) is stored on exit in
065: *  A(1:m-k+i-1,n-k+i), and tau in TAU(i).
066: *
067: *  =====================================================================
068: *
069: *     .. Parameters ..
070:       COMPLEX            ONE
071:       PARAMETER          ( ONE = ( 1.0E+0, 0.0E+0 ) )
072: *     ..
073: *     .. Local Scalars ..
074:       INTEGER            I, K
075:       COMPLEX            ALPHA
076: *     ..
077: *     .. External Subroutines ..
078:       EXTERNAL           CLARF, CLARFP, XERBLA
079: *     ..
080: *     .. Intrinsic Functions ..
081:       INTRINSIC          CONJG, MAX, MIN
082: *     ..
083: *     .. Executable Statements ..
084: *
085: *     Test the input arguments
086: *
087:       INFO = 0
088:       IF( M.LT.0 ) THEN
089:          INFO = -1
090:       ELSE IF( N.LT.0 ) THEN
091:          INFO = -2
092:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
093:          INFO = -4
094:       END IF
095:       IF( INFO.NE.0 ) THEN
096:          CALL XERBLA( 'CGEQL2', -INFO )
097:          RETURN
098:       END IF
099: *
100:       K = MIN( M, N )
101: *
102:       DO 10 I = K, 1, -1
103: *
104: *        Generate elementary reflector H(i) to annihilate
105: *        A(1:m-k+i-1,n-k+i)
106: *
107:          ALPHA = A( M-K+I, N-K+I )
108:          CALL CLARFP( M-K+I, ALPHA, A( 1, N-K+I ), 1, TAU( I ) )
109: *
110: *        Apply H(i)' to A(1:m-k+i,1:n-k+i-1) from the left
111: *
112:          A( M-K+I, N-K+I ) = ONE
113:          CALL CLARF( 'Left', M-K+I, N-K+I-1, A( 1, N-K+I ), 1,
114:      $               CONJG( TAU( I ) ), A, LDA, WORK )
115:          A( M-K+I, N-K+I ) = ALPHA
116:    10 CONTINUE
117:       RETURN
118: *
119: *     End of CGEQL2
120: *
121:       END
122: