LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zlarf1f.f
Go to the documentation of this file.
1*> \brief \b ZLARF1F applies an elementary reflector to a general rectangular
2* matrix assuming v(1) = 1.
3*
4* =========== DOCUMENTATION ===========
5*
6* Online html documentation available at
7* http://www.netlib.org/lapack/explore-html/
8*
9*> Download ZLARF1F + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlarf1f.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlarf1f.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarf1f.f">
15*> [TXT]</a>
16*
17* Definition:
18* ===========
19*
20* SUBROUTINE ZLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
21*
22* .. Scalar Arguments ..
23* CHARACTER SIDE
24* INTEGER INCV, LDC, M, N
25* COMPLEX*16 TAU
26* ..
27* .. Array Arguments ..
28* COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZLARF1F applies a complex elementary reflector H to a real m by n matrix
38*> C, from either the left or the right. H is represented in the form
39*>
40*> H = I - tau * v * v**H
41*>
42*> where tau is a complex scalar and v is a complex vector.
43*>
44*> If tau = 0, then H is taken to be the unit matrix.
45*>
46*> To apply H**H, supply conjg(tau) instead
47*> tau.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] SIDE
54*> \verbatim
55*> SIDE is CHARACTER*1
56*> = 'L': form H * C
57*>
58*> \param[in] M
59*> \verbatim
60*> M is INTEGER
61*> The number of rows of the matrix C.
62*> \endverbatim
63*>
64*> \param[in] N
65*> \verbatim
66*> N is INTEGER
67*> The number of columns of the matrix C.
68*> \endverbatim
69*>
70*> \param[in] V
71*> \verbatim
72*> V is COMPLEX*16 array, dimension
73*> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
74*> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
75*> The vector v in the representation of H. V is not used if
76*> TAU = 0. V(1) is not referenced or modified.
77*> \endverbatim
78*>
79*> \param[in] INCV
80*> \verbatim
81*> INCV is INTEGER
82*> The increment between elements of v. INCV <> 0.
83*> \endverbatim
84*>
85*> \param[in] TAU
86*> \verbatim
87*> TAU is COMPLEX*16
88*> The value tau in the representation of H.
89*> \endverbatim
90*>
91*> \param[in,out] C
92*> \verbatim
93*> C is COMPLEX*16 array, dimension (LDC,N)
94*> On entry, the m by n matrix C.
95*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
96*> or C * H if SIDE = 'R'.
97*> \endverbatim
98*>
99*> \param[in] LDC
100*> \verbatim
101*> LDC is INTEGER
102*> The leading dimension of the array C. LDC >= max(1,M).
103*> \endverbatim
104*>
105*> \param[out] WORK
106*> \verbatim
107*> WORK is COMPLEX*16 array, dimension
108*> (N) if SIDE = 'L'
109*> or (M) if SIDE = 'R'
110*> \endverbatim
111* To take advantage of the fact that v(1) = 1, we do the following
112* v = [ 1 v_2 ]**T
113* If SIDE='L'
114* |-----|
115* | C_1 |
116* C =| C_2 |
117* |-----|
118* C_1\in\mathbb{C}^{1\times n}, C_2\in\mathbb{C}^{m-1\times n}
119* So we compute:
120* C = HC = (I - \tau vv**T)C
121* = C - \tau vv**T C
122* w = C**T v = [ C_1**T C_2**T ] [ 1 v_2 ]**T
123* = C_1**T + C_2**T v ( ZGEMM then ZAXPYC-like )
124* C = C - \tau vv**T C
125* = C - \tau vw**T
126* Giving us C_1 = C_1 - \tau w**T ( ZAXPYC-like )
127* and
128* C_2 = C_2 - \tau v_2w**T ( ZGERC )
129* If SIDE='R'
130*
131* C = [ C_1 C_2 ]
132* C_1\in\mathbb{C}^{m\times 1}, C_2\in\mathbb{C}^{m\times n-1}
133* So we compute:
134* C = CH = C(I - \tau vv**T)
135* = C - \tau Cvv**T
136*
137* w = Cv = [ C_1 C_2 ] [ 1 v_2 ]**T
138* = C_1 + C_2v_2 ( ZGEMM then ZAXPYC-like )
139* C = C - \tau Cvv**T
140* = C - \tau wv**T
141* Giving us C_1 = C_1 - \tau w ( ZAXPYC-like )
142* and
143* C_2 = C_2 - \tau wv_2**T ( ZGERC )
144*
145* Authors:
146* ========
147*
148*> \author Univ. of Tennessee
149*> \author Univ. of California Berkeley
150*> \author Univ. of Colorado Denver
151*> \author NAG Ltd.
152*
153*> \ingroup larf
154*
155* =====================================================================
156 SUBROUTINE zlarf1f( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
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*
301 END
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
subroutine zlarf1f(side, m, n, v, incv, tau, c, ldc, work)
ZLARF1F applies an elementary reflector to a general rectangular
Definition zlarf1f.f:157
subroutine zscal(n, za, zx, incx)
ZSCAL
Definition zscal.f:78