Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dtzrzf (3p)

Name

dtzrzf - N ( M<=N ) real upper trapezoidal matrix A to upper triangular form by means of orthogonal transformations

Synopsis

SUBROUTINE DTZRZF(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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

SUBROUTINE DTZRZF_64(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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




F95 INTERFACE
SUBROUTINE TZRZF(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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

SUBROUTINE TZRZF_64(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           dtzrzf(3P)



NAME
       dtzrzf  - reduce the M-by-N ( M<=N ) real upper trapezoidal matrix A to
       upper triangular form by means of orthogonal transformations


SYNOPSIS
       SUBROUTINE DTZRZF(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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

       SUBROUTINE DTZRZF_64(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE TZRZF(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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

       SUBROUTINE TZRZF_64(M, N, A, LDA, TAU, WORK, LWORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       dtzrzf  reduces  the M-by-N ( M<=N ) real upper trapezoidal matrix A to
       upper triangular form by means of orthogonal transformations.

       The upper trapezoidal matrix A is factored as

          A = ( R  0 ) * Z,

       where Z is an N-by-N orthogonal matrix and R is an M-by-M upper  trian-
       gular matrix.


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  leading M-by-N upper trapezoidal part of the
                 array A must contain the matrix to be factorized.
                 On exit, the leading M-by-M upper triangular part of  A  con-
                 tains the upper triangular matrix R, and elements M+1 to N of
                 the first M rows of A, with  the  array  TAU,  represent  the
                 orthogonal  matrix Z as a product of M elementary reflectors.


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


       TAU (output)
                 The scalar factors of the elementary reflectors.


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


       LWORK (input)
                 The dimension of the array  WORK.  LWORK  >=  max(1,M).   For
                 optimum  performance  LWORK  >= M*NB, where NB is the optimal
                 blocksize.

                 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
       Based on contributions by
         A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA

       The N-by-N matrix Z can be computed by

          Z =  Z(1)*Z(2)* ... *Z(M)

       where each N-by-N Z(k) is given by

          Z(k) = I - tau(k)*v(k)*v(k)**T

       with v(k) is the kth row vector of the M-by-N matrix

          V = ( I   A(:,M+1:N) )

       I  is  the M-by-M identity matrix, A(:,M+1:N) is the output stored in A
       on exit from DTZRZF, and tau(k) is the kth element of the array TAU.




                                  7 Nov 2015                        dtzrzf(3P)