Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sorgbr (3p)

Name

sorgbr - mined by SGEBRD when reducing a real matrix A to bidiagonal form

Synopsis

SUBROUTINE SORGBR(VECT, M, N, K, A, LDA, TAU, WORK, LWORK, INFO)

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

SUBROUTINE SORGBR_64(VECT, M, N, K, A, LDA, TAU, WORK, LWORK, INFO)

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




F95 INTERFACE
SUBROUTINE ORGBR(VECT, M, N, K, A, LDA, TAU, WORK, LWORK,
INFO)

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

SUBROUTINE ORGBR_64(VECT, M, N, K, A, LDA, TAU, WORK, LWORK,
INFO)

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




C INTERFACE
#include <sunperf.h>

void sorgbr(char vect, int m, int n, int k, float *a,  int  lda,  float
*tau, int *info);

void  sorgbr_64(char  vect, long m, long n, long k, float *a, long lda,
float *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           sorgbr(3P)



NAME
       sorgbr  - generate one of the real orthogonal matrices Q or P**T deter-
       mined by SGEBRD when reducing a real matrix A to bidiagonal form


SYNOPSIS
       SUBROUTINE SORGBR(VECT, M, N, K, A, LDA, TAU, WORK, LWORK, INFO)

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

       SUBROUTINE SORGBR_64(VECT, M, N, K, A, LDA, TAU, WORK, LWORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE ORGBR(VECT, M, N, K, A, LDA, TAU, WORK, LWORK,
              INFO)

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

       SUBROUTINE ORGBR_64(VECT, M, N, K, A, LDA, TAU, WORK, LWORK,
              INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void sorgbr(char vect, int m, int n, int k, float *a,  int  lda,  float
                 *tau, int *info);

       void  sorgbr_64(char  vect, long m, long n, long k, float *a, long lda,
                 float *tau, long *info);



PURPOSE
       sorgbr generates one of the real orthogonal matrices Q or  P**T  deter-
       mined 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  reflec-
       tors H(i) or G(i) respectively.

       If  VECT = 'Q', A is assumed to have been an M-by-K matrix, and Q is of
       order M:
       if m >= k, Q = H(1) H(2) . . . H(k) and SORGBR returns the first n col-
       umns of Q, where m >= n >= k;
       if  m < k, Q = H(1) H(2) . . . H(m-1) and SORGBR returns Q as an M-by-M
       matrix.

       If VECT = 'P', A is assumed to have been a K-by-N matrix, and  P**T  is
       of order N:
       if  k  <  n, P**T = G(k) . . . G(2) G(1) and SORGBR returns the first m
       rows of P**T, where n >= m >= k;
       if k >= n, P**T = G(n-1) . . . G(2) G(1) and SORGBR returns P**T as  an
       N-by-N matrix.


ARGUMENTS
       VECT (input)
                 Specifies  whether  the  matrix  Q  or  the  matrix  P**T  is
                 required, as defined in the transformation applied by SGEBRD:
                 = 'Q':  generate Q;
                 = 'P':  generate P**T.


       M (input) The number of rows of the matrix Q or P**T to be returned.  M
                 >= 0.


       N (input) The number of columns of the matrix Q or P**T to be returned.
                 N  >= 0.  If VECT = 'Q', M >= N >= min(M,K); if VECT = 'P', N
                 >= M >= min(N,K).


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


       A (input/output)
                 On entry, the vectors which define the elementary reflectors,
                 as returned by SGEBRD.  On exit, the M-by-N matrix Q or P**T.


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


       TAU (input)
                 (min(M,K)) if VECT = 'Q' (min(N,K)) if VECT = 'P' TAU(i) must
                 contain the scalar factor of the elementary reflector H(i) or
                 G(i), which determines Q or P**T, as returned  by  SGEBRD  in
                 its array argument TAUQ or TAUP.


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


       LWORK (input)
                 The  dimension  of  the array WORK. LWORK >= max(1,min(M,N)).
                 For optimum performance LWORK >= min(M,N)*NB, 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                        sorgbr(3P)