Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dorgl2 (3p)

Name

dorgl2 - generate an m by n real matrix Q with orthonormal rows,

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

void  dorgl2(int  m, int n, int k, double *a, int lda, double *tau, int
*info);

void dorgl2_64(long m, long n, long k,  double  *a,  long  lda,  double
*tau, long *info);

Description

Oracle Solaris Studio Performance Library                           dorgl2(3P)



NAME
       dorgl2 - generate an m by n real matrix Q with orthonormal rows,


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void  dorgl2(int  m, int n, int k, double *a, int lda, double *tau, int
                 *info);

       void dorgl2_64(long m, long n, long k,  double  *a,  long  lda,  double
                 *tau, long *info);



PURPOSE
       dorgl2  generates  an m by n real matrix Q with orthonormal rows, which
       is defined as the first m rows of a product of k elementary  reflectors
       of order n

             Q  =  H(k) . . . H(2) H(1)

       as returned by DGELQF.


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


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


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


       A (input/output)
                 On entry, the i-th row must contain the vector which  defines
                 the elementary reflector H(i), for i = 1,2,...,k, as returned
                 by DGELQF in the first k rows of its array  argument  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 DGELQF.


       WORK (workspace)
                 dimension(M)

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




                                  7 Nov 2015                        dorgl2(3P)