LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cget54.f
Go to the documentation of this file.
1*> \brief \b CGET54
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 CGET54( N, A, LDA, B, LDB, S, LDS, T, LDT, U, LDU, V,
12* LDV, WORK, RESULT )
13*
14* .. Scalar Arguments ..
15* INTEGER LDA, LDB, LDS, LDT, LDU, LDV, N
16* REAL RESULT
17* ..
18* .. Array Arguments ..
19* COMPLEX A( LDA, * ), B( LDB, * ), S( LDS, * ),
20* $ T( LDT, * ), U( LDU, * ), V( LDV, * ),
21* $ WORK( * )
22* ..
23*
24*
25*> \par Purpose:
26* =============
27*>
28*> \verbatim
29*>
30*> CGET54 checks a generalized decomposition of the form
31*>
32*> A = U*S*V' and B = U*T* V'
33*>
34*> where ' means conjugate transpose and U and V are unitary.
35*>
36*> Specifically,
37*>
38*> RESULT = ||( A - U*S*V', B - U*T*V' )|| / (||( A, B )||*n*ulp )
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] N
45*> \verbatim
46*> N is INTEGER
47*> The size of the matrix. If it is zero, SGET54 does nothing.
48*> It must be at least zero.
49*> \endverbatim
50*>
51*> \param[in] A
52*> \verbatim
53*> A is COMPLEX array, dimension (LDA, N)
54*> The original (unfactored) matrix A.
55*> \endverbatim
56*>
57*> \param[in] LDA
58*> \verbatim
59*> LDA is INTEGER
60*> The leading dimension of A. It must be at least 1
61*> and at least N.
62*> \endverbatim
63*>
64*> \param[in] B
65*> \verbatim
66*> B is COMPLEX array, dimension (LDB, N)
67*> The original (unfactored) matrix B.
68*> \endverbatim
69*>
70*> \param[in] LDB
71*> \verbatim
72*> LDB is INTEGER
73*> The leading dimension of B. It must be at least 1
74*> and at least N.
75*> \endverbatim
76*>
77*> \param[in] S
78*> \verbatim
79*> S is COMPLEX array, dimension (LDS, N)
80*> The factored matrix S.
81*> \endverbatim
82*>
83*> \param[in] LDS
84*> \verbatim
85*> LDS is INTEGER
86*> The leading dimension of S. It must be at least 1
87*> and at least N.
88*> \endverbatim
89*>
90*> \param[in] T
91*> \verbatim
92*> T is COMPLEX array, dimension (LDT, N)
93*> The factored matrix T.
94*> \endverbatim
95*>
96*> \param[in] LDT
97*> \verbatim
98*> LDT is INTEGER
99*> The leading dimension of T. It must be at least 1
100*> and at least N.
101*> \endverbatim
102*>
103*> \param[in] U
104*> \verbatim
105*> U is COMPLEX array, dimension (LDU, N)
106*> The orthogonal matrix on the left-hand side in the
107*> decomposition.
108*> \endverbatim
109*>
110*> \param[in] LDU
111*> \verbatim
112*> LDU is INTEGER
113*> The leading dimension of U. LDU must be at least N and
114*> at least 1.
115*> \endverbatim
116*>
117*> \param[in] V
118*> \verbatim
119*> V is COMPLEX array, dimension (LDV, N)
120*> The orthogonal matrix on the left-hand side in the
121*> decomposition.
122*> \endverbatim
123*>
124*> \param[in] LDV
125*> \verbatim
126*> LDV is INTEGER
127*> The leading dimension of V. LDV must be at least N and
128*> at least 1.
129*> \endverbatim
130*>
131*> \param[out] WORK
132*> \verbatim
133*> WORK is COMPLEX array, dimension (3*N**2)
134*> \endverbatim
135*>
136*> \param[out] RESULT
137*> \verbatim
138*> RESULT is REAL
139*> The value RESULT, It is currently limited to 1/ulp, to
140*> avoid overflow. Errors are flagged by RESULT=10/ulp.
141*> \endverbatim
142*
143* Authors:
144* ========
145*
146*> \author Univ. of Tennessee
147*> \author Univ. of California Berkeley
148*> \author Univ. of Colorado Denver
149*> \author NAG Ltd.
150*
151*> \ingroup complex_eig
152*
153* =====================================================================
154 SUBROUTINE cget54( N, A, LDA, B, LDB, S, LDS, T, LDT, U, LDU, V,
155 $ LDV, WORK, RESULT )
156*
157* -- LAPACK test routine --
158* -- LAPACK is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 INTEGER LDA, LDB, LDS, LDT, LDU, LDV, N
163 REAL RESULT
164* ..
165* .. Array Arguments ..
166 COMPLEX A( LDA, * ), B( LDB, * ), S( LDS, * ),
167 $ t( ldt, * ), u( ldu, * ), v( ldv, * ),
168 $ work( * )
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 REAL ZERO, ONE
175 parameter( zero = 0.0e+0, one = 1.0e+0 )
176 COMPLEX CZERO, CONE
177 parameter( czero = ( 0.0e+0, 0.0e+0 ),
178 $ cone = ( 1.0e+0, 0.0e+0 ) )
179* ..
180* .. Local Scalars ..
181 REAL ABNORM, ULP, UNFL, WNORM
182* ..
183* .. Local Arrays ..
184 REAL DUM( 1 )
185* ..
186* .. External Functions ..
187 REAL CLANGE, SLAMCH
188 EXTERNAL clange, slamch
189* ..
190* .. External Subroutines ..
191 EXTERNAL cgemm, clacpy
192* ..
193* .. Intrinsic Functions ..
194 INTRINSIC max, min, real
195* ..
196* .. Executable Statements ..
197*
198 result = zero
199 IF( n.LE.0 )
200 $ RETURN
201*
202* Constants
203*
204 unfl = slamch( 'Safe minimum' )
205 ulp = slamch( 'Epsilon' )*slamch( 'Base' )
206*
207* compute the norm of (A,B)
208*
209 CALL clacpy( 'Full', n, n, a, lda, work, n )
210 CALL clacpy( 'Full', n, n, b, ldb, work( n*n+1 ), n )
211 abnorm = max( clange( '1', n, 2*n, work, n, dum ), unfl )
212*
213* Compute W1 = A - U*S*V', and put in the array WORK(1:N*N)
214*
215 CALL clacpy( ' ', n, n, a, lda, work, n )
216 CALL cgemm( 'N', 'N', n, n, n, cone, u, ldu, s, lds, czero,
217 $ work( n*n+1 ), n )
218*
219 CALL cgemm( 'N', 'C', n, n, n, -cone, work( n*n+1 ), n, v, ldv,
220 $ cone, work, n )
221*
222* Compute W2 = B - U*T*V', and put in the workarray W(N*N+1:2*N*N)
223*
224 CALL clacpy( ' ', n, n, b, ldb, work( n*n+1 ), n )
225 CALL cgemm( 'N', 'N', n, n, n, cone, u, ldu, t, ldt, czero,
226 $ work( 2*n*n+1 ), n )
227*
228 CALL cgemm( 'N', 'C', n, n, n, -cone, work( 2*n*n+1 ), n, v, ldv,
229 $ cone, work( n*n+1 ), n )
230*
231* Compute norm(W)/ ( ulp*norm((A,B)) )
232*
233 wnorm = clange( '1', n, 2*n, work, n, dum )
234*
235 IF( abnorm.GT.wnorm ) THEN
236 result = ( wnorm / abnorm ) / ( 2*n*ulp )
237 ELSE
238 IF( abnorm.LT.one ) THEN
239 result = ( min( wnorm, 2*n*abnorm ) / abnorm ) / ( 2*n*ulp )
240 ELSE
241 result = min( wnorm / abnorm, real( 2*n ) ) / ( 2*n*ulp )
242 END IF
243 END IF
244*
245 RETURN
246*
247* End of CGET54
248*
249 END
subroutine cget54(n, a, lda, b, ldb, s, lds, t, ldt, u, ldu, v, ldv, work, result)
CGET54
Definition cget54.f:156
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
Definition cgemm.f:188
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
Definition clacpy.f:103