1       SUBROUTINE ZUNG2R( M, N, K, A, LDA, TAU, WORK, INFO )
  2 *
  3 *  -- LAPACK routine (version 3.2) --
  4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  6 *     November 2006
  7 *
  8 *     .. Scalar Arguments ..
  9       INTEGER            INFO, K, LDA, M, N
 10 *     ..
 11 *     .. Array Arguments ..
 12       COMPLEX*16         A( LDA, * ), TAU( * ), WORK( * )
 13 *     ..
 14 *
 15 *  Purpose
 16 *  =======
 17 *
 18 *  ZUNG2R generates an m by n complex matrix Q with orthonormal columns,
 19 *  which is defined as the first n columns of a product of k elementary
 20 *  reflectors of order m
 21 *
 22 *        Q  =  H(1) H(2) . . . H(k)
 23 *
 24 *  as returned by ZGEQRF.
 25 *
 26 *  Arguments
 27 *  =========
 28 *
 29 *  M       (input) INTEGER
 30 *          The number of rows of the matrix Q. M >= 0.
 31 *
 32 *  N       (input) INTEGER
 33 *          The number of columns of the matrix Q. M >= N >= 0.
 34 *
 35 *  K       (input) INTEGER
 36 *          The number of elementary reflectors whose product defines the
 37 *          matrix Q. N >= K >= 0.
 38 *
 39 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
 40 *          On entry, the i-th column must contain the vector which
 41 *          defines the elementary reflector H(i), for i = 1,2,...,k, as
 42 *          returned by ZGEQRF in the first k columns of its array
 43 *          argument A.
 44 *          On exit, the m by n matrix Q.
 45 *
 46 *  LDA     (input) INTEGER
 47 *          The first dimension of the array A. LDA >= max(1,M).
 48 *
 49 *  TAU     (input) COMPLEX*16 array, dimension (K)
 50 *          TAU(i) must contain the scalar factor of the elementary
 51 *          reflector H(i), as returned by ZGEQRF.
 52 *
 53 *  WORK    (workspace) COMPLEX*16 array, dimension (N)
 54 *
 55 *  INFO    (output) INTEGER
 56 *          = 0: successful exit
 57 *          < 0: if INFO = -i, the i-th argument has an illegal value
 58 *
 59 *  =====================================================================
 60 *
 61 *     .. Parameters ..
 62       COMPLEX*16         ONE, ZERO
 63       PARAMETER          ( ONE = ( 1.0D+00.0D+0 ),
 64      $                   ZERO = ( 0.0D+00.0D+0 ) )
 65 *     ..
 66 *     .. Local Scalars ..
 67       INTEGER            I, J, L
 68 *     ..
 69 *     .. External Subroutines ..
 70       EXTERNAL           XERBLA, ZLARF, ZSCAL
 71 *     ..
 72 *     .. Intrinsic Functions ..
 73       INTRINSIC          MAX
 74 *     ..
 75 *     .. Executable Statements ..
 76 *
 77 *     Test the input arguments
 78 *
 79       INFO = 0
 80       IF( M.LT.0 ) THEN
 81          INFO = -1
 82       ELSE IF( N.LT.0 .OR. N.GT.M ) THEN
 83          INFO = -2
 84       ELSE IF( K.LT.0 .OR. K.GT.N ) THEN
 85          INFO = -3
 86       ELSE IF( LDA.LT.MAX1, M ) ) THEN
 87          INFO = -5
 88       END IF
 89       IF( INFO.NE.0 ) THEN
 90          CALL XERBLA( 'ZUNG2R'-INFO )
 91          RETURN
 92       END IF
 93 *
 94 *     Quick return if possible
 95 *
 96       IF( N.LE.0 )
 97      $   RETURN
 98 *
 99 *     Initialise columns k+1:n to columns of the unit matrix
100 *
101       DO 20 J = K + 1, N
102          DO 10 L = 1, M
103             A( L, J ) = ZERO
104    10    CONTINUE
105          A( J, J ) = ONE
106    20 CONTINUE
107 *
108       DO 40 I = K, 1-1
109 *
110 *        Apply H(i) to A(i:m,i:n) from the left
111 *
112          IF( I.LT.N ) THEN
113             A( I, I ) = ONE
114             CALL ZLARF( 'Left', M-I+1, N-I, A( I, I ), 1, TAU( I ),
115      $                  A( I, I+1 ), LDA, WORK )
116          END IF
117          IF( I.LT.M )
118      $      CALL ZSCAL( M-I, -TAU( I ), A( I+1, I ), 1 )
119          A( I, I ) = ONE - TAU( I )
120 *
121 *        Set A(1:i-1,i) to zero
122 *
123          DO 30 L = 1, I - 1
124             A( L, I ) = ZERO
125    30    CONTINUE
126    40 CONTINUE
127       RETURN
128 *
129 *     End of ZUNG2R
130 *
131       END