Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

clarzb (3p)

Name

clarzb - apply a complex block reflector H or its transpose H**H to a complex distributed M-by-N C from the left or the right

Synopsis

SUBROUTINE CLARZB(SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV, T,
LDT, C, LDC, WORK, LDWORK)

CHARACTER*1 SIDE, TRANS, DIRECT, STOREV
COMPLEX V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
INTEGER M, N, K, L, LDV, LDT, LDC, LDWORK

SUBROUTINE CLARZB_64(SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV,
T, LDT, C, LDC, WORK, LDWORK)

CHARACTER*1 SIDE, TRANS, DIRECT, STOREV
COMPLEX V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
INTEGER*8 M, N, K, L, LDV, LDT, LDC, 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
COMPLEX, DIMENSION(:,:) :: V, T, C, WORK
INTEGER :: M, N, K, L, LDV, LDT, LDC, LDWORK

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
COMPLEX, DIMENSION(:,:) :: V, T, C, WORK
INTEGER(8) :: M, N, K, L, LDV, LDT, LDC, LDWORK




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           clarzb(3P)



NAME
       clarzb  -  apply a complex block reflector H or its transpose H**H to a
       complex distributed M-by-N C from the left or the right


SYNOPSIS
       SUBROUTINE CLARZB(SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV, T,
             LDT, C, LDC, WORK, LDWORK)

       CHARACTER*1 SIDE, TRANS, DIRECT, STOREV
       COMPLEX V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
       INTEGER M, N, K, L, LDV, LDT, LDC, LDWORK

       SUBROUTINE CLARZB_64(SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V, LDV,
             T, LDT, C, LDC, WORK, LDWORK)

       CHARACTER*1 SIDE, TRANS, DIRECT, STOREV
       COMPLEX V(LDV,*), T(LDT,*), C(LDC,*), WORK(LDWORK,*)
       INTEGER*8 M, N, K, L, LDV, LDT, LDC, 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
       COMPLEX, DIMENSION(:,:) :: V, T, C, WORK
       INTEGER :: M, N, K, L, LDV, LDT, LDC, LDWORK

       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
       COMPLEX, DIMENSION(:,:) :: V, T, C, WORK
       INTEGER(8) :: M, N, K, L, LDV, LDT, LDC, LDWORK




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       clarzb 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.


ARGUMENTS
       SIDE (input)
                 = 'L': apply H or H' from the Left
                 = 'R': apply H or H' from the Right


       TRANS (input)
                 = 'N': apply H (No transpose)
                 = 'C': apply H' (Conjugate transpose)


       DIRECT (input)
                 Indicates  how  H  is  formed  from  a  product of elementary
                 reflectors = 'F': H = H(1) H(2) . . . H(k) (Forward, not sup-
                 ported yet)
                 = 'B': H = H(k) . . . H(2) H(1) (Backward)


       STOREV (input)
                 Indicates how the vectors which define the elementary reflec-
                 tors are stored:
                 = 'C': Columnwise                        (not supported yet)
                 = 'R': Rowwise


       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 reflec-
                 tors whose product defines the block reflector).


       L (input) The number of columns of the matrix V containing the meaning-
                 ful part of the Householder reflectors.  If SIDE = 'L', M  >=
                 L >= 0, if SIDE = 'R', N >= L >= 0.


       V (input) COMPLEX  array  of dimension (LDV,NV).  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).

FURTHER DETAILS
       Based on contributions by
         A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA




                                  7 Nov 2015                        clarzb(3P)