001:       SUBROUTINE ZGERQ2( 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*16         A( LDA, * ), TAU( * ), WORK( * )
012: *     ..
013: *
014: *  Purpose
015: *  =======
016: *
017: *  ZGERQ2 computes an RQ factorization of a complex m by n matrix A:
018: *  A = R * Q.
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*16 array, dimension (LDA,N)
030: *          On entry, the m by n matrix A.
031: *          On exit, if m <= n, the upper triangle of the subarray
032: *          A(1:m,n-m+1:n) contains the m by m upper triangular matrix R;
033: *          if m >= n, the elements on and above the (m-n)-th subdiagonal
034: *          contain the m by n upper trapezoidal matrix R; the remaining
035: *          elements, with the array TAU, represent the unitary matrix
036: *          Q as a product of elementary reflectors (see Further
037: *          Details).
038: *
039: *  LDA     (input) INTEGER
040: *          The leading dimension of the array A.  LDA >= max(1,M).
041: *
042: *  TAU     (output) COMPLEX*16 array, dimension (min(M,N))
043: *          The scalar factors of the elementary reflectors (see Further
044: *          Details).
045: *
046: *  WORK    (workspace) COMPLEX*16 array, dimension (M)
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(1)' H(2)' . . . H(k)', 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(n-k+i+1:n) = 0 and v(n-k+i) = 1; conjg(v(1:n-k+i-1)) is stored on
065: *  exit in A(m-k+i,1:n-k+i-1), and tau in TAU(i).
066: *
067: *  =====================================================================
068: *
069: *     .. Parameters ..
070:       COMPLEX*16         ONE
071:       PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ) )
072: *     ..
073: *     .. Local Scalars ..
074:       INTEGER            I, K
075:       COMPLEX*16         ALPHA
076: *     ..
077: *     .. External Subroutines ..
078:       EXTERNAL           XERBLA, ZLACGV, ZLARF, ZLARFP
079: *     ..
080: *     .. Intrinsic Functions ..
081:       INTRINSIC          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( 'ZGERQ2', -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(m-k+i,1:n-k+i-1)
106: *
107:          CALL ZLACGV( N-K+I, A( M-K+I, 1 ), LDA )
108:          ALPHA = A( M-K+I, N-K+I )
109:          CALL ZLARFP( N-K+I, ALPHA, A( M-K+I, 1 ), LDA, TAU( I ) )
110: *
111: *        Apply H(i) to A(1:m-k+i-1,1:n-k+i) from the right
112: *
113:          A( M-K+I, N-K+I ) = ONE
114:          CALL ZLARF( 'Right', M-K+I-1, N-K+I, A( M-K+I, 1 ), LDA,
115:      $               TAU( I ), A, LDA, WORK )
116:          A( M-K+I, N-K+I ) = ALPHA
117:          CALL ZLACGV( N-K+I-1, A( M-K+I, 1 ), LDA )
118:    10 CONTINUE
119:       RETURN
120: *
121: *     End of ZGERQ2
122: *
123:       END
124: