1 SUBROUTINE SRQT02( M, N, K, A, AF, Q, R, LDA, TAU, WORK, LWORK,
2 $ RWORK, RESULT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 INTEGER K, LDA, LWORK, M, N
10 * ..
11 * .. Array Arguments ..
12 REAL A( LDA, * ), AF( LDA, * ), Q( LDA, * ),
13 $ R( LDA, * ), RESULT( * ), RWORK( * ), TAU( * ),
14 $ WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * SRQT02 tests SORGRQ, which generates an m-by-n matrix Q with
21 * orthonornmal rows that is defined as the product of k elementary
22 * reflectors.
23 *
24 * Given the RQ factorization of an m-by-n matrix A, SRQT02 generates
25 * the orthogonal matrix Q defined by the factorization of the last k
26 * rows of A; it compares R(m-k+1:m,n-m+1:n) with
27 * A(m-k+1:m,1:n)*Q(n-m+1:n,1:n)', and checks that the rows of Q are
28 * orthonormal.
29 *
30 * Arguments
31 * =========
32 *
33 * M (input) INTEGER
34 * The number of rows of the matrix Q to be generated. M >= 0.
35 *
36 * N (input) INTEGER
37 * The number of columns of the matrix Q to be generated.
38 * N >= M >= 0.
39 *
40 * K (input) INTEGER
41 * The number of elementary reflectors whose product defines the
42 * matrix Q. M >= K >= 0.
43 *
44 * A (input) REAL array, dimension (LDA,N)
45 * The m-by-n matrix A which was factorized by SRQT01.
46 *
47 * AF (input) REAL array, dimension (LDA,N)
48 * Details of the RQ factorization of A, as returned by SGERQF.
49 * See SGERQF for further details.
50 *
51 * Q (workspace) REAL array, dimension (LDA,N)
52 *
53 * R (workspace) REAL array, dimension (LDA,M)
54 *
55 * LDA (input) INTEGER
56 * The leading dimension of the arrays A, AF, Q and L. LDA >= N.
57 *
58 * TAU (input) REAL array, dimension (M)
59 * The scalar factors of the elementary reflectors corresponding
60 * to the RQ factorization in AF.
61 *
62 * WORK (workspace) REAL array, dimension (LWORK)
63 *
64 * LWORK (input) INTEGER
65 * The dimension of the array WORK.
66 *
67 * RWORK (workspace) REAL array, dimension (M)
68 *
69 * RESULT (output) REAL array, dimension (2)
70 * The test ratios:
71 * RESULT(1) = norm( R - A*Q' ) / ( N * norm(A) * EPS )
72 * RESULT(2) = norm( I - Q*Q' ) / ( N * EPS )
73 *
74 * =====================================================================
75 *
76 * .. Parameters ..
77 REAL ZERO, ONE
78 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
79 REAL ROGUE
80 PARAMETER ( ROGUE = -1.0E+10 )
81 * ..
82 * .. Local Scalars ..
83 INTEGER INFO
84 REAL ANORM, EPS, RESID
85 * ..
86 * .. External Functions ..
87 REAL SLAMCH, SLANGE, SLANSY
88 EXTERNAL SLAMCH, SLANGE, SLANSY
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL SGEMM, SLACPY, SLASET, SORGRQ, SSYRK
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC MAX, REAL
95 * ..
96 * .. Scalars in Common ..
97 CHARACTER*32 SRNAMT
98 * ..
99 * .. Common blocks ..
100 COMMON / SRNAMC / SRNAMT
101 * ..
102 * .. Executable Statements ..
103 *
104 * Quick return if possible
105 *
106 IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 ) THEN
107 RESULT( 1 ) = ZERO
108 RESULT( 2 ) = ZERO
109 RETURN
110 END IF
111 *
112 EPS = SLAMCH( 'Epsilon' )
113 *
114 * Copy the last k rows of the factorization to the array Q
115 *
116 CALL SLASET( 'Full', M, N, ROGUE, ROGUE, Q, LDA )
117 IF( K.LT.N )
118 $ CALL SLACPY( 'Full', K, N-K, AF( M-K+1, 1 ), LDA,
119 $ Q( M-K+1, 1 ), LDA )
120 IF( K.GT.1 )
121 $ CALL SLACPY( 'Lower', K-1, K-1, AF( M-K+2, N-K+1 ), LDA,
122 $ Q( M-K+2, N-K+1 ), LDA )
123 *
124 * Generate the last n rows of the matrix Q
125 *
126 SRNAMT = 'SORGRQ'
127 CALL SORGRQ( M, N, K, Q, LDA, TAU( M-K+1 ), WORK, LWORK, INFO )
128 *
129 * Copy R(m-k+1:m,n-m+1:n)
130 *
131 CALL SLASET( 'Full', K, M, ZERO, ZERO, R( M-K+1, N-M+1 ), LDA )
132 CALL SLACPY( 'Upper', K, K, AF( M-K+1, N-K+1 ), LDA,
133 $ R( M-K+1, N-K+1 ), LDA )
134 *
135 * Compute R(m-k+1:m,n-m+1:n) - A(m-k+1:m,1:n) * Q(n-m+1:n,1:n)'
136 *
137 CALL SGEMM( 'No transpose', 'Transpose', K, M, N, -ONE,
138 $ A( M-K+1, 1 ), LDA, Q, LDA, ONE, R( M-K+1, N-M+1 ),
139 $ LDA )
140 *
141 * Compute norm( R - A*Q' ) / ( N * norm(A) * EPS ) .
142 *
143 ANORM = SLANGE( '1', K, N, A( M-K+1, 1 ), LDA, RWORK )
144 RESID = SLANGE( '1', K, M, R( M-K+1, N-M+1 ), LDA, RWORK )
145 IF( ANORM.GT.ZERO ) THEN
146 RESULT( 1 ) = ( ( RESID / REAL( MAX( 1, N ) ) ) / ANORM ) / EPS
147 ELSE
148 RESULT( 1 ) = ZERO
149 END IF
150 *
151 * Compute I - Q*Q'
152 *
153 CALL SLASET( 'Full', M, M, ZERO, ONE, R, LDA )
154 CALL SSYRK( 'Upper', 'No transpose', M, N, -ONE, Q, LDA, ONE, R,
155 $ LDA )
156 *
157 * Compute norm( I - Q*Q' ) / ( N * EPS ) .
158 *
159 RESID = SLANSY( '1', 'Upper', M, R, LDA, RWORK )
160 *
161 RESULT( 2 ) = ( RESID / REAL( MAX( 1, N ) ) ) / EPS
162 *
163 RETURN
164 *
165 * End of SRQT02
166 *
167 END
2 $ RWORK, RESULT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 INTEGER K, LDA, LWORK, M, N
10 * ..
11 * .. Array Arguments ..
12 REAL A( LDA, * ), AF( LDA, * ), Q( LDA, * ),
13 $ R( LDA, * ), RESULT( * ), RWORK( * ), TAU( * ),
14 $ WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * SRQT02 tests SORGRQ, which generates an m-by-n matrix Q with
21 * orthonornmal rows that is defined as the product of k elementary
22 * reflectors.
23 *
24 * Given the RQ factorization of an m-by-n matrix A, SRQT02 generates
25 * the orthogonal matrix Q defined by the factorization of the last k
26 * rows of A; it compares R(m-k+1:m,n-m+1:n) with
27 * A(m-k+1:m,1:n)*Q(n-m+1:n,1:n)', and checks that the rows of Q are
28 * orthonormal.
29 *
30 * Arguments
31 * =========
32 *
33 * M (input) INTEGER
34 * The number of rows of the matrix Q to be generated. M >= 0.
35 *
36 * N (input) INTEGER
37 * The number of columns of the matrix Q to be generated.
38 * N >= M >= 0.
39 *
40 * K (input) INTEGER
41 * The number of elementary reflectors whose product defines the
42 * matrix Q. M >= K >= 0.
43 *
44 * A (input) REAL array, dimension (LDA,N)
45 * The m-by-n matrix A which was factorized by SRQT01.
46 *
47 * AF (input) REAL array, dimension (LDA,N)
48 * Details of the RQ factorization of A, as returned by SGERQF.
49 * See SGERQF for further details.
50 *
51 * Q (workspace) REAL array, dimension (LDA,N)
52 *
53 * R (workspace) REAL array, dimension (LDA,M)
54 *
55 * LDA (input) INTEGER
56 * The leading dimension of the arrays A, AF, Q and L. LDA >= N.
57 *
58 * TAU (input) REAL array, dimension (M)
59 * The scalar factors of the elementary reflectors corresponding
60 * to the RQ factorization in AF.
61 *
62 * WORK (workspace) REAL array, dimension (LWORK)
63 *
64 * LWORK (input) INTEGER
65 * The dimension of the array WORK.
66 *
67 * RWORK (workspace) REAL array, dimension (M)
68 *
69 * RESULT (output) REAL array, dimension (2)
70 * The test ratios:
71 * RESULT(1) = norm( R - A*Q' ) / ( N * norm(A) * EPS )
72 * RESULT(2) = norm( I - Q*Q' ) / ( N * EPS )
73 *
74 * =====================================================================
75 *
76 * .. Parameters ..
77 REAL ZERO, ONE
78 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
79 REAL ROGUE
80 PARAMETER ( ROGUE = -1.0E+10 )
81 * ..
82 * .. Local Scalars ..
83 INTEGER INFO
84 REAL ANORM, EPS, RESID
85 * ..
86 * .. External Functions ..
87 REAL SLAMCH, SLANGE, SLANSY
88 EXTERNAL SLAMCH, SLANGE, SLANSY
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL SGEMM, SLACPY, SLASET, SORGRQ, SSYRK
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC MAX, REAL
95 * ..
96 * .. Scalars in Common ..
97 CHARACTER*32 SRNAMT
98 * ..
99 * .. Common blocks ..
100 COMMON / SRNAMC / SRNAMT
101 * ..
102 * .. Executable Statements ..
103 *
104 * Quick return if possible
105 *
106 IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 ) THEN
107 RESULT( 1 ) = ZERO
108 RESULT( 2 ) = ZERO
109 RETURN
110 END IF
111 *
112 EPS = SLAMCH( 'Epsilon' )
113 *
114 * Copy the last k rows of the factorization to the array Q
115 *
116 CALL SLASET( 'Full', M, N, ROGUE, ROGUE, Q, LDA )
117 IF( K.LT.N )
118 $ CALL SLACPY( 'Full', K, N-K, AF( M-K+1, 1 ), LDA,
119 $ Q( M-K+1, 1 ), LDA )
120 IF( K.GT.1 )
121 $ CALL SLACPY( 'Lower', K-1, K-1, AF( M-K+2, N-K+1 ), LDA,
122 $ Q( M-K+2, N-K+1 ), LDA )
123 *
124 * Generate the last n rows of the matrix Q
125 *
126 SRNAMT = 'SORGRQ'
127 CALL SORGRQ( M, N, K, Q, LDA, TAU( M-K+1 ), WORK, LWORK, INFO )
128 *
129 * Copy R(m-k+1:m,n-m+1:n)
130 *
131 CALL SLASET( 'Full', K, M, ZERO, ZERO, R( M-K+1, N-M+1 ), LDA )
132 CALL SLACPY( 'Upper', K, K, AF( M-K+1, N-K+1 ), LDA,
133 $ R( M-K+1, N-K+1 ), LDA )
134 *
135 * Compute R(m-k+1:m,n-m+1:n) - A(m-k+1:m,1:n) * Q(n-m+1:n,1:n)'
136 *
137 CALL SGEMM( 'No transpose', 'Transpose', K, M, N, -ONE,
138 $ A( M-K+1, 1 ), LDA, Q, LDA, ONE, R( M-K+1, N-M+1 ),
139 $ LDA )
140 *
141 * Compute norm( R - A*Q' ) / ( N * norm(A) * EPS ) .
142 *
143 ANORM = SLANGE( '1', K, N, A( M-K+1, 1 ), LDA, RWORK )
144 RESID = SLANGE( '1', K, M, R( M-K+1, N-M+1 ), LDA, RWORK )
145 IF( ANORM.GT.ZERO ) THEN
146 RESULT( 1 ) = ( ( RESID / REAL( MAX( 1, N ) ) ) / ANORM ) / EPS
147 ELSE
148 RESULT( 1 ) = ZERO
149 END IF
150 *
151 * Compute I - Q*Q'
152 *
153 CALL SLASET( 'Full', M, M, ZERO, ONE, R, LDA )
154 CALL SSYRK( 'Upper', 'No transpose', M, N, -ONE, Q, LDA, ONE, R,
155 $ LDA )
156 *
157 * Compute norm( I - Q*Q' ) / ( N * EPS ) .
158 *
159 RESID = SLANSY( '1', 'Upper', M, R, LDA, RWORK )
160 *
161 RESULT( 2 ) = ( RESID / REAL( MAX( 1, N ) ) ) / EPS
162 *
163 RETURN
164 *
165 * End of SRQT02
166 *
167 END