LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cgqrts.f
Go to the documentation of this file.
1 *> \brief \b CGQRTS
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE CGQRTS( N, M, P, A, AF, Q, R, LDA, TAUA, B, BF, Z, T,
12 * BWK, LDB, TAUB, WORK, LWORK, RWORK, RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDB, LWORK, M, P, N
16 * ..
17 * .. Array Arguments ..
18 * REAL RWORK( * ), RESULT( 4 )
19 * COMPLEX A( LDA, * ), AF( LDA, * ), R( LDA, * ),
20 * $ Q( LDA, * ), B( LDB, * ), BF( LDB, * ),
21 * $ T( LDB, * ), Z( LDB, * ), BWK( LDB, * ),
22 * $ TAUA( * ), TAUB( * ), WORK( LWORK )
23 * ..
24 *
25 *
26 *> \par Purpose:
27 * =============
28 *>
29 *> \verbatim
30 *>
31 *> CGQRTS tests CGGQRF, which computes the GQR factorization of an
32 *> N-by-M matrix A and a N-by-P matrix B: A = Q*R and B = Q*T*Z.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] N
39 *> \verbatim
40 *> N is INTEGER
41 *> The number of rows of the matrices A and B. N >= 0.
42 *> \endverbatim
43 *>
44 *> \param[in] M
45 *> \verbatim
46 *> M is INTEGER
47 *> The number of columns of the matrix A. M >= 0.
48 *> \endverbatim
49 *>
50 *> \param[in] P
51 *> \verbatim
52 *> P is INTEGER
53 *> The number of columns of the matrix B. P >= 0.
54 *> \endverbatim
55 *>
56 *> \param[in] A
57 *> \verbatim
58 *> A is COMPLEX array, dimension (LDA,M)
59 *> The N-by-M matrix A.
60 *> \endverbatim
61 *>
62 *> \param[out] AF
63 *> \verbatim
64 *> AF is COMPLEX array, dimension (LDA,N)
65 *> Details of the GQR factorization of A and B, as returned
66 *> by CGGQRF, see CGGQRF for further details.
67 *> \endverbatim
68 *>
69 *> \param[out] Q
70 *> \verbatim
71 *> Q is COMPLEX array, dimension (LDA,N)
72 *> The M-by-M unitary matrix Q.
73 *> \endverbatim
74 *>
75 *> \param[out] R
76 *> \verbatim
77 *> R is COMPLEX array, dimension (LDA,MAX(M,N))
78 *> \endverbatim
79 *>
80 *> \param[in] LDA
81 *> \verbatim
82 *> LDA is INTEGER
83 *> The leading dimension of the arrays A, AF, R and Q.
84 *> LDA >= max(M,N).
85 *> \endverbatim
86 *>
87 *> \param[out] TAUA
88 *> \verbatim
89 *> TAUA is COMPLEX array, dimension (min(M,N))
90 *> The scalar factors of the elementary reflectors, as returned
91 *> by CGGQRF.
92 *> \endverbatim
93 *>
94 *> \param[in] B
95 *> \verbatim
96 *> B is COMPLEX array, dimension (LDB,P)
97 *> On entry, the N-by-P matrix A.
98 *> \endverbatim
99 *>
100 *> \param[out] BF
101 *> \verbatim
102 *> BF is COMPLEX array, dimension (LDB,N)
103 *> Details of the GQR factorization of A and B, as returned
104 *> by CGGQRF, see CGGQRF for further details.
105 *> \endverbatim
106 *>
107 *> \param[out] Z
108 *> \verbatim
109 *> Z is COMPLEX array, dimension (LDB,P)
110 *> The P-by-P unitary matrix Z.
111 *> \endverbatim
112 *>
113 *> \param[out] T
114 *> \verbatim
115 *> T is COMPLEX array, dimension (LDB,max(P,N))
116 *> \endverbatim
117 *>
118 *> \param[out] BWK
119 *> \verbatim
120 *> BWK is COMPLEX array, dimension (LDB,N)
121 *> \endverbatim
122 *>
123 *> \param[in] LDB
124 *> \verbatim
125 *> LDB is INTEGER
126 *> The leading dimension of the arrays B, BF, Z and T.
127 *> LDB >= max(P,N).
128 *> \endverbatim
129 *>
130 *> \param[out] TAUB
131 *> \verbatim
132 *> TAUB is COMPLEX array, dimension (min(P,N))
133 *> The scalar factors of the elementary reflectors, as returned
134 *> by SGGRQF.
135 *> \endverbatim
136 *>
137 *> \param[out] WORK
138 *> \verbatim
139 *> WORK is COMPLEX array, dimension (LWORK)
140 *> \endverbatim
141 *>
142 *> \param[in] LWORK
143 *> \verbatim
144 *> LWORK is INTEGER
145 *> The dimension of the array WORK, LWORK >= max(N,M,P)**2.
146 *> \endverbatim
147 *>
148 *> \param[out] RWORK
149 *> \verbatim
150 *> RWORK is REAL array, dimension (max(N,M,P))
151 *> \endverbatim
152 *>
153 *> \param[out] RESULT
154 *> \verbatim
155 *> RESULT is REAL array, dimension (4)
156 *> The test ratios:
157 *> RESULT(1) = norm( R - Q'*A ) / ( MAX(M,N)*norm(A)*ULP)
158 *> RESULT(2) = norm( T*Z - Q'*B ) / (MAX(P,N)*norm(B)*ULP)
159 *> RESULT(3) = norm( I - Q'*Q ) / ( M*ULP )
160 *> RESULT(4) = norm( I - Z'*Z ) / ( P*ULP )
161 *> \endverbatim
162 *
163 * Authors:
164 * ========
165 *
166 *> \author Univ. of Tennessee
167 *> \author Univ. of California Berkeley
168 *> \author Univ. of Colorado Denver
169 *> \author NAG Ltd.
170 *
171 *> \date November 2011
172 *
173 *> \ingroup complex_eig
174 *
175 * =====================================================================
176  SUBROUTINE cgqrts( N, M, P, A, AF, Q, R, LDA, TAUA, B, BF, Z, T,
177  $ bwk, ldb, taub, work, lwork, rwork, result )
178 *
179 * -- LAPACK test routine (version 3.4.0) --
180 * -- LAPACK is a software package provided by Univ. of Tennessee, --
181 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
182 * November 2011
183 *
184 * .. Scalar Arguments ..
185  INTEGER lda, ldb, lwork, m, p, n
186 * ..
187 * .. Array Arguments ..
188  REAL rwork( * ), result( 4 )
189  COMPLEX a( lda, * ), af( lda, * ), r( lda, * ),
190  $ q( lda, * ), b( ldb, * ), bf( ldb, * ),
191  $ t( ldb, * ), z( ldb, * ), bwk( ldb, * ),
192  $ taua( * ), taub( * ), work( lwork )
193 * ..
194 *
195 * =====================================================================
196 *
197 * .. Parameters ..
198  REAL zero, one
199  parameter( zero = 0.0e+0, one = 1.0e+0 )
200  COMPLEX czero, cone
201  parameter( czero = ( 0.0e+0, 0.0e+0 ),
202  $ cone = ( 1.0e+0, 0.0e+0 ) )
203  COMPLEX crogue
204  parameter( crogue = ( -1.0e+10, 0.0e+0 ) )
205 * ..
206 * .. Local Scalars ..
207  INTEGER info
208  REAL anorm, bnorm, ulp, unfl, resid
209 * ..
210 * .. External Functions ..
211  REAL slamch, clange, clanhe
212  EXTERNAL slamch, clange, clanhe
213 * ..
214 * .. External Subroutines ..
215  EXTERNAL cgemm, clacpy, claset, cungqr,
216  $ cungrq, cherk
217 * ..
218 * .. Intrinsic Functions ..
219  INTRINSIC max, min, real
220 * ..
221 * .. Executable Statements ..
222 *
223  ulp = slamch( 'Precision' )
224  unfl = slamch( 'Safe minimum' )
225 *
226 * Copy the matrix A to the array AF.
227 *
228  CALL clacpy( 'Full', n, m, a, lda, af, lda )
229  CALL clacpy( 'Full', n, p, b, ldb, bf, ldb )
230 *
231  anorm = max( clange( '1', n, m, a, lda, rwork ), unfl )
232  bnorm = max( clange( '1', n, p, b, ldb, rwork ), unfl )
233 *
234 * Factorize the matrices A and B in the arrays AF and BF.
235 *
236  CALL cggqrf( n, m, p, af, lda, taua, bf, ldb, taub, work,
237  $ lwork, info )
238 *
239 * Generate the N-by-N matrix Q
240 *
241  CALL claset( 'Full', n, n, crogue, crogue, q, lda )
242  CALL clacpy( 'Lower', n-1, m, af( 2,1 ), lda, q( 2,1 ), lda )
243  CALL cungqr( n, n, min( n, m ), q, lda, taua, work, lwork, info )
244 *
245 * Generate the P-by-P matrix Z
246 *
247  CALL claset( 'Full', p, p, crogue, crogue, z, ldb )
248  IF( n.LE.p ) THEN
249  IF( n.GT.0 .AND. n.LT.p )
250  $ CALL clacpy( 'Full', n, p-n, bf, ldb, z( p-n+1, 1 ), ldb )
251  IF( n.GT.1 )
252  $ CALL clacpy( 'Lower', n-1, n-1, bf( 2, p-n+1 ), ldb,
253  $ z( p-n+2, p-n+1 ), ldb )
254  ELSE
255  IF( p.GT.1)
256  $ CALL clacpy( 'Lower', p-1, p-1, bf( n-p+2, 1 ), ldb,
257  $ z( 2, 1 ), ldb )
258  END IF
259  CALL cungrq( p, p, min( n, p ), z, ldb, taub, work, lwork, info )
260 *
261 * Copy R
262 *
263  CALL claset( 'Full', n, m, czero, czero, r, lda )
264  CALL clacpy( 'Upper', n, m, af, lda, r, lda )
265 *
266 * Copy T
267 *
268  CALL claset( 'Full', n, p, czero, czero, t, ldb )
269  IF( n.LE.p ) THEN
270  CALL clacpy( 'Upper', n, n, bf( 1, p-n+1 ), ldb, t( 1, p-n+1 ),
271  $ ldb )
272  ELSE
273  CALL clacpy( 'Full', n-p, p, bf, ldb, t, ldb )
274  CALL clacpy( 'Upper', p, p, bf( n-p+1, 1 ), ldb, t( n-p+1, 1 ),
275  $ ldb )
276  END IF
277 *
278 * Compute R - Q'*A
279 *
280  CALL cgemm( 'Conjugate transpose', 'No transpose', n, m, n, -cone,
281  $ q, lda, a, lda, cone, r, lda )
282 *
283 * Compute norm( R - Q'*A ) / ( MAX(M,N)*norm(A)*ULP ) .
284 *
285  resid = clange( '1', n, m, r, lda, rwork )
286  IF( anorm.GT.zero ) THEN
287  result( 1 ) = ( ( resid / REAL( MAX(1,M,N) ) ) / anorm ) / ulp
288  ELSE
289  result( 1 ) = zero
290  END IF
291 *
292 * Compute T*Z - Q'*B
293 *
294  CALL cgemm( 'No Transpose', 'No transpose', n, p, p, cone, t, ldb,
295  $ z, ldb, czero, bwk, ldb )
296  CALL cgemm( 'Conjugate transpose', 'No transpose', n, p, n, -cone,
297  $ q, lda, b, ldb, cone, bwk, ldb )
298 *
299 * Compute norm( T*Z - Q'*B ) / ( MAX(P,N)*norm(A)*ULP ) .
300 *
301  resid = clange( '1', n, p, bwk, ldb, rwork )
302  IF( bnorm.GT.zero ) THEN
303  result( 2 ) = ( ( resid / REAL( MAX(1,P,N ) ) )/bnorm ) / ulp
304  ELSE
305  result( 2 ) = zero
306  END IF
307 *
308 * Compute I - Q'*Q
309 *
310  CALL claset( 'Full', n, n, czero, cone, r, lda )
311  CALL cherk( 'Upper', 'Conjugate transpose', n, n, -one, q, lda,
312  $ one, r, lda )
313 *
314 * Compute norm( I - Q'*Q ) / ( N * ULP ) .
315 *
316  resid = clanhe( '1', 'Upper', n, r, lda, rwork )
317  result( 3 ) = ( resid / REAL( MAX( 1, N ) ) ) / ulp
318 *
319 * Compute I - Z'*Z
320 *
321  CALL claset( 'Full', p, p, czero, cone, t, ldb )
322  CALL cherk( 'Upper', 'Conjugate transpose', p, p, -one, z, ldb,
323  $ one, t, ldb )
324 *
325 * Compute norm( I - Z'*Z ) / ( P*ULP ) .
326 *
327  resid = clanhe( '1', 'Upper', p, t, ldb, rwork )
328  result( 4 ) = ( resid / REAL( MAX( 1, P ) ) ) / ulp
329 *
330  return
331 *
332 * End of CGQRTS
333 *
334  END