1STZRZF(1)                LAPACK routine (version 3.2)                STZRZF(1)
2
3
4

NAME

6       STZRZF - reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A to
7       upper triangular form by means of orthogonal transformations
8

SYNOPSIS

10       SUBROUTINE STZRZF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
11
12           INTEGER        INFO, LDA, LWORK, M, N
13
14           REAL           A( LDA, * ), TAU( * ), WORK( * )
15

PURPOSE

17       STZRZF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix  A  to
18       upper  triangular  form  by  means  of orthogonal transformations.  The
19       upper trapezoidal matrix A is factored as
20          A = ( R  0 ) * Z,
21       where Z is an N-by-N orthogonal matrix and R is an M-by-M upper  trian‐
22       gular matrix.
23

ARGUMENTS

25       M       (input) INTEGER
26               The number of rows of the matrix A.  M >= 0.
27
28       N       (input) INTEGER
29               The number of columns of the matrix A.  N >= M.
30
31       A       (input/output) REAL array, dimension (LDA,N)
32               On  entry,  the  leading  M-by-N  upper trapezoidal part of the
33               array A must contain the matrix to be factorized.  On exit, the
34               leading  M-by-M  upper  triangular part of A contains the upper
35               triangular matrix R, and elements M+1 to N of the first M  rows
36               of  A, with the array TAU, represent the orthogonal matrix Z as
37               a product of M elementary reflectors.
38
39       LDA     (input) INTEGER
40               The leading dimension of the array A.  LDA >= max(1,M).
41
42       TAU     (output) REAL array, dimension (M)
43               The scalar factors of the elementary reflectors.
44
45       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
46               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
47
48       LWORK   (input) INTEGER
49               The dimension of the array WORK.  LWORK >= max(1,M).  For opti‐
50               mum  performance  LWORK >= M*NB, where NB is the optimal block‐
51               size.  If LWORK = -1, then a workspace query  is  assumed;  the
52               routine  only  calculates  the  optimal size of the WORK array,
53               returns this value as the first entry of the WORK array, and no
54               error message related to LWORK is issued by XERBLA.
55
56       INFO    (output) INTEGER
57               = 0:  successful exit
58               < 0:  if INFO = -i, the i-th argument had an illegal value
59

FURTHER DETAILS

61       Based on contributions by
62         A.  Petitet,  Computer  Science Dept., Univ. of Tenn., Knoxville, USA
63       The factorization is obtained by Householder's method.  The kth  trans‐
64       formation matrix, Z( k ), which is used to introduce zeros into the ( m
65       - k + 1 )th row of A, is given in the form
66          Z( k ) = ( I     0   ),
67                   ( 0  T( k ) )
68       where
69          T( k ) = I - tau*u( k )*u( k )',   u( k ) = (   1    ),
70                                                      (   0    )
71                                                      ( z( k  )  )  tau  is  a
72       scalar  and  z( k ) is an ( n - m ) element vector.  tau and z( k ) are
73       chosen to annihilate the elements of the kth row of X.
74       The scalar tau is returned in the kth element of TAU and the vector  u(
75       k ) in the kth row of A, such that the elements of z( k ) are in  a( k,
76       m + 1 ), ..., a( k, n ). The elements of R are returned  in  the  upper
77       triangular part of A.
78       Z is given by
79          Z =  Z( 1 ) * Z( 2 ) * ... * Z( m ).
80
81
82
83 LAPACK routine (version 3.2)    November 2008                       STZRZF(1)
Impressum