1DTZRZF(1) LAPACK routine (version 3.1) DTZRZF(1)
2
3
4
6 DTZRZF - the M-by-N ( M<=N ) real upper trapezoidal matrix A to upper
7 triangular form by means of orthogonal transformations
8
10 SUBROUTINE DTZRZF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
11
12 INTEGER INFO, LDA, LWORK, M, N
13
14 DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
15
17 DTZRZF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A to
18 upper triangular form by means of orthogonal transformations.
19
20 The upper trapezoidal matrix A is factored as
21
22 A = ( R 0 ) * Z,
23
24 where Z is an N-by-N orthogonal matrix and R is an M-by-M upper trian‐
25 gular matrix.
26
27
29 M (input) INTEGER
30 The number of rows of the matrix A. M >= 0.
31
32 N (input) INTEGER
33 The number of columns of the matrix A. N >= M.
34
35 A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
36 On entry, the leading M-by-N upper trapezoidal part of the
37 array A must contain the matrix to be factorized. On exit, the
38 leading M-by-M upper triangular part of A contains the upper
39 triangular matrix R, and elements M+1 to N of the first M rows
40 of A, with the array TAU, represent the orthogonal matrix Z as
41 a product of M elementary reflectors.
42
43 LDA (input) INTEGER
44 The leading dimension of the array A. LDA >= max(1,M).
45
46 TAU (output) DOUBLE PRECISION array, dimension (M)
47 The scalar factors of the elementary reflectors.
48
49 WORK (workspace/output) DOUBLE PRECISION array, dimension
50 (MAX(1,LWORK))
51 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
52
53 LWORK (input) INTEGER
54 The dimension of the array WORK. LWORK >= max(1,M). For opti‐
55 mum performance LWORK >= M*NB, where NB is the optimal block‐
56 size.
57
58 If LWORK = -1, then a workspace query is assumed; the routine
59 only calculates the optimal size of the WORK array, returns
60 this value as the first entry of the WORK array, and no error
61 message related to LWORK is issued by XERBLA.
62
63 INFO (output) INTEGER
64 = 0: successful exit
65 < 0: if INFO = -i, the i-th argument had an illegal value
66
68 Based on contributions by
69 A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
70
71 The factorization is obtained by Householder's method. The kth trans‐
72 formation matrix, Z( k ), which is used to introduce zeros into the ( m
73 - k + 1 )th row of A, is given in the form
74
75 Z( k ) = ( I 0 ),
76 ( 0 T( k ) )
77
78 where
79
80 T( k ) = I - tau*u( k )*u( k )', u( k ) = ( 1 ),
81 ( 0 )
82 ( z( k ) )
83
84 tau is a scalar and z( k ) is an ( n - m ) element vector. tau and z(
85 k ) are chosen to annihilate the elements of the kth row of X.
86
87 The scalar tau is returned in the kth element of TAU and the vector u(
88 k ) in the kth row of A, such that the elements of z( k ) are in a( k,
89 m + 1 ), ..., a( k, n ). The elements of R are returned in the upper
90 triangular part of A.
91
92 Z is given by
93
94 Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
95
96
97
98
99 LAPACK routine (version 3.1) November 2006 DTZRZF(1)