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

◆ dlarf()

subroutine dlarf ( 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 )

DLARF applies an elementary reflector to a general rectangular matrix.

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

Purpose:
!>
!> DLARF 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.
!> 
[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 121 of file dlarf.f.

122*
123* -- LAPACK auxiliary routine --
124* -- LAPACK is a software package provided by Univ. of Tennessee, --
125* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126*
127* .. Scalar Arguments ..
128 CHARACTER SIDE
129 INTEGER INCV, LDC, M, N
130 DOUBLE PRECISION TAU
131* ..
132* .. Array Arguments ..
133 DOUBLE PRECISION C( LDC, * ), V( * ), WORK( * )
134* ..
135*
136* =====================================================================
137*
138* .. Parameters ..
139 DOUBLE PRECISION ONE, ZERO
140 parameter( one = 1.0d+0, zero = 0.0d+0 )
141* ..
142* .. Local Scalars ..
143 LOGICAL APPLYLEFT
144 INTEGER I, LASTV, LASTC
145* ..
146* .. External Subroutines ..
147 EXTERNAL dgemv, dger
148* ..
149* .. External Functions ..
150 LOGICAL LSAME
151 INTEGER ILADLR, ILADLC
152 EXTERNAL lsame, iladlr, iladlc
153* ..
154* .. Executable Statements ..
155*
156 applyleft = lsame( side, 'L' )
157 lastv = 0
158 lastc = 0
159 IF( tau.NE.zero ) THEN
160! Set up variables for scanning V. LASTV begins pointing to the end
161! of V.
162 IF( applyleft ) THEN
163 lastv = m
164 ELSE
165 lastv = n
166 END IF
167 IF( incv.GT.0 ) THEN
168 i = 1 + (lastv-1) * incv
169 ELSE
170 i = 1
171 END IF
172! Look for the last non-zero row in V.
173 DO WHILE( lastv.GT.0 .AND. v( i ).EQ.zero )
174 lastv = lastv - 1
175 i = i - incv
176 END DO
177 IF( applyleft ) THEN
178! Scan for the last non-zero column in C(1:lastv,:).
179 lastc = iladlc(lastv, n, c, ldc)
180 ELSE
181! Scan for the last non-zero row in C(:,1:lastv).
182 lastc = iladlr(m, lastv, c, ldc)
183 END IF
184 END IF
185! Note that lastc.eq.0 renders the BLAS operations null; no special
186! case is needed at this level.
187 IF( applyleft ) THEN
188*
189* Form H * C
190*
191 IF( lastv.GT.0 ) THEN
192*
193* w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
194*
195 CALL dgemv( 'Transpose', lastv, lastc, one, c, ldc, v,
196 $ incv,
197 $ zero, work, 1 )
198*
199* C(1:lastv,1:lastc) := C(...) - v(1:lastv,1) * w(1:lastc,1)**T
200*
201 CALL dger( lastv, lastc, -tau, v, incv, work, 1, c, ldc )
202 END IF
203 ELSE
204*
205* Form C * H
206*
207 IF( lastv.GT.0 ) THEN
208*
209* w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
210*
211 CALL dgemv( 'No transpose', lastc, lastv, one, c, ldc,
212 $ v, incv, zero, work, 1 )
213*
214* C(1:lastc,1:lastv) := C(...) - w(1:lastc,1) * v(1:lastv,1)**T
215*
216 CALL dger( lastc, lastv, -tau, work, 1, v, incv, c, ldc )
217 END IF
218 END IF
219 RETURN
220*
221* End of DLARF
222*
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
Here is the call graph for this function:
Here is the caller graph for this function: