LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slarf1l.f
Go to the documentation of this file.
1*> \brief \b SLARF1L applies an elementary reflector to a general rectangular
2* matrix assuming v(lastv) = 1, where lastv is the last non-zero
3* element
4*
5* =========== DOCUMENTATION ===========
6*
7* Online html documentation available at
8* http://www.netlib.org/lapack/explore-html/
9*
10*> Download SLARF1L + dependencies
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarf1l.f">
12*> [TGZ]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarf1l.f">
14*> [ZIP]</a>
15*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarf1l.f">
16*> [TXT]</a>
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SLARF1L( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
22*
23* .. Scalar Arguments ..
24* CHARACTER SIDE
25* INTEGER INCV, LDC, M, N
26* REAL TAU
27* ..
28* .. Array Arguments ..
29* REAL C( LDC, * ), V( * ), WORK( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> SLARF1L applies a real elementary reflector H to a real m by n matrix
39*> C, from either the left or the right. H is represented in the form
40*>
41*> H = I - tau * v * v**T
42*>
43*> where tau is a real scalar and v is a real vector assuming v(lastv) = 1,
44*> where lastv is the last non-zero element.
45*>
46*> If tau = 0, then H is taken to be the unit matrix.
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] SIDE
53*> \verbatim
54*> SIDE is CHARACTER*1
55*> = 'L': form H * C
56*> = 'R': form C * H
57*> \endverbatim
58*>
59*> \param[in] M
60*> \verbatim
61*> M is INTEGER
62*> The number of rows of the matrix C.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*> N is INTEGER
68*> The number of columns of the matrix C.
69*> \endverbatim
70*>
71*> \param[in] V
72*> \verbatim
73*> V is REAL array, dimension
74*> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
75*> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
76*> The vector v in the representation of H. V is not used if
77*> TAU = 0.
78*> \endverbatim
79*>
80*> \param[in] INCV
81*> \verbatim
82*> INCV is INTEGER
83*> The increment between elements of v. INCV > 0.
84*> \endverbatim
85*>
86*> \param[in] TAU
87*> \verbatim
88*> TAU is REAL
89*> The value tau in the representation of H.
90*> \endverbatim
91*>
92*> \param[in,out] C
93*> \verbatim
94*> C is REAL array, dimension (LDC,N)
95*> On entry, the m by n matrix C.
96*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
97*> or C * H if SIDE = 'R'.
98*> \endverbatim
99*>
100*> \param[in] LDC
101*> \verbatim
102*> LDC is INTEGER
103*> The leading dimension of the array C. LDC >= max(1,M).
104*> \endverbatim
105*>
106*> \param[out] WORK
107*> \verbatim
108*> WORK is REAL array, dimension
109*> (N) if SIDE = 'L'
110*> or (M) if SIDE = 'R'
111*> \endverbatim
112*
113* Authors:
114* ========
115*
116*> \author Univ. of Tennessee
117*> \author Univ. of California Berkeley
118*> \author Univ. of Colorado Denver
119*> \author NAG Ltd.
120*
121*> \ingroup larf1l
122*
123* =====================================================================
124 SUBROUTINE slarf1l( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
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*
252 END
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
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine slarf1l(side, m, n, v, incv, tau, c, ldc, work)
SLARF1L applies an elementary reflector to a general rectangular
Definition slarf1l.f:125