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

◆ slarf1l()

subroutine slarf1l ( character side,
integer m,
integer n,
real, dimension( * ) v,
integer incv,
real tau,
real, dimension( ldc, * ) c,
integer ldc,
real, dimension( * ) work )

SLARF1L applies an elementary reflector to a general rectangular

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

Purpose:
!>
!> SLARF1L 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 assuming v(lastv) = 1,
!> where lastv is the last non-zero element.
!>
!> 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 REAL 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 REAL
!>          The value tau in the representation of H.
!> 
[in,out]C
!>          C is REAL 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 REAL 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 124 of file slarf1l.f.

125*
126* -- LAPACK auxiliary routine --
127* -- LAPACK is a software package provided by Univ. of Tennessee, --
128* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130* .. Scalar Arguments ..
131 CHARACTER SIDE
132 INTEGER INCV, LDC, M, N
133 REAL TAU
134* ..
135* .. Array Arguments ..
136 REAL C( LDC, * ), V( * ), WORK( * )
137* ..
138*
139* =====================================================================
140*
141* .. Parameters ..
142 REAL ONE, ZERO
143 parameter( one = 1.0e+0, zero = 0.0e+0 )
144* ..
145* .. Local Scalars ..
146 LOGICAL APPLYLEFT
147 INTEGER I, LASTV, LASTC, FIRSTV
148* ..
149* .. External Subroutines ..
150 EXTERNAL sgemv, sger, saxpy, sscal
151* ..
152* .. External Functions ..
153 LOGICAL LSAME
154 INTEGER ILASLR, ILASLC
155 EXTERNAL lsame, ilaslr, ilaslc
156* ..
157* .. Executable Statements ..
158*
159 applyleft = lsame( side, 'L' )
160 firstv = 1
161 lastc = 0
162 IF( tau.NE.zero ) THEN
163! Set up variables for scanning V. LASTV begins pointing to the end
164! of V up to V(1).
165 IF( applyleft ) THEN
166 lastv = m
167 ELSE
168 lastv = n
169 END IF
170 i = 1
171! Look for the last non-zero row in V.
172 DO WHILE( lastv.GT.firstv .AND. v( i ).EQ.zero )
173 firstv = firstv + 1
174 i = i + incv
175 END DO
176 IF( applyleft ) THEN
177! Scan for the last non-zero column in C(1:lastv,:).
178 lastc = ilaslc(lastv, n, c, ldc)
179 ELSE
180! Scan for the last non-zero row in C(:,1:lastv).
181 lastc = ilaslr(m, lastv, c, ldc)
182 END IF
183 END IF
184 IF( lastc.EQ.0 ) THEN
185 RETURN
186 END IF
187 IF( applyleft ) THEN
188*
189* Form H * C
190*
191 IF( lastv.EQ.firstv ) THEN
192*
193* C(lastv,1:lastc) := ( 1 - tau ) * C(lastv,1:lastc)
194*
195 CALL sscal( lastc, one - tau, c( lastv, 1 ), ldc )
196 ELSE
197*
198* w(1:lastc,1) := C(firstv:lastv-1,1:lastc)**T * v(firstv:lastv-1,1)
199*
200 CALL sgemv( 'Transpose', lastv - firstv, lastc, one,
201 $ c( firstv, 1 ), ldc, v( i ), incv, zero,
202 $ work, 1 )
203*
204* w(1:lastc,1) += C(lastv,1:lastc)**T * v(lastv,1)
205*
206 CALL saxpy( lastc, one, c( lastv, 1 ), ldc, work, 1 )
207*
208* C(lastv,1:lastc) += - tau * v(lastv,1) * w(1:lastc,1)**T
209*
210 CALL saxpy( lastc, -tau, work, 1, c( lastv, 1 ), ldc )
211*
212* C(firstv:lastv-1,1:lastc) += - tau * v(firstv:lastv-1,1) * w(1:lastc,1)**T
213*
214 CALL sger( lastv - firstv, lastc, -tau, v( i ), incv,
215 $ work, 1, c( firstv, 1 ), ldc)
216 END IF
217 ELSE
218*
219* Form C * H
220*
221 IF( lastv.EQ.firstv ) THEN
222*
223* C(1:lastc,lastv) := ( 1 - tau ) * C(1:lastc,lastv)
224*
225 CALL sscal( lastc, one - tau, c( 1, lastv ), 1 )
226 ELSE
227*
228* w(1:lastc,1) := C(1:lastc,firstv:lastv-1) * v(firstv:lastv-1,1)
229*
230 CALL sgemv( 'No transpose', lastc, lastv - firstv, one,
231 $ c( 1, firstv ), ldc, v( i ), incv, zero,
232 $ work, 1 )
233*
234* w(1:lastc,1) += C(1:lastc,lastv) * v(lastv,1)
235*
236 CALL saxpy( lastc, one, c( 1, lastv ), 1, work, 1 )
237*
238* C(1:lastc,lastv) += - tau * v(lastv,1) * w(1:lastc,1)
239*
240 CALL saxpy( lastc, -tau, work, 1, c( 1, lastv ), 1 )
241*
242* C(1:lastc,firstv:lastv-1) += - tau * w(1:lastc,1) * v(firstv:lastv-1)**T
243*
244 CALL sger( lastc, lastv - firstv, -tau, work, 1, v( i ),
245 $ incv, c( 1, firstv ), ldc )
246 END IF
247 END IF
248 RETURN
249*
250* End of SLARF1L
251*
subroutine saxpy(n, sa, sx, incx, sy, incy)
SAXPY
Definition saxpy.f:89
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)
SGER
Definition sger.f:130
integer function ilaslc(m, n, a, lda)
ILASLC scans a matrix for its last non-zero column.
Definition ilaslc.f:76
integer function ilaslr(m, n, a, lda)
ILASLR scans a matrix for its last non-zero row.
Definition ilaslr.f:76
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
Here is the call graph for this function:
Here is the caller graph for this function: