LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slarf1f.f
Go to the documentation of this file.
1*> \brief \b SLARF1F 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 SLARF1F + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarf1f.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarf1f.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarf1f.f">
15*> [TXT]</a>
16*
17* Definition:
18* ===========
19*
20* SUBROUTINE SLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
21*
22* .. Scalar Arguments ..
23* CHARACTER SIDE
24* INTEGER INCV, LDC, M, N
25* REAL TAU
26* ..
27* .. Array Arguments ..
28* REAL C( LDC, * ), V( * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> SLARF1F applies a real 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**T
41*>
42*> where tau is a real scalar and v is a real vector assuming v(1) = 1.
43*>
44*> If tau = 0, then H is taken to be the unit matrix.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] SIDE
51*> \verbatim
52*> SIDE is CHARACTER*1
53*> = 'L': form H * C
54*> = 'R': form C * H
55*> \endverbatim
56*>
57*> \param[in] M
58*> \verbatim
59*> M is INTEGER
60*> The number of rows of the matrix C.
61*> \endverbatim
62*>
63*> \param[in] N
64*> \verbatim
65*> N is INTEGER
66*> The number of columns of the matrix C.
67*> \endverbatim
68*>
69*> \param[in] V
70*> \verbatim
71*> V is REAL array, dimension
72*> (1 + (M-1)*abs(INCV)) if SIDE = 'L'
73*> or (1 + (N-1)*abs(INCV)) if SIDE = 'R'
74*> The vector v in the representation of H. V is not used if
75*> TAU = 0.
76*> \endverbatim
77*>
78*> \param[in] INCV
79*> \verbatim
80*> INCV is INTEGER
81*> The increment between elements of v. INCV <> 0.
82*> \endverbatim
83*>
84*> \param[in] TAU
85*> \verbatim
86*> TAU is REAL
87*> The value tau in the representation of H.
88*> \endverbatim
89*>
90*> \param[in,out] C
91*> \verbatim
92*> C is REAL array, dimension (LDC,N)
93*> On entry, the m by n matrix C.
94*> On exit, C is overwritten by the matrix H * C if SIDE = 'L',
95*> or C * H if SIDE = 'R'.
96*> \endverbatim
97*>
98*> \param[in] LDC
99*> \verbatim
100*> LDC is INTEGER
101*> The leading dimension of the array C. LDC >= max(1,M).
102*> \endverbatim
103*>
104*> \param[out] WORK
105*> \verbatim
106*> WORK is REAL array, dimension
107*> (N) if SIDE = 'L'
108*> or (M) if SIDE = 'R'
109*> \endverbatim
110*
111* Authors:
112* ========
113*
114*> \author Univ. of Tennessee
115*> \author Univ. of California Berkeley
116*> \author Univ. of Colorado Denver
117*> \author NAG Ltd.
118*
119*> \ingroup larf1f
120*
121* =====================================================================
122 SUBROUTINE slarf1f( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
123*
124* -- LAPACK auxiliary routine --
125* -- LAPACK is a software package provided by Univ. of Tennessee, --
126* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
127*
128* .. Scalar Arguments ..
129 CHARACTER SIDE
130 INTEGER INCV, LDC, M, N
131 REAL TAU
132* ..
133* .. Array Arguments ..
134 REAL C( LDC, * ), V( * ), WORK( * )
135* ..
136*
137* =====================================================================
138*
139* .. Parameters ..
140 REAL ONE, ZERO
141 parameter( one = 1.0e+0, zero = 0.0e+0 )
142* ..
143* .. Local Scalars ..
144 LOGICAL APPLYLEFT
145 INTEGER I, LASTV, LASTC
146* ..
147* .. External Subroutines ..
148 EXTERNAL sgemv, sger, saxpy, sscal
149* ..
150* .. External Functions ..
151 LOGICAL LSAME
152 INTEGER ILASLR, ILASLC
153 EXTERNAL lsame, ilaslr, ilaslc
154* ..
155* .. Executable Statements ..
156*
157 applyleft = lsame( side, 'L' )
158 lastv = 1
159 lastc = 0
160 IF( tau.NE.zero ) THEN
161! Set up variables for scanning V. LASTV begins pointing to the end
162! of V up to V(1).
163 IF( applyleft ) THEN
164 lastv = m
165 ELSE
166 lastv = n
167 END IF
168 IF( incv.GT.0 ) THEN
169 i = 1 + (lastv-1) * incv
170 ELSE
171 i = 1
172 END IF
173! Look for the last non-zero row in V.
174 DO WHILE( lastv.GT.1 .AND. v( i ).EQ.zero )
175 lastv = lastv - 1
176 i = i - incv
177 END DO
178 IF( applyleft ) THEN
179! Scan for the last non-zero column in C(1:lastv,:).
180 lastc = ilaslc(lastv, n, c, ldc)
181 ELSE
182! Scan for the last non-zero row in C(:,1:lastv).
183 lastc = ilaslr(m, lastv, c, ldc)
184 END IF
185 END IF
186 IF( lastc.EQ.0 ) THEN
187 RETURN
188 END IF
189 IF( applyleft ) THEN
190*
191* Form H * C
192*
193 IF( lastv.EQ.1 ) THEN
194*
195* C(1,1:lastc) := ( 1 - tau ) * C(1,1:lastc)
196*
197 CALL sscal( lastc, one - tau, c, ldc )
198 ELSE
199*
200* w(1:lastc,1) := C(2:lastv,1:lastc)**T * v(2:lastv,1)
201*
202 CALL sgemv( 'Transpose', lastv - 1, lastc, one, c( 2, 1 ),
203 $ ldc, v( 1 + incv ), incv, zero, work, 1 )
204*
205* w(1:lastc,1) += v(1,1) * C(1,1:lastc)**T
206*
207 CALL saxpy( lastc, one, c, ldc, work, 1 )
208*
209* C(1, 1:lastc) += - tau * v(1,1) * w(1:lastc,1)**T
210*
211 CALL saxpy( lastc, -tau, work, 1, c, ldc )
212*
213* C(2:lastv,1:lastc) += - tau * v(2:lastv,1) * w(1:lastc,1)**T
214*
215 CALL sger( lastv - 1, lastc, -tau, v( 1 + incv ), incv,
216 $ work, 1, c( 2, 1 ), ldc )
217 END IF
218 ELSE
219*
220* Form C * H
221*
222 IF( lastv.EQ.1 ) THEN
223*
224* C(1:lastc,1) := ( 1 - tau ) * C(1:lastc,1)
225*
226 CALL sscal( lastc, one - tau, c, 1 )
227 ELSE
228*
229* w(1:lastc,1) := C(1:lastc,2:lastv) * v(2:lastv,1)
230*
231 CALL sgemv( 'No transpose', lastc, lastv - 1, one,
232 $ c( 1, 2 ), ldc, v( 1 + incv ), incv, zero,
233 $ work, 1 )
234*
235* w(1:lastc,1) += v(1,1) * C(1:lastc,1)
236*
237 CALL saxpy( lastc, one, c, 1, work, 1 )
238*
239* C(1:lastc,1) += - tau * v(1,1) * w(1:lastc,1)
240*
241 CALL saxpy( lastc, -tau, work, 1, c, 1 )
242*
243* C(1:lastc,2:lastv) += - tau * w(1:lastc,1) * v(2:lastv)**T
244*
245 CALL sger( lastc, lastv - 1, -tau, work, 1,
246 $ v( 1 + incv ), incv, c( 1, 2 ), ldc )
247 END IF
248 END IF
249 RETURN
250*
251* End of SLARF1F
252*
253 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 slarf1f(side, m, n, v, incv, tau, c, ldc, work)
SLARF1F applies an elementary reflector to a general rectangular
Definition slarf1f.f:123