Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zung2l (3p)

Name

zung2l - ization determined by cgeqlf (unblocked algorithm)

Synopsis

SUBROUTINE ZUNG2L(M, N, K, A, LDA, TAU, WORK, INFO)

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

SUBROUTINE ZUNG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

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




F95 INTERFACE
SUBROUTINE UNG2L(M, N, K, A, LDA, TAU, WORK, INFO)

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

SUBROUTINE UNG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

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




C INTERFACE
#include <sunperf.h>

void zung2l(int m, int n, int k, doublecomplex *a, int lda,  doublecom-
plex *tau, int *info);

void zung2l_64(long m, long n, long k, doublecomplex *a, long lda, dou-
blecomplex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           zung2l(3P)



NAME
       zung2l - generate all or part of the unitary matrix Q from a QL factor-
       ization determined by cgeqlf (unblocked algorithm)


SYNOPSIS
       SUBROUTINE ZUNG2L(M, N, K, A, LDA, TAU, WORK, INFO)

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

       SUBROUTINE ZUNG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE UNG2L(M, N, K, A, LDA, TAU, WORK, INFO)

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

       SUBROUTINE UNG2L_64(M, N, K, A, LDA, TAU, WORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void zung2l(int m, int n, int k, doublecomplex *a, int lda,  doublecom-
                 plex *tau, int *info);

       void zung2l_64(long m, long n, long k, doublecomplex *a, long lda, dou-
                 blecomplex *tau, long *info);



PURPOSE
       zung2l generates an M-by-N complex matrix Q with  orthonormal  columns,
       which  is  defined  as  the last N columns of a product of K elementary
       reflectors of order M

             Q  =  H(K) . . . H(2) * H(1)

       as returned by ZGEQLF.


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


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


       K (input) The number of elementary reflectors whose product defines the
                 matrix Q. N >= K >= 0.


       A (input/output)
                 On entry, the (n-k+i)-th column must contain the vector which
                 defines the elementary reflector H(i), for i = 1,2,...,k,  as
                 returned  by  ZGEQLF in the last k columns of its array argu-
                 ment A.  On exit, the m-by-n matrix Q.


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


       TAU (input)
                 TAU(i) must contain  the  scalar  factor  of  the  elementary
                 reflector H(i), as returned by ZGEQLF.


       WORK (workspace)
                 dimension(N)

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




                                  7 Nov 2015                        zung2l(3P)