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

◆ dlarf1f()

subroutine dlarf1f ( character side,
integer m,
integer n,
double precision, dimension( * ) v,
integer incv,
double precision tau,
double precision, dimension( ldc, * ) c,
integer ldc,
double precision, dimension( * ) work )

DLARF1F applies an elementary reflector to a general rectangular

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

Purpose:
!>
!> DLARF1F applies a real 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**T
!>
!> where tau is a real scalar and v is a real vector.
!>
!> If tau = 0, then H is taken to be the unit matrix.
!> 
Parameters
[in]SIDE
!>          SIDE is CHARACTER*1
!>          = 'L': form  H * C
!>          = 'R': form  C * H
!> 
[in]M
!>          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 DOUBLE PRECISION 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 DOUBLE PRECISION
!>          The value tau in the representation of H.
!> 
[in,out]C
!>          C is DOUBLE PRECISION 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 DOUBLE PRECISION 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 dlarf1f.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 DOUBLE PRECISION TAU
166* ..
167* .. Array Arguments ..
168 DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 DOUBLE PRECISION ONE, ZERO
175 parameter( one = 1.0d+0, zero = 0.0d+0 )
176* ..
177* .. Local Scalars ..
178 LOGICAL APPLYLEFT
179 INTEGER I, LASTV, LASTC
180* ..
181* .. External Subroutines ..
182 EXTERNAL dgemv, dger, daxpy, dscal
183* ..
184* .. External Functions ..
185 LOGICAL LSAME
186 INTEGER ILADLR, ILADLC
187 EXTERNAL lsame, iladlr, iladlc
188* ..
189* .. Executable Statements ..
190*
191 applyleft = lsame( side, 'L' )
192 lastv = 1
193 lastc = 0
194 IF( tau.NE.zero ) THEN
195! Set up variables for scanning V. LASTV begins pointing to the end
196! of V.
197 IF( applyleft ) THEN
198 lastv = m
199 ELSE
200 lastv = n
201 END IF
202 IF( incv.GT.0 ) THEN
203 i = 1 + (lastv-1) * incv
204 ELSE
205 i = 1
206 END IF
207! Look for the last non-zero row in V.
208! Since we are assuming that V(1) = 1, and it is not stored, so we
209! shouldn't access it.
210 DO WHILE( lastv.GT.1 .AND. v( i ).EQ.zero )
211 lastv = lastv - 1
212 i = i - incv
213 END DO
214 IF( applyleft ) THEN
215! Scan for the last non-zero column in C(1:lastv,:).
216 lastc = iladlc(lastv, n, c, ldc)
217 ELSE
218! Scan for the last non-zero row in C(:,1:lastv).
219 lastc = iladlr(m, lastv, c, ldc)
220 END IF
221 END IF
222 IF( lastc.EQ.0 ) THEN
223 RETURN
224 END IF
225 IF( applyleft ) THEN
226*
227* Form H * C
228*
229 ! Check if lastv = 1. This means v = 1, So we just need to compute
230 ! C := HC = (1-\tau)C.
231 IF( lastv.EQ.1 ) THEN
232*
233* C(1,1:lastc) := ( 1 - tau ) * C(1,1:lastc)
234*
235 CALL dscal(lastc, one - tau, c, ldc)
236 ELSE
237*
238* w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
239*
240 ! w(1:lastc,1) := C(2:lastv,1:lastc)**T * v(2:lastv,1)
241 CALL dgemv( 'Transpose', lastv-1, lastc, one, c(1+1,1),
242 $ ldc, v(1+incv), incv, zero, work, 1)
243 ! w(1:lastc,1) += C(1,1:lastc)**T * v(1,1) = C(1,1:lastc)**T
244 CALL daxpy(lastc, one, c, ldc, work, 1)
245*
246* C(1:lastv,1:lastc) := C(...) - tau * v(1:lastv,1) * w(1:lastc,1)**T
247*
248 ! C(1, 1:lastc) := C(...) - tau * v(1,1) * w(1:lastc,1)**T
249 ! = C(...) - tau * w(1:lastc,1)**T
250 CALL daxpy(lastc, -tau, work, 1, c, ldc)
251 ! C(2:lastv,1:lastc) := C(...) - tau * v(2:lastv,1)*w(1:lastc,1)**T
252 CALL dger(lastv-1, lastc, -tau, v(1+incv), incv, work, 1,
253 $ c(1+1,1), ldc)
254 END IF
255 ELSE
256*
257* Form C * H
258*
259 ! Check if n = 1. This means v = 1, so we just need to compute
260 ! C := CH = C(1-\tau).
261 IF( lastv.EQ.1 ) THEN
262*
263* C(1:lastc,1) := ( 1 - tau ) * C(1:lastc,1)
264*
265 CALL dscal(lastc, one - tau, c, 1)
266 ELSE
267*
268* w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
269*
270 ! w(1:lastc,1) := C(1:lastc,2:lastv) * v(2:lastv,1)
271 CALL dgemv( 'No transpose', lastc, lastv-1, one,
272 $ c(1,1+1), ldc, v(1+incv), incv, zero, work, 1 )
273 ! w(1:lastc,1) += C(1:lastc,1) v(1,1) = C(1:lastc,1)
274 CALL daxpy(lastc, one, c, 1, work, 1)
275*
276* C(1:lastc,1:lastv) := C(...) - tau * w(1:lastc,1) * v(1:lastv,1)**T
277*
278 ! C(1:lastc,1) := C(...) - tau * w(1:lastc,1) * v(1,1)**T
279 ! = C(...) - tau * w(1:lastc,1)
280 CALL daxpy(lastc, -tau, work, 1, c, 1)
281 ! C(1:lastc,2:lastv) := C(...) - tau * w(1:lastc,1) * v(2:lastv)**T
282 CALL dger( lastc, lastv-1, -tau, work, 1, v(1+incv),
283 $ incv, c(1,1+1), ldc )
284 END IF
285 END IF
286 RETURN
287*
288* End of DLARF1F
289*
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
subroutine dger(m, n, alpha, x, incx, y, incy, a, lda)
DGER
Definition dger.f:130
integer function iladlc(m, n, a, lda)
ILADLC scans a matrix for its last non-zero column.
Definition iladlc.f:76
integer function iladlr(m, n, a, lda)
ILADLR scans a matrix for its last non-zero row.
Definition iladlr.f:76
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: