slarzb


NAME

slarzb - 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


SYNOPSIS

  SUBROUTINE SLARZB( SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV, 
 *      T, LDT, C, LDC, WORK, LDWORK)
  CHARACTER * 1 SIDE, TRANS, DIRECT, STOREV
  INTEGER M, N, K, L, LDV, LDT, LDC, LDWORK
  REAL V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
 
  SUBROUTINE SLARZB_64( SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, 
 *      LDV, T, LDT, C, LDC, WORK, LDWORK)
  CHARACTER * 1 SIDE, TRANS, DIRECT, STOREV
  INTEGER*8 M, N, K, L, LDV, LDT, LDC, LDWORK
  REAL V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
 

F95 INTERFACE

  SUBROUTINE LARZB( SIDE, TRANS, DIRECT, STOREV, [M], [N], K, L, V, 
 *       [LDV], T, [LDT], C, [LDC], [WORK], [LDWORK])
  CHARACTER(LEN=1) :: SIDE, TRANS, DIRECT, STOREV
  INTEGER :: M, N, K, L, LDV, LDT, LDC, LDWORK
  REAL, DIMENSION(:,:) :: V, T, C, WORK
 
  SUBROUTINE LARZB_64( SIDE, TRANS, DIRECT, STOREV, [M], [N], K, L, V, 
 *       [LDV], T, [LDT], C, [LDC], [WORK], [LDWORK])
  CHARACTER(LEN=1) :: SIDE, TRANS, DIRECT, STOREV
  INTEGER(8) :: M, N, K, L, LDV, LDT, LDC, LDWORK
  REAL, DIMENSION(:,:) :: V, T, C, WORK
 

C INTERFACE

#include <sunperf.h>

void slarzb(char side, char trans, char direct, char storev, int m, int n, int k, int l, float *v, int ldv, float *t, int ldt, float *c, int ldc, int ldwork);

void slarzb_64(char side, char trans, char direct, char storev, long m, long n, long k, long l, float *v, long ldv, float *t, long ldt, float *c, long ldc, long ldwork);


PURPOSE

slarzb 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.


ARGUMENTS

* SIDE (input)
* TRANS (input)

* DIRECT (input)
Indicates how H is formed from a product of elementary reflectors

* STOREV (input)
Indicates how the vectors which define the elementary reflectors are stored:

* M (input)
The number of rows of the matrix C.

* N (input)
The number of columns of the matrix C.

* K (input)
The order of the matrix T (= the number of elementary reflectors whose product defines the block reflector).

* L (input)
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.

* V (input)
If STOREV = 'C', NV = K; if STOREV = 'R', NV = L.

* LDV (input)
The leading dimension of the array V. If STOREV = 'C', LDV >= L; if STOREV = 'R', LDV >= K.

* T (input)
The triangular K-by-K matrix T in the representation of the block reflector.

* LDT (input)
The leading dimension of the array T. LDT >= K.

* C (input/output)
On entry, the M-by-N matrix C. On exit, C is overwritten by H*C or H'*C or C*H or C*H'.

* LDC (input)
The leading dimension of the array C. LDC >= max(1,M).

* WORK (workspace)
dimension(MAX(M,N),K)

* LDWORK (input)
The leading dimension of the array WORK. If SIDE = 'L', LDWORK >= max(1,N); if SIDE = 'R', LDWORK >= max(1,M). .SH FURTHER DETAILS Based on contributions by

  A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA