Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sorg2l (3p)

Name

sorg2l - generate an m by n real matrix Q with orthonormal columns,

Synopsis

SUBROUTINE SORG2L(M, N, K, A, LDA, TAU, WORK, INFO)

INTEGER M, N, K, LDA, INFO
REAL A(LDA,*), TAU(*), WORK(*)

SUBROUTINE SORG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

INTEGER*8 M, N, K, LDA, INFO
REAL A(LDA,*), TAU(*), WORK(*)




F95 INTERFACE
SUBROUTINE ORG2L(M, N, K, A, LDA, TAU, WORK, INFO)

INTEGER :: M, N, K, LDA, INFO
REAL, DIMENSION(:) :: TAU, WORK
REAL, DIMENSION(:,:) :: A

SUBROUTINE ORG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

INTEGER(8) :: M, N, K, LDA, INFO
REAL, DIMENSION(:) :: TAU, WORK
REAL, DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void  sorg2l(int  m,  int  n, int k, float *a, int lda, float *tau, int
*info);

void sorg2l_64(long m, long n, long k, float *a, long lda, float  *tau,
long *info);

Description

Oracle Solaris Studio Performance Library                           sorg2l(3P)



NAME
       sorg2l - generate an m by n real matrix Q with orthonormal columns,


SYNOPSIS
       SUBROUTINE SORG2L(M, N, K, A, LDA, TAU, WORK, INFO)

       INTEGER M, N, K, LDA, INFO
       REAL A(LDA,*), TAU(*), WORK(*)

       SUBROUTINE SORG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

       INTEGER*8 M, N, K, LDA, INFO
       REAL A(LDA,*), TAU(*), WORK(*)




   F95 INTERFACE
       SUBROUTINE ORG2L(M, N, K, A, LDA, TAU, WORK, INFO)

       INTEGER :: M, N, K, LDA, INFO
       REAL, DIMENSION(:) :: TAU, WORK
       REAL, DIMENSION(:,:) :: A

       SUBROUTINE ORG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

       INTEGER(8) :: M, N, K, LDA, INFO
       REAL, DIMENSION(:) :: TAU, WORK
       REAL, DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void  sorg2l(int  m,  int  n, int k, float *a, int lda, float *tau, int
                 *info);

       void sorg2l_64(long m, long n, long k, float *a, long lda, float  *tau,
                 long *info);



PURPOSE
       sorg2l  L  generates  an m by n real matrix Q with orthonormal columns,
       which is defined as the last n columns of a  product  of  k  elementary
       reflectors of order m

             Q  =  H(k) . . . H(2) H(1)

       as returned by SGEQLF.


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


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


       K (input) The number of elementary reflectors whose product defines the
                 matrix Q. N >= K >= 0.


       A (input/output)
                 On entry, the (n-k+i)-th column must contain the vector which
                 defines  the elementary reflector H(i), for i = 1,2,...,k, as
                 returned by SGEQLF in the last k columns of its  array  argu-
                 ment A.  On exit, the m by n matrix Q.


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


       TAU (input)
                 TAU(i)  must  contain  the  scalar  factor  of the elementary
                 reflector H(i), as returned by SGEQLF.


       WORK (workspace)
                 dimension(N)

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




                                  7 Nov 2015                        sorg2l(3P)