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

ZLARF applies an elementary reflector to a general rectangular matrix.

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

Purpose:
 ZLARF applies a complex elementary reflector H to a complex M-by-N
 matrix C, from either the left or the right. H is represented in the
 form

       H = I - tau * v * v**H

 where tau is a complex scalar and v is a complex vector.

 If tau = 0, then H is taken to be the unit matrix.

 To apply H**H, supply conjg(tau) instead
 tau.
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 COMPLEX*16 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 COMPLEX*16
          The value tau in the representation of H.
[in,out]C
          C is COMPLEX*16 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 COMPLEX*16 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 130 of file zlarf.f.

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