1 SUBROUTINE CQLT02( 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 RESULT( * ), RWORK( * )
13 COMPLEX A( LDA, * ), AF( LDA, * ), L( LDA, * ),
14 $ Q( LDA, * ), TAU( * ), WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * CQLT02 tests CUNGQL, which generates an m-by-n matrix Q with
21 * orthonornmal columns that is defined as the product of k elementary
22 * reflectors.
23 *
24 * Given the QL factorization of an m-by-n matrix A, CQLT02 generates
25 * the orthogonal matrix Q defined by the factorization of the last k
26 * columns of A; it compares L(m-n+1:m,n-k+1:n) with
27 * Q(1:m,m-n+1:m)'*A(1:m,n-k+1:n), and checks that the columns 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 * M >= N >= 0.
39 *
40 * K (input) INTEGER
41 * The number of elementary reflectors whose product defines the
42 * matrix Q. N >= K >= 0.
43 *
44 * A (input) COMPLEX array, dimension (LDA,N)
45 * The m-by-n matrix A which was factorized by CQLT01.
46 *
47 * AF (input) COMPLEX array, dimension (LDA,N)
48 * Details of the QL factorization of A, as returned by CGEQLF.
49 * See CGEQLF for further details.
50 *
51 * Q (workspace) COMPLEX array, dimension (LDA,N)
52 *
53 * L (workspace) COMPLEX array, dimension (LDA,N)
54 *
55 * LDA (input) INTEGER
56 * The leading dimension of the arrays A, AF, Q and L. LDA >= M.
57 *
58 * TAU (input) COMPLEX array, dimension (N)
59 * The scalar factors of the elementary reflectors corresponding
60 * to the QL factorization in AF.
61 *
62 * WORK (workspace) COMPLEX 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( L - Q'*A ) / ( M * norm(A) * EPS )
72 * RESULT(2) = norm( I - Q'*Q ) / ( M * EPS )
73 *
74 * =====================================================================
75 *
76 * .. Parameters ..
77 REAL ZERO, ONE
78 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
79 COMPLEX ROGUE
80 PARAMETER ( ROGUE = ( -1.0E+10, -1.0E+10 ) )
81 * ..
82 * .. Local Scalars ..
83 INTEGER INFO
84 REAL ANORM, EPS, RESID
85 * ..
86 * .. External Functions ..
87 REAL CLANGE, CLANSY, SLAMCH
88 EXTERNAL CLANGE, CLANSY, SLAMCH
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL CGEMM, CHERK, CLACPY, CLASET, CUNGQL
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC CMPLX, 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 columns of the factorization to the array Q
115 *
116 CALL CLASET( 'Full', M, N, ROGUE, ROGUE, Q, LDA )
117 IF( K.LT.M )
118 $ CALL CLACPY( 'Full', M-K, K, AF( 1, N-K+1 ), LDA,
119 $ Q( 1, N-K+1 ), LDA )
120 IF( K.GT.1 )
121 $ CALL CLACPY( 'Upper', K-1, K-1, AF( M-K+1, N-K+2 ), LDA,
122 $ Q( M-K+1, N-K+2 ), LDA )
123 *
124 * Generate the last n columns of the matrix Q
125 *
126 SRNAMT = 'CUNGQL'
127 CALL CUNGQL( M, N, K, Q, LDA, TAU( N-K+1 ), WORK, LWORK, INFO )
128 *
129 * Copy L(m-n+1:m,n-k+1:n)
130 *
131 CALL CLASET( 'Full', N, K, CMPLX( ZERO ), CMPLX( ZERO ),
132 $ L( M-N+1, N-K+1 ), LDA )
133 CALL CLACPY( 'Lower', K, K, AF( M-K+1, N-K+1 ), LDA,
134 $ L( M-K+1, N-K+1 ), LDA )
135 *
136 * Compute L(m-n+1:m,n-k+1:n) - Q(1:m,m-n+1:m)' * A(1:m,n-k+1:n)
137 *
138 CALL CGEMM( 'Conjugate transpose', 'No transpose', N, K, M,
139 $ CMPLX( -ONE ), Q, LDA, A( 1, N-K+1 ), LDA,
140 $ CMPLX( ONE ), L( M-N+1, N-K+1 ), LDA )
141 *
142 * Compute norm( L - Q'*A ) / ( M * norm(A) * EPS ) .
143 *
144 ANORM = CLANGE( '1', M, K, A( 1, N-K+1 ), LDA, RWORK )
145 RESID = CLANGE( '1', N, K, L( M-N+1, N-K+1 ), LDA, RWORK )
146 IF( ANORM.GT.ZERO ) THEN
147 RESULT( 1 ) = ( ( RESID / REAL( MAX( 1, M ) ) ) / ANORM ) / EPS
148 ELSE
149 RESULT( 1 ) = ZERO
150 END IF
151 *
152 * Compute I - Q'*Q
153 *
154 CALL CLASET( 'Full', N, N, CMPLX( ZERO ), CMPLX( ONE ), L, LDA )
155 CALL CHERK( 'Upper', 'Conjugate transpose', N, M, -ONE, Q, LDA,
156 $ ONE, L, LDA )
157 *
158 * Compute norm( I - Q'*Q ) / ( M * EPS ) .
159 *
160 RESID = CLANSY( '1', 'Upper', N, L, LDA, RWORK )
161 *
162 RESULT( 2 ) = ( RESID / REAL( MAX( 1, M ) ) ) / EPS
163 *
164 RETURN
165 *
166 * End of CQLT02
167 *
168 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 RESULT( * ), RWORK( * )
13 COMPLEX A( LDA, * ), AF( LDA, * ), L( LDA, * ),
14 $ Q( LDA, * ), TAU( * ), WORK( LWORK )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * CQLT02 tests CUNGQL, which generates an m-by-n matrix Q with
21 * orthonornmal columns that is defined as the product of k elementary
22 * reflectors.
23 *
24 * Given the QL factorization of an m-by-n matrix A, CQLT02 generates
25 * the orthogonal matrix Q defined by the factorization of the last k
26 * columns of A; it compares L(m-n+1:m,n-k+1:n) with
27 * Q(1:m,m-n+1:m)'*A(1:m,n-k+1:n), and checks that the columns 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 * M >= N >= 0.
39 *
40 * K (input) INTEGER
41 * The number of elementary reflectors whose product defines the
42 * matrix Q. N >= K >= 0.
43 *
44 * A (input) COMPLEX array, dimension (LDA,N)
45 * The m-by-n matrix A which was factorized by CQLT01.
46 *
47 * AF (input) COMPLEX array, dimension (LDA,N)
48 * Details of the QL factorization of A, as returned by CGEQLF.
49 * See CGEQLF for further details.
50 *
51 * Q (workspace) COMPLEX array, dimension (LDA,N)
52 *
53 * L (workspace) COMPLEX array, dimension (LDA,N)
54 *
55 * LDA (input) INTEGER
56 * The leading dimension of the arrays A, AF, Q and L. LDA >= M.
57 *
58 * TAU (input) COMPLEX array, dimension (N)
59 * The scalar factors of the elementary reflectors corresponding
60 * to the QL factorization in AF.
61 *
62 * WORK (workspace) COMPLEX 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( L - Q'*A ) / ( M * norm(A) * EPS )
72 * RESULT(2) = norm( I - Q'*Q ) / ( M * EPS )
73 *
74 * =====================================================================
75 *
76 * .. Parameters ..
77 REAL ZERO, ONE
78 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
79 COMPLEX ROGUE
80 PARAMETER ( ROGUE = ( -1.0E+10, -1.0E+10 ) )
81 * ..
82 * .. Local Scalars ..
83 INTEGER INFO
84 REAL ANORM, EPS, RESID
85 * ..
86 * .. External Functions ..
87 REAL CLANGE, CLANSY, SLAMCH
88 EXTERNAL CLANGE, CLANSY, SLAMCH
89 * ..
90 * .. External Subroutines ..
91 EXTERNAL CGEMM, CHERK, CLACPY, CLASET, CUNGQL
92 * ..
93 * .. Intrinsic Functions ..
94 INTRINSIC CMPLX, 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 columns of the factorization to the array Q
115 *
116 CALL CLASET( 'Full', M, N, ROGUE, ROGUE, Q, LDA )
117 IF( K.LT.M )
118 $ CALL CLACPY( 'Full', M-K, K, AF( 1, N-K+1 ), LDA,
119 $ Q( 1, N-K+1 ), LDA )
120 IF( K.GT.1 )
121 $ CALL CLACPY( 'Upper', K-1, K-1, AF( M-K+1, N-K+2 ), LDA,
122 $ Q( M-K+1, N-K+2 ), LDA )
123 *
124 * Generate the last n columns of the matrix Q
125 *
126 SRNAMT = 'CUNGQL'
127 CALL CUNGQL( M, N, K, Q, LDA, TAU( N-K+1 ), WORK, LWORK, INFO )
128 *
129 * Copy L(m-n+1:m,n-k+1:n)
130 *
131 CALL CLASET( 'Full', N, K, CMPLX( ZERO ), CMPLX( ZERO ),
132 $ L( M-N+1, N-K+1 ), LDA )
133 CALL CLACPY( 'Lower', K, K, AF( M-K+1, N-K+1 ), LDA,
134 $ L( M-K+1, N-K+1 ), LDA )
135 *
136 * Compute L(m-n+1:m,n-k+1:n) - Q(1:m,m-n+1:m)' * A(1:m,n-k+1:n)
137 *
138 CALL CGEMM( 'Conjugate transpose', 'No transpose', N, K, M,
139 $ CMPLX( -ONE ), Q, LDA, A( 1, N-K+1 ), LDA,
140 $ CMPLX( ONE ), L( M-N+1, N-K+1 ), LDA )
141 *
142 * Compute norm( L - Q'*A ) / ( M * norm(A) * EPS ) .
143 *
144 ANORM = CLANGE( '1', M, K, A( 1, N-K+1 ), LDA, RWORK )
145 RESID = CLANGE( '1', N, K, L( M-N+1, N-K+1 ), LDA, RWORK )
146 IF( ANORM.GT.ZERO ) THEN
147 RESULT( 1 ) = ( ( RESID / REAL( MAX( 1, M ) ) ) / ANORM ) / EPS
148 ELSE
149 RESULT( 1 ) = ZERO
150 END IF
151 *
152 * Compute I - Q'*Q
153 *
154 CALL CLASET( 'Full', N, N, CMPLX( ZERO ), CMPLX( ONE ), L, LDA )
155 CALL CHERK( 'Upper', 'Conjugate transpose', N, M, -ONE, Q, LDA,
156 $ ONE, L, LDA )
157 *
158 * Compute norm( I - Q'*Q ) / ( M * EPS ) .
159 *
160 RESID = CLANSY( '1', 'Upper', N, L, LDA, RWORK )
161 *
162 RESULT( 2 ) = ( RESID / REAL( MAX( 1, M ) ) ) / EPS
163 *
164 RETURN
165 *
166 * End of CQLT02
167 *
168 END