Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cggqrf (3p)

Name

cggqrf - M matrix A and an N-by-P matrix B.

Synopsis

SUBROUTINE CGGQRF(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK, LWORK,
INFO)

COMPLEX A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)
INTEGER N, M, P, LDA, LDB, LWORK, INFO

SUBROUTINE CGGQRF_64(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK,
LWORK, INFO)

COMPLEX A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)
INTEGER*8 N, M, P, LDA, LDB, LWORK, INFO




F95 INTERFACE
SUBROUTINE GGQRF(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK,
LWORK, INFO)

COMPLEX, DIMENSION(:) :: TAUA, TAUB, WORK
COMPLEX, DIMENSION(:,:) :: A, B
INTEGER :: N, M, P, LDA, LDB, LWORK, INFO

SUBROUTINE GGQRF_64(N, M, P, A, LDA, TAUA, B, LDB, TAUB,
WORK, LWORK, INFO)

COMPLEX, DIMENSION(:) :: TAUA, TAUB, WORK
COMPLEX, DIMENSION(:,:) :: A, B
INTEGER(8) :: N, M, P, LDA, LDB, LWORK, INFO




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           cggqrf(3P)



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


SYNOPSIS
       SUBROUTINE CGGQRF(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK, LWORK,
             INFO)

       COMPLEX A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)
       INTEGER N, M, P, LDA, LDB, LWORK, INFO

       SUBROUTINE CGGQRF_64(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK,
             LWORK, INFO)

       COMPLEX A(LDA,*), TAUA(*), B(LDB,*), TAUB(*), WORK(*)
       INTEGER*8 N, M, P, LDA, LDB, LWORK, INFO




   F95 INTERFACE
       SUBROUTINE GGQRF(N, M, P, A, LDA, TAUA, B, LDB, TAUB, WORK,
              LWORK, INFO)

       COMPLEX, DIMENSION(:) :: TAUA, TAUB, WORK
       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER :: N, M, P, LDA, LDB, LWORK, INFO

       SUBROUTINE GGQRF_64(N, M, P, A, LDA, TAUA, B, LDB, TAUB,
              WORK, LWORK, INFO)

       COMPLEX, DIMENSION(:) :: TAUA, TAUB, WORK
       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER(8) :: N, M, P, LDA, LDB, LWORK, INFO




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       cggqrf 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 unitary matrix, Z is a P-by-P unitary 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
       conjugate transpose of matrix Z.


ARGUMENTS
       N (input) The number of rows of the matrices A and B. N >= 0.


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


       P (input) The number of columns of the matrix B.  P >= 0.


       A (input/output)
                 On entry, the N-by-M matrix A.  On exit, the elements on  and
                 above  the  diagonal  of  the array contain the min(N,M)-by-M
                 upper trapezoidal matrix R (R is upper triangular if N >= M);
                 the  elements below the diagonal, with the array TAUA, repre-
                 sent the unitary matrix Q as a product of min(N,M) elementary
                 reflectors (see Further Details).


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


       TAUA (output)
                 The  scalar factors of the elementary reflectors which repre-
                 sent the unitary matrix Q (see Further Details).


       B (input/output)
                 On entry, the N-by-P matrix B.  On exit, if N <= P, the upper
                 triangle  of  the subarray B(1:N,P-N+1:P) contains the N-by-N
                 upper triangular matrix T; if N >  P,  the  elements  on  and
                 above  the  (N-P)-th  subdiagonal  contain  the  N-by-P upper
                 trapezoidal matrix T; the remaining elements, with the  array
                 TAUB,  represent the unitary matrix Z as a product of elemen-
                 tary reflectors (see Further Details).


       LDB (input)
                 The leading dimension of the array B. LDB >= max(1,N).


       TAUB (output)
                 The scalar factors of the elementary reflectors which  repre-
                 sent the unitary matrix Z (see Further Details).


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


       LWORK (input)
                 The  dimension of the array WORK. LWORK >= max(1,N,M,P).  For
                 optimum  performance  LWORK  >=  max(N,M,P)*max(NB1,NB2,NB3),
                 where  NB1  is the optimal blocksize for the QR factorization
                 of an N-by-M matrix, NB2 is the optimal blocksize for the  RQ
                 factorization  of  an  N-by-P  matrix, and NB3 is the optimal
                 blocksize for a call of CUNMQR.

                 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.

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 complex scalar, and v is a complex 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 CUNGQR.
       To use Q to update another matrix, use LAPACK subroutine CUNMQR.

       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  complex scalar, and v is a complex 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 CUNGRQ.
       To use Z to update another matrix, use LAPACK subroutine CUNMRQ.




                                  7 Nov 2015                        cggqrf(3P)