LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zlarfgp()

subroutine zlarfgp ( integer n,
complex*16 alpha,
complex*16, dimension( * ) x,
integer incx,
complex*16 tau )

ZLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.

Download ZLARFGP + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZLARFGP generates a complex elementary reflector H of order n, such
!> that
!>
!>       H**H * ( alpha ) = ( beta ),   H**H * H = I.
!>              (   x   )   (   0  )
!>
!> where alpha and beta are scalars, beta is real and non-negative, and
!> x is an (n-1)-element complex vector.  H is represented in the form
!>
!>       H = I - tau * ( 1 ) * ( 1 v**H ) ,
!>                     ( v )
!>
!> where tau is a complex scalar and v is a complex (n-1)-element
!> vector. Note that H is not hermitian.
!>
!> If the elements of x are all zero and alpha is real, then tau = 0
!> and H is taken to be the unit matrix.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The order of the elementary reflector.
!> 
[in,out]ALPHA
!>          ALPHA is COMPLEX*16
!>          On entry, the value alpha.
!>          On exit, it is overwritten with the value beta.
!> 
[in,out]X
!>          X is COMPLEX*16 array, dimension
!>                         (1+(N-2)*abs(INCX))
!>          On entry, the vector x.
!>          On exit, it is overwritten with the vector v.
!> 
[in]INCX
!>          INCX is INTEGER
!>          The increment between elements of X. INCX > 0.
!> 
[out]TAU
!>          TAU is COMPLEX*16
!>          The value tau.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 101 of file zlarfgp.f.

102*
103* -- LAPACK auxiliary routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER INCX, N
109 COMPLEX*16 ALPHA, TAU
110* ..
111* .. Array Arguments ..
112 COMPLEX*16 X( * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 DOUBLE PRECISION TWO, ONE, ZERO
119 parameter( two = 2.0d+0, one = 1.0d+0, zero = 0.0d+0 )
120* ..
121* .. Local Scalars ..
122 INTEGER J, KNT
123 DOUBLE PRECISION ALPHI, ALPHR, BETA, BIGNUM, EPS, SMLNUM, XNORM
124 COMPLEX*16 SAVEALPHA
125* ..
126* .. External Functions ..
127 DOUBLE PRECISION DLAMCH, DLAPY3, DLAPY2, DZNRM2
128 COMPLEX*16 ZLADIV
129 EXTERNAL dlamch, dlapy3, dlapy2, dznrm2,
130 $ zladiv
131* ..
132* .. Intrinsic Functions ..
133 INTRINSIC abs, dble, dcmplx, dimag, sign
134* ..
135* .. External Subroutines ..
136 EXTERNAL zdscal, zscal
137* ..
138* .. Executable Statements ..
139*
140 IF( n.LE.0 ) THEN
141 tau = zero
142 RETURN
143 END IF
144*
145 eps = dlamch( 'Precision' )
146 xnorm = dznrm2( n-1, x, incx )
147 alphr = dble( alpha )
148 alphi = dimag( alpha )
149*
150 IF( xnorm.LE.eps*abs(alpha) .AND. alphi.EQ.zero ) THEN
151*
152* H = [1-alpha/abs(alpha) 0; 0 I], sign chosen so ALPHA >= 0.
153*
154 IF( alphr.GE.zero ) THEN
155* When TAU.eq.ZERO, the vector is special-cased to be
156* all zeros in the application routines. We do not need
157* to clear it.
158 tau = zero
159 ELSE
160* However, the application routines rely on explicit
161* zero checks when TAU.ne.ZERO, and we must clear X.
162 tau = two
163 DO j = 1, n-1
164 x( 1 + (j-1)*incx ) = zero
165 END DO
166 alpha = -alpha
167 END IF
168 ELSE
169*
170* general case
171*
172 beta = sign( dlapy3( alphr, alphi, xnorm ), alphr )
173 smlnum = dlamch( 'S' ) / dlamch( 'E' )
174 bignum = one / smlnum
175*
176 knt = 0
177 IF( abs( beta ).LT.smlnum ) THEN
178*
179* XNORM, BETA may be inaccurate; scale X and recompute them
180*
181 10 CONTINUE
182 knt = knt + 1
183 CALL zdscal( n-1, bignum, x, incx )
184 beta = beta*bignum
185 alphi = alphi*bignum
186 alphr = alphr*bignum
187 IF( (abs( beta ).LT.smlnum) .AND. (knt .LT. 20) )
188 $ GO TO 10
189*
190* New BETA is at most 1, at least SMLNUM
191*
192 xnorm = dznrm2( n-1, x, incx )
193 alpha = dcmplx( alphr, alphi )
194 beta = sign( dlapy3( alphr, alphi, xnorm ), alphr )
195 END IF
196 savealpha = alpha
197 alpha = alpha + beta
198 IF( beta.LT.zero ) THEN
199 beta = -beta
200 tau = -alpha / beta
201 ELSE
202 alphr = alphi * (alphi/dble( alpha ))
203 alphr = alphr + xnorm * (xnorm/dble( alpha ))
204 tau = dcmplx( alphr/beta, -alphi/beta )
205 alpha = dcmplx( -alphr, alphi )
206 END IF
207 alpha = zladiv( dcmplx( one ), alpha )
208*
209 IF ( abs(tau).LE.smlnum ) THEN
210*
211* In the case where the computed TAU ends up being a denormalized number,
212* it loses relative accuracy. This is a BIG problem. Solution: flush TAU
213* to ZERO (or TWO or whatever makes a nonnegative real number for BETA).
214*
215* (Bug report provided by Pat Quillen from MathWorks on Jul 29, 2009.)
216* (Thanks Pat. Thanks MathWorks.)
217*
218 alphr = dble( savealpha )
219 alphi = dimag( savealpha )
220 IF( alphi.EQ.zero ) THEN
221 IF( alphr.GE.zero ) THEN
222 tau = zero
223 ELSE
224 tau = two
225 DO j = 1, n-1
226 x( 1 + (j-1)*incx ) = zero
227 END DO
228 beta = dble( -savealpha )
229 END IF
230 ELSE
231 xnorm = dlapy2( alphr, alphi )
232 tau = dcmplx( one - alphr / xnorm, -alphi / xnorm )
233 DO j = 1, n-1
234 x( 1 + (j-1)*incx ) = zero
235 END DO
236 beta = xnorm
237 END IF
238*
239 ELSE
240*
241* This is the general case.
242*
243 CALL zscal( n-1, alpha, x, incx )
244*
245 END IF
246*
247* If BETA is subnormal, it may lose relative accuracy
248*
249 DO 20 j = 1, knt
250 beta = beta*smlnum
251 20 CONTINUE
252 alpha = beta
253 END IF
254*
255 RETURN
256*
257* End of ZLARFGP
258*
complex *16 function zladiv(x, y)
ZLADIV performs complex division in real arithmetic, avoiding unnecessary overflow.
Definition zladiv.f:62
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlapy2(x, y)
DLAPY2 returns sqrt(x2+y2).
Definition dlapy2.f:61
double precision function dlapy3(x, y, z)
DLAPY3 returns sqrt(x2+y2+z2).
Definition dlapy3.f:66
real(wp) function dznrm2(n, x, incx)
DZNRM2
Definition dznrm2.f90:90
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
subroutine zscal(n, za, zx, incx)
ZSCAL
Definition zscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: