LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dlarzb ( character  SIDE,
character  TRANS,
character  DIRECT,
character  STOREV,
integer  M,
integer  N,
integer  K,
integer  L,
double precision, dimension( ldv, * )  V,
integer  LDV,
double precision, dimension( ldt, * )  T,
integer  LDT,
double precision, dimension( ldc, * )  C,
integer  LDC,
double precision, dimension( ldwork, * )  WORK,
integer  LDWORK 
)

DLARZB applies a block reflector or its transpose to a general matrix.

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

Purpose:
 DLARZB applies a real block reflector H or its transpose H**T to
 a real distributed M-by-N  C from the left or the right.

 Currently, only STOREV = 'R' and DIRECT = 'B' are supported.
Parameters
[in]SIDE
          SIDE is CHARACTER*1
          = 'L': apply H or H**T from the Left
          = 'R': apply H or H**T from the Right
[in]TRANS
          TRANS is CHARACTER*1
          = 'N': apply H (No transpose)
          = 'C': apply H**T (Transpose)
[in]DIRECT
          DIRECT is CHARACTER*1
          Indicates how H is formed from a product of elementary
          reflectors
          = 'F': H = H(1) H(2) . . . H(k) (Forward, not supported yet)
          = 'B': H = H(k) . . . H(2) H(1) (Backward)
[in]STOREV
          STOREV is CHARACTER*1
          Indicates how the vectors which define the elementary
          reflectors are stored:
          = 'C': Columnwise                        (not supported yet)
          = 'R': Rowwise
[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]K
          K is INTEGER
          The order of the matrix T (= the number of elementary
          reflectors whose product defines the block reflector).
[in]L
          L is INTEGER
          The number of columns of the matrix V containing the
          meaningful part of the Householder reflectors.
          If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
[in]V
          V is DOUBLE PRECISION array, dimension (LDV,NV).
          If STOREV = 'C', NV = K; if STOREV = 'R', NV = L.
[in]LDV
          LDV is INTEGER
          The leading dimension of the array V.
          If STOREV = 'C', LDV >= L; if STOREV = 'R', LDV >= K.
[in]T
          T is DOUBLE PRECISION array, dimension (LDT,K)
          The triangular K-by-K matrix T in the representation of the
          block reflector.
[in]LDT
          LDT is INTEGER
          The leading dimension of the array T. LDT >= K.
[in,out]C
          C is DOUBLE PRECISION array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by H*C or H**T*C or C*H or C*H**T.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (LDWORK,K)
[in]LDWORK
          LDWORK is INTEGER
          The leading dimension of the array WORK.
          If SIDE = 'L', LDWORK >= max(1,N);
          if SIDE = 'R', LDWORK >= max(1,M).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012
Contributors:
A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
Further Details:
 

Definition at line 185 of file dlarzb.f.

