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

◆ zlarf1f()

subroutine zlarf1f ( character side,
integer m,
integer n,
complex*16, dimension( * ) v,
integer incv,
complex*16 tau,
complex*16, dimension( ldc, * ) c,
integer ldc,
complex*16, dimension( * ) work )

ZLARF1F applies an elementary reflector to a general rectangular

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

Purpose:
!>
!> ZLARF1F applies a complex elementary reflector H to a real m by n matrix
!> C, from either the left or the right. H is represented in the form
!>
!>       H = I - tau * v * v**H
!>
!> where tau is a complex scalar and v is a complex vector.
!>
!> If tau = 0, then H is taken to be the unit matrix.
!>
!> To apply H**H, supply conjg(tau) instead
!> tau.
!> 
Parameters
[in]SIDE
!>          SIDE is CHARACTER*1
!>          = 'L': form  H * C
!>
!> \param[in] M
!> \verbatim
!>          M is INTEGER
!>          The number of rows of the matrix C.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrix C.
!> 
[in]V
!>          V is COMPLEX*16 array, dimension
!>                     (1 + (M-1)*abs(INCV)) if SIDE = 'L'
!>                  or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
!>          The vector v in the representation of H. V is not used if
!>          TAU = 0. V(1) is not referenced or modified.
!> 
[in]INCV
!>          INCV is INTEGER
!>          The increment between elements of v. INCV <> 0.
!> 
[in]TAU
!>          TAU is COMPLEX*16
!>          The value tau in the representation of H.
!> 
[in,out]C
!>          C is COMPLEX*16 array, dimension (LDC,N)
!>          On entry, the m by n matrix C.
!>          On exit, C is overwritten by the matrix H * C if SIDE = 'L',
!>          or C * H if SIDE = 'R'.
!> 
[in]LDC
!>          LDC is INTEGER
!>          The leading dimension of the array C. LDC >= max(1,M).
!> 
[out]WORK
!>          WORK is COMPLEX*16 array, dimension
!>                         (N) if SIDE = 'L'
!>                      or (M) if SIDE = 'R'
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 156 of file zlarf1f.f.

