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

ZLARZB applies a block reflector or its conjugate-transpose to a general matrix.

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

Purpose:
 ZLARZB applies a complex block reflector H or its transpose H**H
 to a complex 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**H from the Left
          = 'R': apply H or H**H from the Right
[in]TRANS
          TRANS is CHARACTER*1
          = 'N': apply H (No transpose)
          = 'C': apply H**H (Conjugate 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by H*C or H**H*C or C*H or C*H**H.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is COMPLEX*16 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 zlarzb.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  COMPLEX*16 c( ldc, * ), t( ldt, * ), v( ldv, * ),
197  $ work( ldwork, * )
198 * ..
199 *
200 * =====================================================================
201 *
202 * .. Parameters ..
203  COMPLEX*16 one
204  parameter ( one = ( 1.0d+0, 0.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 xerbla, zcopy, zgemm, zlacgv, ztrmm
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( 'ZLARZB', -info )
234  RETURN
235  END IF
236 *
237  IF( lsame( trans, 'N' ) ) THEN
238  transt = 'C'
239  ELSE
240  transt = 'N'
241  END IF
242 *
243  IF( lsame( side, 'L' ) ) THEN
244 *
245 * Form H * C or H**H * C
246 *
247 * W( 1:n, 1:k ) = C( 1:k, 1:n )**H
248 *
249  DO 10 j = 1, k
250  CALL zcopy( 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 )**H * V( 1:k, 1:l )**T
255 *
256  IF( l.GT.0 )
257  $ CALL zgemm( 'Transpose', 'Conjugate transpose', n, k, l,
258  $ one, c( m-l+1, 1 ), ldc, v, ldv, one, work,
259  $ ldwork )
260 *
261 * W( 1:n, 1:k ) = W( 1:n, 1:k ) * T**T or W( 1:m, 1:k ) * T
262 *
263  CALL ztrmm( 'Right', 'Lower', transt, 'Non-unit', n, k, one, t,
264  $ ldt, work, ldwork )
265 *
266 * C( 1:k, 1:n ) = C( 1:k, 1:n ) - W( 1:n, 1:k )**H
267 *
268  DO 30 j = 1, n
269  DO 20 i = 1, k
270  c( i, j ) = c( i, j ) - work( j, i )
271  20 CONTINUE
272  30 CONTINUE
273 *
274 * C( m-l+1:m, 1:n ) = C( m-l+1:m, 1:n ) - ...
275 * V( 1:k, 1:l )**H * W( 1:n, 1:k )**H
276 *
277  IF( l.GT.0 )
278  $ CALL zgemm( 'Transpose', 'Transpose', l, n, k, -one, v, ldv,
279  $ work, ldwork, one, c( m-l+1, 1 ), ldc )
280 *
281  ELSE IF( lsame( side, 'R' ) ) THEN
282 *
283 * Form C * H or C * H**H
284 *
285 * W( 1:m, 1:k ) = C( 1:m, 1:k )
286 *
287  DO 40 j = 1, k
288  CALL zcopy( m, c( 1, j ), 1, work( 1, j ), 1 )
289  40 CONTINUE
290 *
291 * W( 1:m, 1:k ) = W( 1:m, 1:k ) + ...
292 * C( 1:m, n-l+1:n ) * V( 1:k, 1:l )**H
293 *
294  IF( l.GT.0 )
295  $ CALL zgemm( 'No transpose', 'Transpose', m, k, l, one,
296  $ c( 1, n-l+1 ), ldc, v, ldv, one, work, ldwork )
297 *
298 * W( 1:m, 1:k ) = W( 1:m, 1:k ) * conjg( T ) or
299 * W( 1:m, 1:k ) * T**H
300 *
301  DO 50 j = 1, k
302  CALL zlacgv( k-j+1, t( j, j ), 1 )
303  50 CONTINUE
304  CALL ztrmm( 'Right', 'Lower', trans, 'Non-unit', m, k, one, t,
305  $ ldt, work, ldwork )
306  DO 60 j = 1, k
307  CALL zlacgv( k-j+1, t( j, j ), 1 )
308  60 CONTINUE
309 *
310 * C( 1:m, 1:k ) = C( 1:m, 1:k ) - W( 1:m, 1:k )
311 *
312  DO 80 j = 1, k
313  DO 70 i = 1, m
314  c( i, j ) = c( i, j ) - work( i, j )
315  70 CONTINUE
316  80 CONTINUE
317 *
318 * C( 1:m, n-l+1:n ) = C( 1:m, n-l+1:n ) - ...
319 * W( 1:m, 1:k ) * conjg( V( 1:k, 1:l ) )
320 *
321  DO 90 j = 1, l
322  CALL zlacgv( k, v( 1, j ), 1 )
323  90 CONTINUE
324  IF( l.GT.0 )
325  $ CALL zgemm( 'No transpose', 'No transpose', m, l, k, -one,
326  $ work, ldwork, v, ldv, one, c( 1, n-l+1 ), ldc )
327  DO 100 j = 1, l
328  CALL zlacgv( k, v( 1, j ), 1 )
329  100 CONTINUE
330 *
331  END IF
332 *
333  RETURN
334 *
335 * End of ZLARZB
336 *
subroutine zcopy(N, ZX, INCX, ZY, INCY)
ZCOPY
Definition: zcopy.f:52
subroutine zgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
ZGEMM
Definition: zgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ztrmm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
ZTRMM
Definition: ztrmm.f:179
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zlacgv(N, X, INCX)
ZLACGV conjugates a complex vector.
Definition: zlacgv.f:76

Here is the call graph for this function:

Here is the caller graph for this function: