Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dlatrz (3p)

Name

dlatrz - factor an upper trapezoidal matrix by means of orthogonal transformations

Synopsis

SUBROUTINE DLATRZ( M, N, L, A, LDA, TAU, WORK )


INTEGER L, LDA, M, N

DOUBLE PRECISION A(LDA,*), TAU(*),WORK(*)


SUBROUTINE DLATRZ_64( M, N, L, A, LDA, TAU, WORK )


INTEGER*8 L, LDA, M, N

DOUBLE PRECISION A(LDA,*), TAU(*),WORK(*)


F95 INTERFACE
SUBROUTINE LATRZ( M, N, L, A, LDA, TAU, WORK )


INTEGER :: M, N, L, LDA

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: TAU, WORK


SUBROUTINE LATRZ_64( M, N, L, A, LDA, TAU, WORK )


INTEGER(8) :: M, N, L, LDA

REAL(8), DIMENSION(:,:) :: A

REAL(8), DIMENSION(:) :: TAU, WORK


C INTERFACE
#include <sunperf.h>

void dlatrz (int m, int n, int l, double *a, int lda, double *tau);


void dlatrz_64 (long m, long n, long l, double  *a,  long  lda,  double
*tau);

Description

Oracle Solaris Studio Performance Library                           dlatrz(3P)



NAME
       dlatrz  -  factor  an  upper  trapezoidal matrix by means of orthogonal
       transformations


SYNOPSIS
       SUBROUTINE DLATRZ( M, N, L, A, LDA, TAU, WORK )


       INTEGER L, LDA, M, N

       DOUBLE PRECISION A(LDA,*), TAU(*),WORK(*)


       SUBROUTINE DLATRZ_64( M, N, L, A, LDA, TAU, WORK )


       INTEGER*8 L, LDA, M, N

       DOUBLE PRECISION A(LDA,*), TAU(*),WORK(*)


   F95 INTERFACE
       SUBROUTINE LATRZ( M, N, L, A, LDA, TAU, WORK )


       INTEGER :: M, N, L, LDA

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: TAU, WORK


       SUBROUTINE LATRZ_64( M, N, L, A, LDA, TAU, WORK )


       INTEGER(8) :: M, N, L, LDA

       REAL(8), DIMENSION(:,:) :: A

       REAL(8), DIMENSION(:) :: TAU, WORK


   C INTERFACE
       #include <sunperf.h>

       void dlatrz (int m, int n, int l, double *a, int lda, double *tau);


       void dlatrz_64 (long m, long n, long l, double  *a,  long  lda,  double
                 *tau);


PURPOSE
       dlatrz factors the M-by-(M+L) real upper trapezoidal matrix [ A1 A2 ] =
       [ A(1:M,1:M) A(1:M,N-L+1:N) ] as ( R  0 ) * Z, by means  of  orthogonal
       transformations.   Z  is an (M+L)-by-(M+L) orthogonal matrix and, R and
       A1 are M-by-M upper triangular matrices.


ARGUMENTS
       M (input)
                 M is INTEGER
                 The number of rows of the matrix A.  M >= 0.


       N (input)
                 N is INTEGER
                 The number of columns of the matrix A.  N >= 0.


       L (input)
                 L is INTEGER
                 The number of columns of the matrix A containing the
                 meaningful part of the Householder vectors. N-M >= L >= 0.


       A (input/output)
                 A is DOUBLE PRECISION array, dimension (LDA,N)
                 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
                 contains the upper triangular matrix R, and elements N-L+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)
                 LDA is INTEGER
                 The leading dimension of the array A.  LDA >= max(1,M).


       TAU (output)
                 TAU is DOUBLE PRECISION array, dimension (M)
                 The scalar factors of the elementary reflectors.


       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension (M)




                                  7 Nov 2015                        dlatrz(3P)