Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgerqf (3p)

Name

sgerqf - N matrix A

Synopsis

SUBROUTINE SGERQF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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

SUBROUTINE SGERQF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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




F95 INTERFACE
SUBROUTINE GERQF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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

SUBROUTINE GERQF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           sgerqf(3P)



NAME
       sgerqf - compute an RQ factorization of a real M-by-N matrix A


SYNOPSIS
       SUBROUTINE SGERQF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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

       SUBROUTINE SGERQF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE GERQF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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

       SUBROUTINE GERQF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       sgerqf computes an RQ factorization of a real M-by-N matrix A: A = R  *
       Q.


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


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


       A (input/output)
                 On entry, the M-by-N matrix A.  On exit, if m <= n, the upper
                 triangle of the subarray A(1:m,n-m+1:n) contains  the  M-by-M
                 upper  triangular  matrix  R;  if m >= n, the elements on and
                 above the  (m-n)-th  subdiagonal  contain  the  M-by-N  upper
                 trapezoidal  matrix R; the remaining elements, with the array
                 TAU, represent the  orthogonal  matrix  Q  as  a  product  of
                 min(m,n) elementary reflectors (see Further Details).


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


       TAU (output)
                 The  scalar factors of the elementary reflectors (see Further
                 Details).


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


       LDWORK (input)
                 The dimension of the array WORK.  LDWORK  >=  max(1,M).   For
                 optimum  performance  LDWORK >= M*NB, where NB is the optimal
                 blocksize.

                 If LDWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  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 LDWORK is issued by XERBLA.


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

FURTHER DETAILS
       The matrix Q is represented as a product of elementary reflectors

          Q = H(1) H(2) . . . H(k), where k = min(m,n).

       Each H(i) has the form

          H(i) = I - tau * v * v'

       where tau is a real scalar, and v is a real vector with
       v(n-k+i+1:n)  =  0  and v(n-k+i) = 1; v(1:n-k+i-1) is stored on exit in
       A(m-k+i,1:n-k+i-1), and tau in TAU(i).




                                  7 Nov 2015                        sgerqf(3P)