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