Contents


NAME

     ztzrzf - reduce the M-by-N  (  M<=N  )  complex  upper  tra-
     pezoidal  matrix A to upper triangular form by means of uni-
     tary transformations

SYNOPSIS

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

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

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

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

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

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

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

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

  C INTERFACE
     #include <sunperf.h>

     void ztzrzf(int m, int n, doublecomplex *a, int  lda,  doub-
               lecomplex *tau, int *info);

     void ztzrzf_64(long m, long n, doublecomplex *a,  long  lda,
               doublecomplex *tau, long *info);

PURPOSE

     ztzrzf 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 >= 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 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 uni-
               tary matrix Z as a product of M elementary reflec-
               tors.

     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.,  Knox-
     ville, USA

     The factorization is obtained by Householder's method.   The
     kth  transformation  matrix, Z( k ), which 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 )',   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 ).