Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sormbr (3p)

Name

sormbr - N matrix C with Q*C or Q**T*C or C*Q**T or C*Q or P*C or P**T*C or C*P or C*P**T.

Synopsis

SUBROUTINE SORMBR(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
WORK, LWORK, INFO)

CHARACTER*1 VECT, SIDE, TRANS
INTEGER M, N, K, LDA, LDC, LWORK, INFO
REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)

SUBROUTINE SORMBR_64(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
WORK, LWORK, INFO)

CHARACTER*1 VECT, SIDE, TRANS
INTEGER*8 M, N, K, LDA, LDC, LWORK, INFO
REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)




F95 INTERFACE
SUBROUTINE ORMBR(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
LDC, WORK, LWORK, INFO)

CHARACTER(LEN=1) :: VECT, SIDE, TRANS
INTEGER :: M, N, K, LDA, LDC, LWORK, INFO
REAL, DIMENSION(:) :: TAU, WORK
REAL, DIMENSION(:,:) :: A, C

SUBROUTINE ORMBR_64(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU,
C, LDC, WORK, LWORK, INFO)

CHARACTER(LEN=1) :: VECT, SIDE, TRANS
INTEGER(8) :: M, N, K, LDA, LDC, LWORK, INFO
REAL, DIMENSION(:) :: TAU, WORK
REAL, DIMENSION(:,:) :: A, C




C INTERFACE
#include <sunperf.h>

void sormbr(char vect, char side, char trans, int  m,  int  n,  int  k,
float *a, int lda, float *tau, float *c, int ldc, int *info);

void sormbr_64(char vect, char side, char trans, long m, long  n,  long
k,  float  *a, long lda, float *tau, float *c, long ldc, long
*info);

Description

Oracle Solaris Studio Performance Library                           sormbr(3P)



NAME
       sormbr - overwrites the general real M-by-N matrix C with Q*C or Q**T*C
       or C*Q**T or C*Q or P*C or P**T*C or C*P or C*P**T.


SYNOPSIS
       SUBROUTINE SORMBR(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
             WORK, LWORK, INFO)

       CHARACTER*1 VECT, SIDE, TRANS
       INTEGER M, N, K, LDA, LDC, LWORK, INFO
       REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)

       SUBROUTINE SORMBR_64(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
             WORK, LWORK, INFO)

       CHARACTER*1 VECT, SIDE, TRANS
       INTEGER*8 M, N, K, LDA, LDC, LWORK, INFO
       REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)




   F95 INTERFACE
       SUBROUTINE ORMBR(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
              LDC, WORK, LWORK, INFO)

       CHARACTER(LEN=1) :: VECT, SIDE, TRANS
       INTEGER :: M, N, K, LDA, LDC, LWORK, INFO
       REAL, DIMENSION(:) :: TAU, WORK
       REAL, DIMENSION(:,:) :: A, C

       SUBROUTINE ORMBR_64(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU,
              C, LDC, WORK, LWORK, INFO)

       CHARACTER(LEN=1) :: VECT, SIDE, TRANS
       INTEGER(8) :: M, N, K, LDA, LDC, LWORK, INFO
       REAL, DIMENSION(:) :: TAU, WORK
       REAL, DIMENSION(:,:) :: A, C




   C INTERFACE
       #include <sunperf.h>

       void sormbr(char vect, char side, char trans, int  m,  int  n,  int  k,
                 float *a, int lda, float *tau, float *c, int ldc, int *info);

       void sormbr_64(char vect, char side, char trans, long m, long  n,  long
                 k,  float  *a, long lda, float *tau, float *c, long ldc, long
                 *info);



PURPOSE
       If VECT = 'Q', SORMBR overwrites the general real M-by-N matrix C with

                       SIDE = 'L'     SIDE = 'R'
       TRANS = 'N':      Q * C          C * Q
       TRANS = 'T':      Q**T * C       C * Q**T

       If VECT = 'P', SORMBR overwrites the general real M-by-N matrix C with

                       SIDE = 'L'     SIDE = 'R'
       TRANS = 'N':      P * C          C * P
       TRANS = 'T':      P**T * C       C * P**T

       Here Q and P**T are the orthogonal matrices determined by  SGEBRD  when
       reducing  a  real  matrix A to bidiagonal form: A = Q * B * P**T. Q and
       P**T are defined as products of elementary  reflectors  H(i)  and  G(i)
       respectively.

       Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the order
       of the orthogonal matrix Q or P**T that is applied.

       If VECT = 'Q', A is assumed to have been an NQ-by-K matrix: if nq >= k,
       Q = H(1) H(2) . . . H(k);
       if nq < k, Q = H(1) H(2) . . . H(nq-1).

       If VECT = 'P', A is assumed to have been a K-by-NQ matrix: if k < nq, P
       = G(1) G(2) . . . G(k);
       if k >= nq, P = G(1) G(2) . . . G(nq-1).


ARGUMENTS
       VECT (input)
                 = 'Q': apply Q or Q**T;
                 = 'P': apply P or P**T.


       SIDE (input)
                 = 'L': apply Q, Q**T, P or P**T from the Left;
                 = 'R': apply Q, Q**T, P or P**T from the Right.


       TRANS (input)
                 = 'N':  No transpose, apply Q  or P;
                 = 'T':  Transpose, apply Q**T or P**T.


       M (input) The number of rows of the matrix C. M >= 0.


       N (input) The number of columns of the matrix C. N >= 0.


       K (input) If VECT = 'Q', the number of columns in the  original  matrix
                 reduced  by SGEBRD.  If VECT = 'P', the number of rows in the
                 original matrix reduced by SGEBRD.  K >= 0.


       A (input) (LDA,min(nq,K)) if VECT = 'Q' (LDA,nq)        if VECT  =  'P'
                 The  vectors  which define the elementary reflectors H(i) and
                 G(i), whose products determine  the  matrices  Q  and  P,  as
                 returned by SGEBRD.


       LDA (input)
                 The  leading dimension of the array A.  If VECT = 'Q', LDA >=
                 max(1,nq); if VECT = 'P', LDA >= max(1,min(nq,K)).


       TAU (input)
                 TAU(i) must contain  the  scalar  factor  of  the  elementary
                 reflector  H(i)  or G(i) which determines Q or P, as returned
                 by SGEBRD in the array argument TAUQ or TAUP.


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


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


       WORK (workspace)
                 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.


       LWORK (input)
                 The dimension of the array WORK.  If SIDE  =  'L',  LWORK  >=
                 max(1,N); if SIDE = 'R', LWORK >= max(1,M).  For optimum per-
                 formance LWORK >= N*NB if SIDE = 'L', and LWORK  >=  M*NB  if
                 SIDE = 'R', where NB is the optimal blocksize.

                 If LWORK = -1, then a workspace query is assumed; the routine
                 only calculates the optimal size of the WORK  array,  returns
                 this value as the first entry of the WORK array, and no error
                 message related to LWORK is issued by XERBLA.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value




                                  7 Nov 2015                        sormbr(3P)