1*> \brief \b ZGEQRFP 2* 3* =========== DOCUMENTATION =========== 4* 5* Online html documentation available at 6* http://www.netlib.org/lapack/explore-html/ 7* 8*> \htmlonly 9*> Download ZGEQRFP + dependencies 10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgeqrfp.f"> 11*> [TGZ]</a> 12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgeqrfp.f"> 13*> [ZIP]</a> 14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqrfp.f"> 15*> [TXT]</a> 16*> \endhtmlonly 17* 18* Definition: 19* =========== 20* 21* SUBROUTINE ZGEQRFP( M, N, A, LDA, TAU, WORK, LWORK, INFO ) 22* 23* .. Scalar Arguments .. 24* INTEGER INFO, LDA, LWORK, 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*> ZGEQR2P computes a QR factorization of a complex M-by-N matrix A: 37*> 38*> A = Q * ( R ), 39*> ( 0 ) 40*> 41*> where: 42*> 43*> Q is a M-by-M orthogonal matrix; 44*> R is an upper-triangular N-by-N matrix with nonnegative diagonal 45*> entries; 46*> 0 is a (M-N)-by-N zero matrix, if M > N. 47*> 48*> \endverbatim 49* 50* Arguments: 51* ========== 52* 53*> \param[in] M 54*> \verbatim 55*> M is INTEGER 56*> The number of rows of the matrix A. M >= 0. 57*> \endverbatim 58*> 59*> \param[in] N 60*> \verbatim 61*> N is INTEGER 62*> The number of columns of the matrix A. N >= 0. 63*> \endverbatim 64*> 65*> \param[in,out] A 66*> \verbatim 67*> A is COMPLEX*16 array, dimension (LDA,N) 68*> On entry, the M-by-N matrix A. 69*> On exit, the elements on and above the diagonal of the array 70*> contain the min(M,N)-by-N upper trapezoidal matrix R (R is 71*> upper triangular if m >= n). The diagonal entries of R 72*> are real and nonnegative; The elements below the diagonal, 73*> with the array TAU, represent the unitary matrix Q as a 74*> product of min(m,n) elementary reflectors (see Further 75*> Details). 76*> \endverbatim 77*> 78*> \param[in] LDA 79*> \verbatim 80*> LDA is INTEGER 81*> The leading dimension of the array A. LDA >= max(1,M). 82*> \endverbatim 83*> 84*> \param[out] TAU 85*> \verbatim 86*> TAU is COMPLEX*16 array, dimension (min(M,N)) 87*> The scalar factors of the elementary reflectors (see Further 88*> Details). 89*> \endverbatim 90*> 91*> \param[out] WORK 92*> \verbatim 93*> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK)) 94*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK. 95*> \endverbatim 96*> 97*> \param[in] LWORK 98*> \verbatim 99*> LWORK is INTEGER 100*> The dimension of the array WORK. LWORK >= max(1,N). 101*> For optimum performance LWORK >= N*NB, where NB is 102*> the optimal blocksize. 103*> 104*> If LWORK = -1, then a workspace query is assumed; the routine 105*> only calculates the optimal size of the WORK array, returns 106*> this value as the first entry of the WORK array, and no error 107*> message related to LWORK is issued by XERBLA. 108*> \endverbatim 109*> 110*> \param[out] INFO 111*> \verbatim 112*> INFO is INTEGER 113*> = 0: successful exit 114*> < 0: if INFO = -i, the i-th argument had an illegal value 115*> \endverbatim 116* 117* Authors: 118* ======== 119* 120*> \author Univ. of Tennessee 121*> \author Univ. of California Berkeley 122*> \author Univ. of Colorado Denver 123*> \author NAG Ltd. 124* 125*> \ingroup complex16GEcomputational 126* 127*> \par Further Details: 128* ===================== 129*> 130*> \verbatim 131*> 132*> The matrix Q is represented as a product of elementary reflectors 133*> 134*> Q = H(1) H(2) . . . H(k), where k = min(m,n). 135*> 136*> Each H(i) has the form 137*> 138*> H(i) = I - tau * v * v**H 139*> 140*> where tau is a complex scalar, and v is a complex vector with 141*> v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in A(i+1:m,i), 142*> and tau in TAU(i). 143*> 144*> See Lapack Working Note 203 for details 145*> \endverbatim 146*> 147* ===================================================================== 148 SUBROUTINE ZGEQRFP( M, N, A, LDA, TAU, WORK, LWORK, INFO ) 149* 150* -- LAPACK computational routine -- 151* -- LAPACK is a software package provided by Univ. of Tennessee, -- 152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- 153* 154* .. Scalar Arguments .. 155 INTEGER INFO, LDA, LWORK, M, N 156* .. 157* .. Array Arguments .. 158 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) 159* .. 160* 161* ===================================================================== 162* 163* .. Local Scalars .. 164 LOGICAL LQUERY 165 INTEGER I, IB, IINFO, IWS, K, LDWORK, LWKOPT, NB, 166 $ NBMIN, NX 167* .. 168* .. External Subroutines .. 169 EXTERNAL XERBLA, ZGEQR2P, ZLARFB, ZLARFT 170* .. 171* .. Intrinsic Functions .. 172 INTRINSIC MAX, MIN 173* .. 174* .. External Functions .. 175 INTEGER ILAENV 176 EXTERNAL ILAENV 177* .. 178* .. Executable Statements .. 179* 180* Test the input arguments 181* 182 INFO = 0 183 NB = ILAENV( 1, 'ZGEQRF', ' ', M, N, -1, -1 ) 184 LWKOPT = N*NB 185 WORK( 1 ) = LWKOPT 186 LQUERY = ( LWORK.EQ.-1 ) 187 IF( M.LT.0 ) THEN 188 INFO = -1 189 ELSE IF( N.LT.0 ) THEN 190 INFO = -2 191 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN 192 INFO = -4 193 ELSE IF( LWORK.LT.MAX( 1, N ) .AND. .NOT.LQUERY ) THEN 194 INFO = -7 195 END IF 196 IF( INFO.NE.0 ) THEN 197 CALL XERBLA( 'ZGEQRFP', -INFO ) 198 RETURN 199 ELSE IF( LQUERY ) THEN 200 RETURN 201 END IF 202* 203* Quick return if possible 204* 205 K = MIN( M, N ) 206 IF( K.EQ.0 ) THEN 207 WORK( 1 ) = 1 208 RETURN 209 END IF 210* 211 NBMIN = 2 212 NX = 0 213 IWS = N 214 IF( NB.GT.1 .AND. NB.LT.K ) THEN 215* 216* Determine when to cross over from blocked to unblocked code. 217* 218 NX = MAX( 0, ILAENV( 3, 'ZGEQRF', ' ', M, N, -1, -1 ) ) 219 IF( NX.LT.K ) THEN 220* 221* Determine if workspace is large enough for blocked code. 222* 223 LDWORK = N 224 IWS = LDWORK*NB 225 IF( LWORK.LT.IWS ) THEN 226* 227* Not enough workspace to use optimal NB: reduce NB and 228* determine the minimum value of NB. 229* 230 NB = LWORK / LDWORK 231 NBMIN = MAX( 2, ILAENV( 2, 'ZGEQRF', ' ', M, N, -1, 232 $ -1 ) ) 233 END IF 234 END IF 235 END IF 236* 237 IF( NB.GE.NBMIN .AND. NB.LT.K .AND. NX.LT.K ) THEN 238* 239* Use blocked code initially 240* 241 DO 10 I = 1, K - NX, NB 242 IB = MIN( K-I+1, NB ) 243* 244* Compute the QR factorization of the current block 245* A(i:m,i:i+ib-1) 246* 247 CALL ZGEQR2P( M-I+1, IB, A( I, I ), LDA, TAU( I ), WORK, 248 $ IINFO ) 249 IF( I+IB.LE.N ) THEN 250* 251* Form the triangular factor of the block reflector 252* H = H(i) H(i+1) . . . H(i+ib-1) 253* 254 CALL ZLARFT( 'Forward', 'Columnwise', M-I+1, IB, 255 $ A( I, I ), LDA, TAU( I ), WORK, LDWORK ) 256* 257* Apply H**H to A(i:m,i+ib:n) from the left 258* 259 CALL ZLARFB( 'Left', 'Conjugate transpose', 'Forward', 260 $ 'Columnwise', M-I+1, N-I-IB+1, IB, 261 $ A( I, I ), LDA, WORK, LDWORK, A( I, I+IB ), 262 $ LDA, WORK( IB+1 ), LDWORK ) 263 END IF 264 10 CONTINUE 265 ELSE 266 I = 1 267 END IF 268* 269* Use unblocked code to factor the last or only block. 270* 271 IF( I.LE.K ) 272 $ CALL ZGEQR2P( M-I+1, N-I+1, A( I, I ), LDA, TAU( I ), WORK, 273 $ IINFO ) 274* 275 WORK( 1 ) = IWS 276 RETURN 277* 278* End of ZGEQRFP 279* 280 END 281