1 SUBROUTINE DTZRQF( M, N, A, LDA, TAU, INFO )
2 *
3 * -- LAPACK routine (version 3.3.1) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * -- April 2011 --
7 *
8 * .. Scalar Arguments ..
9 INTEGER INFO, LDA, M, N
10 * ..
11 * .. Array Arguments ..
12 DOUBLE PRECISION A( LDA, * ), TAU( * )
13 * ..
14 *
15 * Purpose
16 * =======
17 *
18 * This routine is deprecated and has been replaced by routine DTZRZF.
19 *
20 * DTZRQF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
21 * to upper triangular form by means of orthogonal transformations.
22 *
23 * The upper trapezoidal matrix A is factored as
24 *
25 * A = ( R 0 ) * Z,
26 *
27 * where Z is an N-by-N orthogonal matrix and R is an M-by-M upper
28 * triangular matrix.
29 *
30 * Arguments
31 * =========
32 *
33 * M (input) INTEGER
34 * The number of rows of the matrix A. M >= 0.
35 *
36 * N (input) INTEGER
37 * The number of columns of the matrix A. N >= M.
38 *
39 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
40 * On entry, the leading M-by-N upper trapezoidal part of the
41 * array A must contain the matrix to be factorized.
42 * On exit, the leading M-by-M upper triangular part of A
43 * contains the upper triangular matrix R, and elements M+1 to
44 * N of the first M rows of A, with the array TAU, represent the
45 * orthogonal matrix Z as a product of M elementary reflectors.
46 *
47 * LDA (input) INTEGER
48 * The leading dimension of the array A. LDA >= max(1,M).
49 *
50 * TAU (output) DOUBLE PRECISION array, dimension (M)
51 * The scalar factors of the elementary reflectors.
52 *
53 * INFO (output) INTEGER
54 * = 0: successful exit
55 * < 0: if INFO = -i, the i-th argument had an illegal value
56 *
57 * Further Details
58 * ===============
59 *
60 * The factorization is obtained by Householder's method. The kth
61 * transformation matrix, Z( k ), which is used to introduce zeros into
62 * the ( m - k + 1 )th row of A, is given in the form
63 *
64 * Z( k ) = ( I 0 ),
65 * ( 0 T( k ) )
66 *
67 * where
68 *
69 * T( k ) = I - tau*u( k )*u( k )**T, u( k ) = ( 1 ),
70 * ( 0 )
71 * ( z( k ) )
72 *
73 * tau is a scalar and z( k ) is an ( n - m ) element vector.
74 * tau and z( k ) are chosen to annihilate the elements of the kth row
75 * of X.
76 *
77 * The scalar tau is returned in the kth element of TAU and the vector
78 * u( k ) in the kth row of A, such that the elements of z( k ) are
79 * in a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
80 * the upper triangular part of A.
81 *
82 * Z is given by
83 *
84 * Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
85 *
86 * =====================================================================
87 *
88 * .. Parameters ..
89 DOUBLE PRECISION ONE, ZERO
90 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
91 * ..
92 * .. Local Scalars ..
93 INTEGER I, K, M1
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC MAX, MIN
97 * ..
98 * .. External Subroutines ..
99 EXTERNAL DAXPY, DCOPY, DGEMV, DGER, DLARFG, XERBLA
100 * ..
101 * .. Executable Statements ..
102 *
103 * Test the input parameters.
104 *
105 INFO = 0
106 IF( M.LT.0 ) THEN
107 INFO = -1
108 ELSE IF( N.LT.M ) THEN
109 INFO = -2
110 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
111 INFO = -4
112 END IF
113 IF( INFO.NE.0 ) THEN
114 CALL XERBLA( 'DTZRQF', -INFO )
115 RETURN
116 END IF
117 *
118 * Perform the factorization.
119 *
120 IF( M.EQ.0 )
121 $ RETURN
122 IF( M.EQ.N ) THEN
123 DO 10 I = 1, N
124 TAU( I ) = ZERO
125 10 CONTINUE
126 ELSE
127 M1 = MIN( M+1, N )
128 DO 20 K = M, 1, -1
129 *
130 * Use a Householder reflection to zero the kth row of A.
131 * First set up the reflection.
132 *
133 CALL DLARFG( N-M+1, A( K, K ), A( K, M1 ), LDA, TAU( K ) )
134 *
135 IF( ( TAU( K ).NE.ZERO ) .AND. ( K.GT.1 ) ) THEN
136 *
137 * We now perform the operation A := A*P( k ).
138 *
139 * Use the first ( k - 1 ) elements of TAU to store a( k ),
140 * where a( k ) consists of the first ( k - 1 ) elements of
141 * the kth column of A. Also let B denote the first
142 * ( k - 1 ) rows of the last ( n - m ) columns of A.
143 *
144 CALL DCOPY( K-1, A( 1, K ), 1, TAU, 1 )
145 *
146 * Form w = a( k ) + B*z( k ) in TAU.
147 *
148 CALL DGEMV( 'No transpose', K-1, N-M, ONE, A( 1, M1 ),
149 $ LDA, A( K, M1 ), LDA, ONE, TAU, 1 )
150 *
151 * Now form a( k ) := a( k ) - tau*w
152 * and B := B - tau*w*z( k )**T.
153 *
154 CALL DAXPY( K-1, -TAU( K ), TAU, 1, A( 1, K ), 1 )
155 CALL DGER( K-1, N-M, -TAU( K ), TAU, 1, A( K, M1 ), LDA,
156 $ A( 1, M1 ), LDA )
157 END IF
158 20 CONTINUE
159 END IF
160 *
161 RETURN
162 *
163 * End of DTZRQF
164 *
165 END
2 *
3 * -- LAPACK routine (version 3.3.1) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * -- April 2011 --
7 *
8 * .. Scalar Arguments ..
9 INTEGER INFO, LDA, M, N
10 * ..
11 * .. Array Arguments ..
12 DOUBLE PRECISION A( LDA, * ), TAU( * )
13 * ..
14 *
15 * Purpose
16 * =======
17 *
18 * This routine is deprecated and has been replaced by routine DTZRZF.
19 *
20 * DTZRQF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
21 * to upper triangular form by means of orthogonal transformations.
22 *
23 * The upper trapezoidal matrix A is factored as
24 *
25 * A = ( R 0 ) * Z,
26 *
27 * where Z is an N-by-N orthogonal matrix and R is an M-by-M upper
28 * triangular matrix.
29 *
30 * Arguments
31 * =========
32 *
33 * M (input) INTEGER
34 * The number of rows of the matrix A. M >= 0.
35 *
36 * N (input) INTEGER
37 * The number of columns of the matrix A. N >= M.
38 *
39 * A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
40 * On entry, the leading M-by-N upper trapezoidal part of the
41 * array A must contain the matrix to be factorized.
42 * On exit, the leading M-by-M upper triangular part of A
43 * contains the upper triangular matrix R, and elements M+1 to
44 * N of the first M rows of A, with the array TAU, represent the
45 * orthogonal matrix Z as a product of M elementary reflectors.
46 *
47 * LDA (input) INTEGER
48 * The leading dimension of the array A. LDA >= max(1,M).
49 *
50 * TAU (output) DOUBLE PRECISION array, dimension (M)
51 * The scalar factors of the elementary reflectors.
52 *
53 * INFO (output) INTEGER
54 * = 0: successful exit
55 * < 0: if INFO = -i, the i-th argument had an illegal value
56 *
57 * Further Details
58 * ===============
59 *
60 * The factorization is obtained by Householder's method. The kth
61 * transformation matrix, Z( k ), which is used to introduce zeros into
62 * the ( m - k + 1 )th row of A, is given in the form
63 *
64 * Z( k ) = ( I 0 ),
65 * ( 0 T( k ) )
66 *
67 * where
68 *
69 * T( k ) = I - tau*u( k )*u( k )**T, u( k ) = ( 1 ),
70 * ( 0 )
71 * ( z( k ) )
72 *
73 * tau is a scalar and z( k ) is an ( n - m ) element vector.
74 * tau and z( k ) are chosen to annihilate the elements of the kth row
75 * of X.
76 *
77 * The scalar tau is returned in the kth element of TAU and the vector
78 * u( k ) in the kth row of A, such that the elements of z( k ) are
79 * in a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
80 * the upper triangular part of A.
81 *
82 * Z is given by
83 *
84 * Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
85 *
86 * =====================================================================
87 *
88 * .. Parameters ..
89 DOUBLE PRECISION ONE, ZERO
90 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
91 * ..
92 * .. Local Scalars ..
93 INTEGER I, K, M1
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC MAX, MIN
97 * ..
98 * .. External Subroutines ..
99 EXTERNAL DAXPY, DCOPY, DGEMV, DGER, DLARFG, XERBLA
100 * ..
101 * .. Executable Statements ..
102 *
103 * Test the input parameters.
104 *
105 INFO = 0
106 IF( M.LT.0 ) THEN
107 INFO = -1
108 ELSE IF( N.LT.M ) THEN
109 INFO = -2
110 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
111 INFO = -4
112 END IF
113 IF( INFO.NE.0 ) THEN
114 CALL XERBLA( 'DTZRQF', -INFO )
115 RETURN
116 END IF
117 *
118 * Perform the factorization.
119 *
120 IF( M.EQ.0 )
121 $ RETURN
122 IF( M.EQ.N ) THEN
123 DO 10 I = 1, N
124 TAU( I ) = ZERO
125 10 CONTINUE
126 ELSE
127 M1 = MIN( M+1, N )
128 DO 20 K = M, 1, -1
129 *
130 * Use a Householder reflection to zero the kth row of A.
131 * First set up the reflection.
132 *
133 CALL DLARFG( N-M+1, A( K, K ), A( K, M1 ), LDA, TAU( K ) )
134 *
135 IF( ( TAU( K ).NE.ZERO ) .AND. ( K.GT.1 ) ) THEN
136 *
137 * We now perform the operation A := A*P( k ).
138 *
139 * Use the first ( k - 1 ) elements of TAU to store a( k ),
140 * where a( k ) consists of the first ( k - 1 ) elements of
141 * the kth column of A. Also let B denote the first
142 * ( k - 1 ) rows of the last ( n - m ) columns of A.
143 *
144 CALL DCOPY( K-1, A( 1, K ), 1, TAU, 1 )
145 *
146 * Form w = a( k ) + B*z( k ) in TAU.
147 *
148 CALL DGEMV( 'No transpose', K-1, N-M, ONE, A( 1, M1 ),
149 $ LDA, A( K, M1 ), LDA, ONE, TAU, 1 )
150 *
151 * Now form a( k ) := a( k ) - tau*w
152 * and B := B - tau*w*z( k )**T.
153 *
154 CALL DAXPY( K-1, -TAU( K ), TAU, 1, A( 1, K ), 1 )
155 CALL DGER( K-1, N-M, -TAU( K ), TAU, 1, A( K, M1 ), LDA,
156 $ A( 1, M1 ), LDA )
157 END IF
158 20 CONTINUE
159 END IF
160 *
161 RETURN
162 *
163 * End of DTZRQF
164 *
165 END