NAME

sggrqf - compute a generalized RQ factorization of an M-by-N matrix A and a P-by-N matrix B


SYNOPSIS

  SUBROUTINE SGGRQF( M, P, N, A, LDA, TAUA, B, LDB, TAUB, WORK, LWORK, 
 *      INFO)
  INTEGER M, P, N, LDA, LDB, LWORK, INFO
  REAL A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)
  SUBROUTINE SGGRQF_64( M, P, N, A, LDA, TAUA, B, LDB, TAUB, WORK, 
 *      LWORK, INFO)
  INTEGER*8 M, P, N, LDA, LDB, LWORK, INFO
  REAL A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)

F95 INTERFACE

  SUBROUTINE GGRQF( [M], [P], [N], A, [LDA], TAUA, B, [LDB], TAUB, 
 *       [WORK], [LWORK], [INFO])
  INTEGER :: M, P, N, LDA, LDB, LWORK, INFO
  REAL, DIMENSION(:) :: TAUA, TAUB, WORK
  REAL, DIMENSION(:,:) :: A, B
  SUBROUTINE GGRQF_64( [M], [P], [N], A, [LDA], TAUA, B, [LDB], TAUB, 
 *       [WORK], [LWORK], [INFO])
  INTEGER(8) :: M, P, N, LDA, LDB, LWORK, INFO
  REAL, DIMENSION(:) :: TAUA, TAUB, WORK
  REAL, DIMENSION(:,:) :: A, B

C INTERFACE

#include <sunperf.h>

void sggrqf(int m, int p, int n, float *a, int lda, float *taua, float *b, int ldb, float *taub, int *info);

void sggrqf_64(long m, long p, long n, float *a, long lda, float *taua, float *b, long ldb, float *taub, long *info);


PURPOSE

sggrqf computes a generalized RQ factorization of an M-by-N matrix A and a P-by-N matrix B:

            A = R*Q,        B = Z*T*Q,

where Q is an N-by-N orthogonal matrix, Z is a P-by-P orthogonal matrix, and R and T assume one of the forms:

if M <= N, R = ( 0 R12 ) M, or if M > N, R = ( R11 ) M-N, N-M M ( R21 ) N N

where R12 or R21 is upper triangular, and

if P >= N, T = ( T11 ) N , or if P < N, T = ( T11 T12 ) P, ( 0 ) P-N P N-P N

where T11 is upper triangular.

In particular, if B is square and nonsingular, the GRQ factorization of A and B implicitly gives the RQ factorization of A*inv(B):

             A*inv(B) = (R*inv(T))*Z'

where inv(B) denotes the inverse of the matrix B, and Z' denotes the transpose of the matrix Z.


ARGUMENTS


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 - taua * v * v'

where taua 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 taua in TAUA(i).

To form Q explicitly, use LAPACK subroutine SORGRQ.

To use Q to update another matrix, use LAPACK subroutine SORMRQ.

The matrix Z is represented as a product of elementary reflectors

   Z  = H(1) H(2) . . . H(k), where k  = min(p,n).

Each H(i) has the form

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

where taub is a real scalar, and v is a real vector with

v(1:i-1) = 0 and v(i) = 1; v(i+1:p) is stored on exit in B(i+1:p,i), and taub in TAUB(i).

To form Z explicitly, use LAPACK subroutine SORGQR.

To use Z to update another matrix, use LAPACK subroutine SORMQR.