LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine slarf ( character  SIDE,
integer  M,
integer  N,
real, dimension( * )  V,
integer  INCV,
real  TAU,
real, dimension( ldc, * )  C,
integer  LDC,
real, dimension( * )  WORK 
)

SLARF applies an elementary reflector to a general rectangular matrix.

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

Purpose:
 SLARF 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 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.
Date
September 2012

Definition at line 126 of file slarf.f.

126 *
127 * -- LAPACK auxiliary routine (version 3.4.2) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * September 2012
131 *
132 * .. Scalar Arguments ..
133  CHARACTER side
134  INTEGER incv, ldc, m, n
135  REAL tau
136 * ..
137 * .. Array Arguments ..
138  REAL c( ldc, * ), v( * ), work( * )
139 * ..
140 *
141 * =====================================================================
142 *
143 * .. Parameters ..
144  REAL one, zero
145  parameter ( one = 1.0e+0, zero = 0.0e+0 )
146 * ..
147 * .. Local Scalars ..
148  LOGICAL applyleft
149  INTEGER i, lastv, lastc
150 * ..
151 * .. External Subroutines ..
152  EXTERNAL sgemv, sger
153 * ..
154 * .. External Functions ..
155  LOGICAL lsame
156  INTEGER ilaslr, ilaslc
157  EXTERNAL lsame, ilaslr, ilaslc
158 * ..
159 * .. Executable Statements ..
160 *
161  applyleft = lsame( side, 'L' )
162  lastv = 0
163  lastc = 0
164  IF( tau.NE.zero ) THEN
165 ! Set up variables for scanning V. LASTV begins pointing to the end
166 ! of V.
167  IF( applyleft ) THEN
168  lastv = m
169  ELSE
170  lastv = n
171  END IF
172  IF( incv.GT.0 ) THEN
173  i = 1 + (lastv-1) * incv
174  ELSE
175  i = 1
176  END IF
177 ! Look for the last non-zero row in V.
178  DO WHILE( lastv.GT.0 .AND. v( i ).EQ.zero )
179  lastv = lastv - 1
180  i = i - incv
181  END DO
182  IF( applyleft ) THEN
183 ! Scan for the last non-zero column in C(1:lastv,:).
184  lastc = ilaslc(lastv, n, c, ldc)
185  ELSE
186 ! Scan for the last non-zero row in C(:,1:lastv).
187  lastc = ilaslr(m, lastv, c, ldc)
188  END IF
189  END IF
190 ! Note that lastc.eq.0 renders the BLAS operations null; no special
191 ! case is needed at this level.
192  IF( applyleft ) THEN
193 *
194 * Form H * C
195 *
196  IF( lastv.GT.0 ) THEN
197 *
198 * w(1:lastc,1) := C(1:lastv,1:lastc)**T * v(1:lastv,1)
199 *
200  CALL sgemv( 'Transpose', lastv, lastc, one, c, ldc, v, incv,
201  $ zero, work, 1 )
202 *
203 * C(1:lastv,1:lastc) := C(...) - v(1:lastv,1) * w(1:lastc,1)**T
204 *
205  CALL sger( lastv, lastc, -tau, v, incv, work, 1, c, ldc )
206  END IF
207  ELSE
208 *
209 * Form C * H
210 *
211  IF( lastv.GT.0 ) THEN
212 *
213 * w(1:lastc,1) := C(1:lastc,1:lastv) * v(1:lastv,1)
214 *
215  CALL sgemv( 'No transpose', lastc, lastv, one, c, ldc,
216  $ v, incv, zero, work, 1 )
217 *
218 * C(1:lastc,1:lastv) := C(...) - w(1:lastc,1) * v(1:lastv,1)**T
219 *
220  CALL sger( lastc, lastv, -tau, work, 1, v, incv, c, ldc )
221  END IF
222  END IF
223  RETURN
224 *
225 * End of SLARF
226 *
integer function ilaslr(M, N, A, LDA)
ILASLR scans a matrix for its last non-zero row.
Definition: ilaslr.f:80
subroutine sger(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
SGER
Definition: sger.f:132
integer function ilaslc(M, N, A, LDA)
ILASLC scans a matrix for its last non-zero column.
Definition: ilaslc.f:80
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: