Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dtzrqf (3p)

Name

dtzrqf - routine is deprecated and has been replaced by routine DTZRZF

Synopsis

SUBROUTINE DTZRQF(M, N, A, LDA, TAU, INFO)

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

SUBROUTINE DTZRQF_64(M, N, A, LDA, TAU, INFO)

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




F95 INTERFACE
SUBROUTINE TZRQF(M, N, A, LDA, TAU, INFO)

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

SUBROUTINE TZRQF_64(M, N, A, LDA, TAU, INFO)

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           dtzrqf(3P)



NAME
       dtzrqf - routine is deprecated and has been replaced by routine DTZRZF


SYNOPSIS
       SUBROUTINE DTZRQF(M, N, A, LDA, TAU, INFO)

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

       SUBROUTINE DTZRQF_64(M, N, A, LDA, TAU, INFO)

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




   F95 INTERFACE
       SUBROUTINE TZRQF(M, N, A, LDA, TAU, INFO)

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

       SUBROUTINE TZRQF_64(M, N, A, LDA, TAU, INFO)

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       dtzrqf routine is deprecated and has been replaced by routine DTZRZF.

       DTZRQF 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 >= M.


       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) DOUBLE PRECISION array, dimension (M)
                 The scalar factors of the elementary reflectors.


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


FURTHER DETAILS
       The  factorization  is obtained by Householder's method. The kth trans-
       formation matrix, Z( k ), which is used to introduce zeros into the ( m
       - k + 1 )th row of A, is given in the form

          Z( k ) = ( I     0   ),
                   ( 0  T( k ) )

       where

          T( k ) = I - tau*u( k )*u( k )**T,   u( k ) = (   1    ),
                                                        (   0    )
                                                        ( z( k ) )

       tau  is a scalar and z( k ) is an ( n - m ) element vector.  tau and z(
       k ) are chosen to annihilate the elements of the kth row of X.

       The scalar tau is returned in the kth element of TAU and the vector  u(
       k ) in the kth row of A, such that the elements of z( k ) are in  a( k,
       m + 1 ), ..., a( k, n ). The elements of R are returned  in  the  upper
       triangular part of A.

       Z is given by

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




                                  7 Nov 2015                        dtzrqf(3P)