1*> \brief \b ZUNGHR 2* 3* =========== DOCUMENTATION =========== 4* 5* Online html documentation available at 6* http://www.netlib.org/lapack/explore-html/ 7* 8*> \htmlonly 9*> Download ZUNGHR + dependencies 10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunghr.f"> 11*> [TGZ]</a> 12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunghr.f"> 13*> [ZIP]</a> 14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunghr.f"> 15*> [TXT]</a> 16*> \endhtmlonly 17* 18* Definition: 19* =========== 20* 21* SUBROUTINE ZUNGHR( N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO ) 22* 23* .. Scalar Arguments .. 24* INTEGER IHI, ILO, INFO, LDA, LWORK, N 25* .. 26* .. Array Arguments .. 27* COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) 28* .. 29* 30* 31*> \par Purpose: 32* ============= 33*> 34*> \verbatim 35*> 36*> ZUNGHR generates a complex unitary matrix Q which is defined as the 37*> product of IHI-ILO elementary reflectors of order N, as returned by 38*> ZGEHRD: 39*> 40*> Q = H(ilo) H(ilo+1) . . . H(ihi-1). 41*> \endverbatim 42* 43* Arguments: 44* ========== 45* 46*> \param[in] N 47*> \verbatim 48*> N is INTEGER 49*> The order of the matrix Q. N >= 0. 50*> \endverbatim 51*> 52*> \param[in] ILO 53*> \verbatim 54*> ILO is INTEGER 55*> \endverbatim 56*> 57*> \param[in] IHI 58*> \verbatim 59*> IHI is INTEGER 60*> 61*> ILO and IHI must have the same values as in the previous call 62*> of ZGEHRD. Q is equal to the unit matrix except in the 63*> submatrix Q(ilo+1:ihi,ilo+1:ihi). 64*> 1 <= ILO <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0. 65*> \endverbatim 66*> 67*> \param[in,out] A 68*> \verbatim 69*> A is COMPLEX*16 array, dimension (LDA,N) 70*> On entry, the vectors which define the elementary reflectors, 71*> as returned by ZGEHRD. 72*> On exit, the N-by-N unitary matrix Q. 73*> \endverbatim 74*> 75*> \param[in] LDA 76*> \verbatim 77*> LDA is INTEGER 78*> The leading dimension of the array A. LDA >= max(1,N). 79*> \endverbatim 80*> 81*> \param[in] TAU 82*> \verbatim 83*> TAU is COMPLEX*16 array, dimension (N-1) 84*> TAU(i) must contain the scalar factor of the elementary 85*> reflector H(i), as returned by ZGEHRD. 86*> \endverbatim 87*> 88*> \param[out] WORK 89*> \verbatim 90*> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK)) 91*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK. 92*> \endverbatim 93*> 94*> \param[in] LWORK 95*> \verbatim 96*> LWORK is INTEGER 97*> The dimension of the array WORK. LWORK >= IHI-ILO. 98*> For optimum performance LWORK >= (IHI-ILO)*NB, where NB is 99*> the optimal blocksize. 100*> 101*> If LWORK = -1, then a workspace query is assumed; the routine 102*> only calculates the optimal size of the WORK array, returns 103*> this value as the first entry of the WORK array, and no error 104*> message related to LWORK is issued by XERBLA. 105*> \endverbatim 106*> 107*> \param[out] INFO 108*> \verbatim 109*> INFO is INTEGER 110*> = 0: successful exit 111*> < 0: if INFO = -i, the i-th argument had an illegal value 112*> \endverbatim 113* 114* Authors: 115* ======== 116* 117*> \author Univ. of Tennessee 118*> \author Univ. of California Berkeley 119*> \author Univ. of Colorado Denver 120*> \author NAG Ltd. 121* 122*> \ingroup complex16OTHERcomputational 123* 124* ===================================================================== 125 SUBROUTINE ZUNGHR( N, ILO, IHI, A, LDA, TAU, WORK, LWORK, INFO ) 126* 127* -- LAPACK computational routine -- 128* -- LAPACK is a software package provided by Univ. of Tennessee, -- 129* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- 130* 131* .. Scalar Arguments .. 132 INTEGER IHI, ILO, INFO, LDA, LWORK, N 133* .. 134* .. Array Arguments .. 135 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) 136* .. 137* 138* ===================================================================== 139* 140* .. Parameters .. 141 COMPLEX*16 ZERO, ONE 142 PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ), 143 $ ONE = ( 1.0D+0, 0.0D+0 ) ) 144* .. 145* .. Local Scalars .. 146 LOGICAL LQUERY 147 INTEGER I, IINFO, J, LWKOPT, NB, NH 148* .. 149* .. External Subroutines .. 150 EXTERNAL XERBLA, ZUNGQR 151* .. 152* .. External Functions .. 153 INTEGER ILAENV 154 EXTERNAL ILAENV 155* .. 156* .. Intrinsic Functions .. 157 INTRINSIC MAX, MIN 158* .. 159* .. Executable Statements .. 160* 161* Test the input arguments 162* 163 INFO = 0 164 NH = IHI - ILO 165 LQUERY = ( LWORK.EQ.-1 ) 166 IF( N.LT.0 ) THEN 167 INFO = -1 168 ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN 169 INFO = -2 170 ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN 171 INFO = -3 172 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN 173 INFO = -5 174 ELSE IF( LWORK.LT.MAX( 1, NH ) .AND. .NOT.LQUERY ) THEN 175 INFO = -8 176 END IF 177* 178 IF( INFO.EQ.0 ) THEN 179 NB = ILAENV( 1, 'ZUNGQR', ' ', NH, NH, NH, -1 ) 180 LWKOPT = MAX( 1, NH )*NB 181 WORK( 1 ) = LWKOPT 182 END IF 183* 184 IF( INFO.NE.0 ) THEN 185 CALL XERBLA( 'ZUNGHR', -INFO ) 186 RETURN 187 ELSE IF( LQUERY ) THEN 188 RETURN 189 END IF 190* 191* Quick return if possible 192* 193 IF( N.EQ.0 ) THEN 194 WORK( 1 ) = 1 195 RETURN 196 END IF 197* 198* Shift the vectors which define the elementary reflectors one 199* column to the right, and set the first ilo and the last n-ihi 200* rows and columns to those of the unit matrix 201* 202 DO 40 J = IHI, ILO + 1, -1 203 DO 10 I = 1, J - 1 204 A( I, J ) = ZERO 205 10 CONTINUE 206 DO 20 I = J + 1, IHI 207 A( I, J ) = A( I, J-1 ) 208 20 CONTINUE 209 DO 30 I = IHI + 1, N 210 A( I, J ) = ZERO 211 30 CONTINUE 212 40 CONTINUE 213 DO 60 J = 1, ILO 214 DO 50 I = 1, N 215 A( I, J ) = ZERO 216 50 CONTINUE 217 A( J, J ) = ONE 218 60 CONTINUE 219 DO 80 J = IHI + 1, N 220 DO 70 I = 1, N 221 A( I, J ) = ZERO 222 70 CONTINUE 223 A( J, J ) = ONE 224 80 CONTINUE 225* 226 IF( NH.GT.0 ) THEN 227* 228* Generate Q(ilo+1:ihi,ilo+1:ihi) 229* 230 CALL ZUNGQR( NH, NH, NH, A( ILO+1, ILO+1 ), LDA, TAU( ILO ), 231 $ WORK, LWORK, IINFO ) 232 END IF 233 WORK( 1 ) = LWKOPT 234 RETURN 235* 236* End of ZUNGHR 237* 238 END 239