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