185 *
186 * -- LAPACK computational routine (version 3.4.2) --
187 * -- LAPACK is a software package provided by Univ. of Tennessee, --
188 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
189 * September 2012
190 *
191 * .. Scalar Arguments ..
192  CHARACTER direct, side, storev, trans
193  INTEGER k, l, ldc, ldt, ldv, ldwork, m, n
194 * ..
195 * .. Array Arguments ..
196  DOUBLE PRECISION c( ldc, * ), t( ldt, * ), v( ldv, * ),
197  $ work( ldwork, * )
198 * ..
199 *
200 * =====================================================================
201 *
202 * .. Parameters ..
203  DOUBLE PRECISION one
204  parameter ( one = 1.0d+0 )
205 * ..
206 * .. Local Scalars ..
207  CHARACTER transt
208  INTEGER i, info, j
209 * ..
210 * .. External Functions ..
211  LOGICAL lsame
212  EXTERNAL lsame
213 * ..
214 * .. External Subroutines ..
215  EXTERNAL dcopy, dgemm, dtrmm, xerbla
216 * ..
217 * .. Executable Statements ..
218 *
219 * Quick return if possible
220 *
221  IF( m.LE.0 .OR. n.LE.0 )
222  $ RETURN
223 *
224 * Check for currently supported options
225 *
226  info = 0
227  IF( .NOT.lsame( direct, 'B' ) ) THEN
228  info = -3
229  ELSE IF( .NOT.lsame( storev, 'R' ) ) THEN
230  info = -4
231  END IF
232  IF( info.NE.0 ) THEN
233  CALL xerbla( 'DLARZB', -info )
234  RETURN
235  END IF
236 *
237  IF( lsame( trans, 'N' ) ) THEN
238  transt = 'T'
239  ELSE
240  transt = 'N'
241  END IF
242 *
243  IF( lsame( side, 'L' ) ) THEN
244 *
245 * Form H * C or H**T * C
246 *
247 * W( 1:n, 1:k ) = C( 1:k, 1:n )**T
248 *
249  DO 10 j = 1, k
250  CALL dcopy( n, c( j, 1 ), ldc, work( 1, j ), 1 )
251  10 CONTINUE
252 *
253 * W( 1:n, 1:k ) = W( 1:n, 1:k ) + ...
254 * C( m-l+1:m, 1:n )**T * V( 1:k, 1:l )**T
255 *
256  IF( l.GT.0 )
257  $ CALL dgemm( 'Transpose', 'Transpose', n, k, l, one,
258  $ c( m-l+1, 1 ), ldc, v, ldv, one, work, ldwork )
259 *
260 * W( 1:n, 1:k ) = W( 1:n, 1:k ) * T**T or W( 1:m, 1:k ) * T
261 *
262  CALL dtrmm( 'Right', 'Lower', transt, 'Non-unit', n, k, one, t,
263  $ ldt, work, ldwork )
264 *
265 * C( 1:k, 1:n ) = C( 1:k, 1:n ) - W( 1:n, 1:k )**T
266 *
267  DO 30 j = 1, n
268  DO 20 i = 1, k
269  c( i, j ) = c( i, j ) - work( j, i )
270  20 CONTINUE
271  30 CONTINUE
272 *
273 * C( m-l+1:m, 1:n ) = C( m-l+1:m, 1:n ) - ...
274 * V( 1:k, 1:l )**T * W( 1:n, 1:k )**T
275 *
276  IF( l.GT.0 )
277  $ CALL dgemm( 'Transpose', 'Transpose', l, n, k, -one, v, ldv,
278  $ work, ldwork, one, c( m-l+1, 1 ), ldc )
279 *
280  ELSE IF( lsame( side, 'R' ) ) THEN
281 *
282 * Form C * H or C * H**T
283 *
284 * W( 1:m, 1:k ) = C( 1:m, 1:k )
285 *
286  DO 40 j = 1, k
287  CALL dcopy( m, c( 1, j ), 1, work( 1, j ), 1 )
288  40 CONTINUE
289 *
290 * W( 1:m, 1:k ) = W( 1:m, 1:k ) + ...
291 * C( 1:m, n-l+1:n ) * V( 1:k, 1:l )**T
292 *
293  IF( l.GT.0 )
294  $ CALL dgemm( 'No transpose', 'Transpose', m, k, l, one,
295  $ c( 1, n-l+1 ), ldc, v, ldv, one, work, ldwork )
296 *
297 * W( 1:m, 1:k ) = W( 1:m, 1:k ) * T or W( 1:m, 1:k ) * T**T
298 *
299  CALL dtrmm( 'Right', 'Lower', trans, 'Non-unit', m, k, one, t,
300  $ ldt, work, ldwork )
301 *
302 * C( 1:m, 1:k ) = C( 1:m, 1:k ) - W( 1:m, 1:k )
303 *
304  DO 60 j = 1, k
305  DO 50 i = 1, m
306  c( i, j ) = c( i, j ) - work( i, j )
307  50 CONTINUE
308  60 CONTINUE
309 *
310 * C( 1:m, n-l+1:n ) = C( 1:m, n-l+1:n ) - ...
311 * W( 1:m, 1:k ) * V( 1:k, 1:l )
312 *
313  IF( l.GT.0 )
314  $ CALL dgemm( 'No transpose', 'No transpose', m, l, k, -one,
315  $ work, ldwork, v, ldv, one, c( 1, n-l+1 ), ldc )
316 *
317  END IF
318 *
319  RETURN
320 *
321 * End of DLARZB
322 *
subroutine dcopy(N, DX, INCX, DY, INCY)
DCOPY
Definition: dcopy.f:53
subroutine dtrmm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
DTRMM
Definition: dtrmm.f:179
subroutine dgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
DGEMM
Definition: dgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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: