1*> \brief \b ZUNG2R 2* 3* =========== DOCUMENTATION =========== 4* 5* Online html documentation available at 6* http://www.netlib.org/lapack/explore-html/ 7* 8*> \htmlonly 9*> Download ZUNG2R + dependencies 10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zung2r.f"> 11*> [TGZ]</a> 12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zung2r.f"> 13*> [ZIP]</a> 14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zung2r.f"> 15*> [TXT]</a> 16*> \endhtmlonly 17* 18* Definition: 19* =========== 20* 21* SUBROUTINE ZUNG2R( M, N, K, A, LDA, TAU, WORK, INFO ) 22* 23* .. Scalar Arguments .. 24* INTEGER INFO, K, LDA, M, N 25* .. 26* .. Array Arguments .. 27* COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) 28* .. 29* 30* 31*> \par Purpose: 32* ============= 33*> 34*> \verbatim 35*> 36*> ZUNG2R generates an m by n complex matrix Q with orthonormal columns, 37*> which is defined as the first n columns of a product of k elementary 38*> reflectors of order m 39*> 40*> Q = H(1) H(2) . . . H(k) 41*> 42*> as returned by ZGEQRF. 43*> \endverbatim 44* 45* Arguments: 46* ========== 47* 48*> \param[in] M 49*> \verbatim 50*> M is INTEGER 51*> The number of rows of the matrix Q. M >= 0. 52*> \endverbatim 53*> 54*> \param[in] N 55*> \verbatim 56*> N is INTEGER 57*> The number of columns of the matrix Q. M >= N >= 0. 58*> \endverbatim 59*> 60*> \param[in] K 61*> \verbatim 62*> K is INTEGER 63*> The number of elementary reflectors whose product defines the 64*> matrix Q. N >= K >= 0. 65*> \endverbatim 66*> 67*> \param[in,out] A 68*> \verbatim 69*> A is COMPLEX*16 array, dimension (LDA,N) 70*> On entry, the i-th column must contain the vector which 71*> defines the elementary reflector H(i), for i = 1,2,...,k, as 72*> returned by ZGEQRF in the first k columns of its array 73*> argument A. 74*> On exit, the m by n matrix Q. 75*> \endverbatim 76*> 77*> \param[in] LDA 78*> \verbatim 79*> LDA is INTEGER 80*> The first dimension of the array A. LDA >= max(1,M). 81*> \endverbatim 82*> 83*> \param[in] TAU 84*> \verbatim 85*> TAU is COMPLEX*16 array, dimension (K) 86*> TAU(i) must contain the scalar factor of the elementary 87*> reflector H(i), as returned by ZGEQRF. 88*> \endverbatim 89*> 90*> \param[out] WORK 91*> \verbatim 92*> WORK is COMPLEX*16 array, dimension (N) 93*> \endverbatim 94*> 95*> \param[out] INFO 96*> \verbatim 97*> INFO is INTEGER 98*> = 0: successful exit 99*> < 0: if INFO = -i, the i-th argument has an illegal value 100*> \endverbatim 101* 102* Authors: 103* ======== 104* 105*> \author Univ. of Tennessee 106*> \author Univ. of California Berkeley 107*> \author Univ. of Colorado Denver 108*> \author NAG Ltd. 109* 110*> \ingroup complex16OTHERcomputational 111* 112* ===================================================================== 113 SUBROUTINE ZUNG2R( M, N, K, A, LDA, TAU, WORK, INFO ) 114* 115* -- LAPACK computational routine -- 116* -- LAPACK is a software package provided by Univ. of Tennessee, -- 117* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- 118* 119* .. Scalar Arguments .. 120 INTEGER INFO, K, LDA, M, N 121* .. 122* .. Array Arguments .. 123 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) 124* .. 125* 126* ===================================================================== 127* 128* .. Parameters .. 129 COMPLEX*16 ONE, ZERO 130 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ), 131 $ ZERO = ( 0.0D+0, 0.0D+0 ) ) 132* .. 133* .. Local Scalars .. 134 INTEGER I, J, L 135* .. 136* .. External Subroutines .. 137 EXTERNAL XERBLA, ZLARF, ZSCAL 138* .. 139* .. Intrinsic Functions .. 140 INTRINSIC MAX 141* .. 142* .. Executable Statements .. 143* 144* Test the input arguments 145* 146 INFO = 0 147 IF( M.LT.0 ) THEN 148 INFO = -1 149 ELSE IF( N.LT.0 .OR. N.GT.M ) THEN 150 INFO = -2 151 ELSE IF( K.LT.0 .OR. K.GT.N ) THEN 152 INFO = -3 153 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN 154 INFO = -5 155 END IF 156 IF( INFO.NE.0 ) THEN 157 CALL XERBLA( 'ZUNG2R', -INFO ) 158 RETURN 159 END IF 160* 161* Quick return if possible 162* 163 IF( N.LE.0 ) 164 $ RETURN 165* 166* Initialise columns k+1:n to columns of the unit matrix 167* 168 DO 20 J = K + 1, N 169 DO 10 L = 1, M 170 A( L, J ) = ZERO 171 10 CONTINUE 172 A( J, J ) = ONE 173 20 CONTINUE 174* 175 DO 40 I = K, 1, -1 176* 177* Apply H(i) to A(i:m,i:n) from the left 178* 179 IF( I.LT.N ) THEN 180 A( I, I ) = ONE 181 CALL ZLARF( 'Left', M-I+1, N-I, A( I, I ), 1, TAU( I ), 182 $ A( I, I+1 ), LDA, WORK ) 183 END IF 184 IF( I.LT.M ) 185 $ CALL ZSCAL( M-I, -TAU( I ), A( I+1, I ), 1 ) 186 A( I, I ) = ONE - TAU( I ) 187* 188* Set A(1:i-1,i) to zero 189* 190 DO 30 L = 1, I - 1 191 A( L, I ) = ZERO 192 30 CONTINUE 193 40 CONTINUE 194 RETURN 195* 196* End of ZUNG2R 197* 198 END 199