Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgelqf (3p)

Name

zgelqf - N matrix A

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

void  zgelqf(int  m,  int  n,  doublecomplex *a, int lda, doublecomplex
*tau, int *info);

void zgelqf_64(long m, long n, doublecomplex *a, long  lda,  doublecom-
plex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           zgelqf(3P)



NAME
       zgelqf - compute an LQ factorization of a complex M-by-N matrix A


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void  zgelqf(int  m,  int  n,  doublecomplex *a, int lda, doublecomplex
                 *tau, int *info);

       void zgelqf_64(long m, long n, doublecomplex *a, long  lda,  doublecom-
                 plex *tau, long *info);



PURPOSE
       zgelqf computes an LQ factorization of a complex M-by-N matrix A: A = L
       * 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, the elements on  and
                 below  the  diagonal  of  the array contain the m-by-min(m,n)
                 lower trapezoidal matrix L (L is lower triangular if m <= n);
                 the  elements  above the diagonal, with the array TAU, repre-
                 sent the unitary matrix Q as a product of elementary  reflec-
                 tors (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(k)' . . . H(2)' H(1)', where k = min(m,n).

       Each H(i) has the form

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

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




                                  7 Nov 2015                        zgelqf(3P)