Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlarzt (3p)

Name

dlarzt - form the triangular factor T of a real block reflector H of order > n, which is defined as a product of k elementary reflectors

Synopsis

SUBROUTINE DLARZT(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

CHARACTER*1 DIRECT, STOREV
INTEGER N, K, LDV, LDT
DOUBLE PRECISION V(LDV,*), TAU(*), T(LDT,*)

SUBROUTINE DLARZT_64(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

CHARACTER*1 DIRECT, STOREV
INTEGER*8 N, K, LDV, LDT
DOUBLE PRECISION V(LDV,*), TAU(*), T(LDT,*)




F95 INTERFACE
SUBROUTINE LARZT(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

CHARACTER(LEN=1) :: DIRECT, STOREV
INTEGER :: N, K, LDV, LDT
REAL(8), DIMENSION(:) :: TAU
REAL(8), DIMENSION(:,:) :: V, T

SUBROUTINE LARZT_64(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

CHARACTER(LEN=1) :: DIRECT, STOREV
INTEGER(8) :: N, K, LDV, LDT
REAL(8), DIMENSION(:) :: TAU
REAL(8), DIMENSION(:,:) :: V, T




C INTERFACE
#include <sunperf.h>

void dlarzt(char direct, char storev, int n, int k, double *v, int ldv,
double *tau, double *t, int ldt);

void  dlarzt_64(char  direct,  char  storev, long n, long k, double *v,
long ldv, double *tau, double *t, long ldt);

Description

Oracle Solaris Studio Performance Library                           dlarzt(3P)



NAME
       dlarzt  -  form  the triangular factor T of a real block reflector H of
       order > n, which is defined as a product of k elementary reflectors


SYNOPSIS
       SUBROUTINE DLARZT(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

       CHARACTER*1 DIRECT, STOREV
       INTEGER N, K, LDV, LDT
       DOUBLE PRECISION V(LDV,*), TAU(*), T(LDT,*)

       SUBROUTINE DLARZT_64(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

       CHARACTER*1 DIRECT, STOREV
       INTEGER*8 N, K, LDV, LDT
       DOUBLE PRECISION V(LDV,*), TAU(*), T(LDT,*)




   F95 INTERFACE
       SUBROUTINE LARZT(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

       CHARACTER(LEN=1) :: DIRECT, STOREV
       INTEGER :: N, K, LDV, LDT
       REAL(8), DIMENSION(:) :: TAU
       REAL(8), DIMENSION(:,:) :: V, T

       SUBROUTINE LARZT_64(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)

       CHARACTER(LEN=1) :: DIRECT, STOREV
       INTEGER(8) :: N, K, LDV, LDT
       REAL(8), DIMENSION(:) :: TAU
       REAL(8), DIMENSION(:,:) :: V, T




   C INTERFACE
       #include <sunperf.h>

       void dlarzt(char direct, char storev, int n, int k, double *v, int ldv,
                 double *tau, double *t, int ldt);

       void  dlarzt_64(char  direct,  char  storev, long n, long k, double *v,
                 long ldv, double *tau, double *t, long ldt);



PURPOSE
       dlarzt forms the triangular factor T of a real  block  reflector  H  of
       order > n, which is defined as a product of k elementary reflectors.

       If DIRECT = 'F', H = H(1) H(2) . . . H(k) and T is upper triangular;

       If DIRECT = 'B', H = H(k) . . . H(2) H(1) and T is lower triangular.

       If STOREV = 'C', the vector which defines the elementary reflector H(i)
       is stored in the i-th column of the array V, and

          H  =  I - V * T * V'

       If STOREV = 'R', the vector which defines the elementary reflector H(i)
       is stored in the i-th row of the array V, and

          H  =  I - V' * T * V

       Currently, only STOREV = 'R' and DIRECT = 'B' are supported.


ARGUMENTS
       DIRECT (input)
                 Specifies  the  order  in which the elementary reflectors are
                 multiplied to form the block reflector:
                 = 'F': H = H(1) H(2) . . . H(k) (Forward, not supported yet)
                 = 'B': H = H(k) . . . H(2) H(1) (Backward)


       STOREV (input)
                 Specifies how the vectors which define the elementary reflec-
                 tors are stored (see also Further Details):
                 = 'R': rowwise


       N (input) The order of the block reflector H. N >= 0.


       K (input) The order of the triangular factor T (= the number of elemen-
                 tary reflectors). K >= 1.


       V (input) (LDV,K) if STOREV = 'C' (LDV,N) if STOREV = 'R' The matrix V.
                 See further details.


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


       TAU (input)
                 Dimension (K) TAU(i) must contain the scalar  factor  of  the
                 elementary reflector H(i).


       T (output)
                 The  k  by  k triangular factor T of the block reflector.  If
                 DIRECT = 'F', T is upper triangular; if DIRECT =  'B',  T  is
                 lower triangular. The rest of the array is not used.


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

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

       The  shape  of the matrix V and the storage of the vectors which define
       the H(i) is best illustrated by the following example with n = 5 and  k
       =  3.  The  elements equal to 1 are not stored; the corresponding array
       elements are modified but restored on exit. The rest of  the  array  is
       not used.

       DIRECT = 'F' and STOREV = 'C':         DIRECT = 'F' and STOREV = 'R':

                                                   ______V_____
              (  v1 v2 v3 )                        /                   ( v1 v2
       v3 )                      ( v1 v1 v1 v1 v1 . . . . 1 )
          V = ( v1 v2 v3 )                      ( v2 v2 v2 v2 v2 . . . 1   )
              ( v1 v2 v3 )                      ( v3 v3 v3 v3 v3 . . 1     )
              ( v1 v2 v3 )
                 .  .  .
                 .  .  .
                 1  .  .
                    1  .
                       1

       DIRECT = 'B' and STOREV = 'C':         DIRECT = 'B' and STOREV = 'R':

                                                             ______V_____
                 1                                                           /
       .  1                           ( 1 . . . . v1 v1 v1 v1 v1 )
                 .  .  1                        ( . 1 . . . v2 v2 v2 v2 v2 )
                 .  .  .                        ( . . 1 . . v3 v3 v3 v3 v3 )
                 .  .  .
              ( v1 v2 v3 )
              ( v1 v2 v3 )
          V = ( v1 v2 v3 )
              ( v1 v2 v3 )
              ( v1 v2 v3 )




                                  7 Nov 2015                        dlarzt(3P)