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