NAME

sggqrf - compute a generalized QR factorization of an N-by-M matrix A and an N-by-P matrix B.


SYNOPSIS

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

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

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

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


PURPOSE

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

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

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 N >= M, R = ( R11 ) M , or if N < M, R = ( R11 R12 ) N, ( 0 ) N-M N M-N M

where R11 is upper triangular, and

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

where T12 or T21 is upper triangular.

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

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

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(n,m).

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(1:i-1) = 0 and v(i) = 1; v(i+1:n) is stored on exit in A(i+1:n,i), and taua in TAUA(i).

To form Q explicitly, use LAPACK subroutine SORGQR.

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

The matrix Z is represented as a product of elementary reflectors

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

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(p-k+i+1:p) = 0 and v(p-k+i) = 1; v(1:p-k+i-1) is stored on exit in B(n-k+i,1:p-k+i-1), and taub in TAUB(i).

To form Z explicitly, use LAPACK subroutine SORGRQ.

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