Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

ztzrqf (3p)

Name

ztzrqf - routine is deprecated and has been replaced by routine ZTZRZF

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

void  ztzrqf(int  m,  int  n,  doublecomplex *a, int lda, doublecomplex
*tau, int *info);

void ztzrqf_64(long m, long n, doublecomplex *a, long  lda,  doublecom-
plex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           ztzrqf(3P)



NAME
       ztzrqf - routine is deprecated and has been replaced by routine ZTZRZF


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

       void  ztzrqf(int  m,  int  n,  doublecomplex *a, int lda, doublecomplex
                 *tau, int *info);

       void ztzrqf_64(long m, long n, doublecomplex *a, long  lda,  doublecom-
                 plex *tau, long *info);



PURPOSE
       ztzrqf routine is deprecated and has been replaced by routine ZTZRZF.

       ZTZRQF  reduces  the M-by-N ( M<=N ) complex upper trapezoidal matrix A
       to upper triangular form by means of unitary transformations.

       The upper trapezoidal matrix A is factored as

          A = ( R  0 ) * Z,

       where Z is an N-by-N unitary matrix and R is an M-by-M upper triangular
       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 contains the
                 upper triangular matrix R, and elements M+1 to N of the first
                 M rows of A, with the array TAU, represent the unitary 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 COMPLEX 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 ), whose conjugate transpose is used to intro-
       duce 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 )**H,   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                        ztzrqf(3P)