157*
158* -- LAPACK auxiliary routine --
159* -- LAPACK is a software package provided by Univ. of Tennessee, --
160* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
161*
162* .. Scalar Arguments ..
163 CHARACTER SIDE
164 INTEGER INCV, LDC, M, N
165 COMPLEX*16 TAU
166* ..
167* .. Array Arguments ..
168 COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 COMPLEX*16 ONE, ZERO
175 parameter( one = ( 1.0d+0, 0.0d+0 ),
176 $ zero = ( 0.0d+0, 0.0d+0 ) )
177* ..
178* .. Local Scalars ..
179 LOGICAL APPLYLEFT
180 INTEGER I, LASTV, LASTC, J
181* ..
182* .. External Subroutines ..
183 EXTERNAL zgemv, zgerc, zscal
184* .. Intrinsic Functions ..
185 INTRINSIC dconjg
186* ..
187* .. External Functions ..
188 LOGICAL LSAME
189 INTEGER ILAZLR, ILAZLC
190 EXTERNAL lsame, ilazlr, ilazlc
191* ..
192* .. Executable Statements ..
193*
194 applyleft = lsame( side, 'L' )
195 lastv = 1
196 lastc = 0
197 IF( tau.NE.zero ) THEN
198! Set up variables for scanning V. LASTV begins pointing to the end
199! of V.
200 IF( applyleft ) THEN
201 lastv = m
202 ELSE
203 lastv = n
204 END IF
205 IF( incv.GT.0 ) THEN
206 i = 1 + (lastv-1) * incv
207 ELSE
208 i = 1
209 END IF
210! Look for the last non-zero row in V.
211! Since we are assuming that V(1) = 1, and it is not stored, so we
212! shouldn't access it.
213 DO WHILE( lastv.GT.1 .AND. v( i ).EQ.zero )
214 lastv = lastv - 1
215 i = i - incv
216 END DO
217 IF( applyleft ) THEN
218! Scan for the last non-zero column in C(1:lastv,:).
219 lastc = ilazlc(lastv, n, c, ldc)
220 ELSE
221! Scan for the last non-zero row in C(:,1:lastv).
222 lastc = ilazlr(m, lastv, c, ldc)
223 END IF
224 END IF
225 IF( lastc.EQ.0 ) THEN
226 RETURN
227 END IF
228 IF( applyleft ) THEN
229*
230* Form H * C
231*
232 ! Check if m = 1. This means v = 1, So we just need to compute
233 ! C := HC = (1-\tau)C.
234 IF( lastv.EQ.1 ) THEN
235 CALL zscal(lastc, one - tau, c, ldc)
236 ELSE
237*
238* w(1:lastc,1) := C(1:lastv,1:lastc)**H * v(1:lastv,1)
239*
240 ! (I - tvv**H)C = C - tvv**H C
241 ! First compute w**H = v**H c -> w = C**H v
242 ! C = [ C_1 C_2 ]**T, v = [1 v_2]**T
243 ! w = C_1**H + C_2**Hv_2
244 ! w = C_2**Hv_2
245 CALL zgemv( 'Conjugate transpose', lastv - 1,
246 $ lastc, one, c( 1+1, 1 ), ldc, v( 1 + incv ),
247 $ incv, zero, work, 1 )
248*
249* w(1:lastc,1) += v(1,1) * C(1,1:lastc)**H
250*
251 DO i = 1, lastc
252 work( i ) = work( i ) + dconjg( c( 1, i ) )
253 END DO
254*
255* C(1:lastv,1:lastc) := C(...) - tau * v(1:lastv,1) * w(1:lastc,1)**H
256*
257 ! C(1, 1:lastc) := C(...) - tau * v(1,1) * w(1:lastc,1)**H
258 ! = C(...) - tau * Conj(w(1:lastc,1))
259 ! This is essentially a zaxpyc
260 DO i = 1, lastc
261 c( 1, i ) = c( 1, i ) - tau * dconjg( work( i ) )
262 END DO
263*
264* C(2:lastv,1:lastc) += - tau * v(2:lastv,1) * w(1:lastc,1)**H
265*
266 CALL zgerc( lastv - 1, lastc, -tau, v( 1 + incv ),
267 $ incv, work, 1, c( 1+1, 1 ), ldc )
268 END IF
269 ELSE
270*
271* Form C * H
272*
273 ! Check if n = 1. This means v = 1, so we just need to compute
274 ! C := CH = C(1-\tau).
275 IF( lastv.EQ.1 ) THEN
276 CALL zscal(lastc, one - tau, c, 1)
277 ELSE
278*
279* w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
280*
281 ! w(1:lastc,1) := C(1:lastc,2:lastv) * v(2:lastv,1)
282 CALL zgemv( 'No transpose', lastc, lastv-1, one,
283 $ c(1,1+1), ldc, v(1+incv), incv, zero, work, 1 )
284 ! w(1:lastc,1) += C(1:lastc,1) v(1,1) = C(1:lastc,1)
285 CALL zaxpy(lastc, one, c, 1, work, 1)
286*
287* C(1:lastc,1:lastv) := C(...) - tau * w(1:lastc,1) * v(1:lastv,1)**T
288*
289 ! C(1:lastc,1) := C(...) - tau * w(1:lastc,1) * v(1,1)**T
290 ! = C(...) - tau * w(1:lastc,1)
291 CALL zaxpy(lastc, -tau, work, 1, c, 1)
292 ! C(1:lastc,2:lastv) := C(...) - tau * w(1:lastc,1) * v(2:lastv)**T
293 CALL zgerc( lastc, lastv-1, -tau, work, 1, v(1+incv),
294 $ incv, c(1,1+1), ldc )
295 END IF
296 END IF
297 RETURN
298*
299* End of ZLARF1F
300*
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)
ZGERC
Definition zgerc.f:130
integer function ilazlc(m, n, a, lda)
ILAZLC scans a matrix for its last non-zero column.
Definition ilazlc.f:76
integer function ilazlr(m, n, a, lda)
ILAZLR scans a matrix for its last non-zero row.
Definition ilazlr.f:76
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
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: