LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zhbt21.f
Go to the documentation of this file.
1*> \brief \b ZHBT21
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 ZHBT21( UPLO, N, KA, KS, A, LDA, D, E, U, LDU, WORK,
12* RWORK, RESULT )
13*
14* .. Scalar Arguments ..
15* CHARACTER UPLO
16* INTEGER KA, KS, LDA, LDU, N
17* ..
18* .. Array Arguments ..
19* DOUBLE PRECISION D( * ), E( * ), RESULT( 2 ), RWORK( * )
20* COMPLEX*16 A( LDA, * ), U( LDU, * ), WORK( * )
21* ..
22*
23*
24*> \par Purpose:
25* =============
26*>
27*> \verbatim
28*>
29*> ZHBT21 generally checks a decomposition of the form
30*>
31*> A = U S U**H
32*>
33*> where **H means conjugate transpose, A is hermitian banded, U is
34*> unitary, and S is diagonal (if KS=0) or symmetric
35*> tridiagonal (if KS=1).
36*>
37*> Specifically:
38*>
39*> RESULT(1) = | A - U S U**H | / ( |A| n ulp ) and
40*> RESULT(2) = | I - U U**H | / ( n ulp )
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] UPLO
47*> \verbatim
48*> UPLO is CHARACTER
49*> If UPLO='U', the upper triangle of A and V will be used and
50*> the (strictly) lower triangle will not be referenced.
51*> If UPLO='L', the lower triangle of A and V will be used and
52*> the (strictly) upper triangle will not be referenced.
53*> \endverbatim
54*>
55*> \param[in] N
56*> \verbatim
57*> N is INTEGER
58*> The size of the matrix. If it is zero, ZHBT21 does nothing.
59*> It must be at least zero.
60*> \endverbatim
61*>
62*> \param[in] KA
63*> \verbatim
64*> KA is INTEGER
65*> The bandwidth of the matrix A. It must be at least zero. If
66*> it is larger than N-1, then max( 0, N-1 ) will be used.
67*> \endverbatim
68*>
69*> \param[in] KS
70*> \verbatim
71*> KS is INTEGER
72*> The bandwidth of the matrix S. It may only be zero or one.
73*> If zero, then S is diagonal, and E is not referenced. If
74*> one, then S is symmetric tri-diagonal.
75*> \endverbatim
76*>
77*> \param[in] A
78*> \verbatim
79*> A is COMPLEX*16 array, dimension (LDA, N)
80*> The original (unfactored) matrix. It is assumed to be
81*> hermitian, and only the upper (UPLO='U') or only the lower
82*> (UPLO='L') will be referenced.
83*> \endverbatim
84*>
85*> \param[in] LDA
86*> \verbatim
87*> LDA is INTEGER
88*> The leading dimension of A. It must be at least 1
89*> and at least min( KA, N-1 ).
90*> \endverbatim
91*>
92*> \param[in] D
93*> \verbatim
94*> D is DOUBLE PRECISION array, dimension (N)
95*> The diagonal of the (symmetric tri-) diagonal matrix S.
96*> \endverbatim
97*>
98*> \param[in] E
99*> \verbatim
100*> E is DOUBLE PRECISION array, dimension (N-1)
101*> The off-diagonal of the (symmetric tri-) diagonal matrix S.
102*> E(1) is the (1,2) and (2,1) element, E(2) is the (2,3) and
103*> (3,2) element, etc.
104*> Not referenced if KS=0.
105*> \endverbatim
106*>
107*> \param[in] U
108*> \verbatim
109*> U is COMPLEX*16 array, dimension (LDU, N)
110*> The unitary matrix in the decomposition, expressed as a
111*> dense matrix (i.e., not as a product of Householder
112*> transformations, Givens transformations, etc.)
113*> \endverbatim
114*>
115*> \param[in] LDU
116*> \verbatim
117*> LDU is INTEGER
118*> The leading dimension of U. LDU must be at least N and
119*> at least 1.
120*> \endverbatim
121*>
122*> \param[out] WORK
123*> \verbatim
124*> WORK is COMPLEX*16 array, dimension (N**2)
125*> \endverbatim
126*>
127*> \param[out] RWORK
128*> \verbatim
129*> RWORK is DOUBLE PRECISION array, dimension (N)
130*> \endverbatim
131*>
132*> \param[out] RESULT
133*> \verbatim
134*> RESULT is DOUBLE PRECISION array, dimension (2)
135*> The values computed by the two tests described above. The
136*> values are currently limited to 1/ulp, to avoid overflow.
137*> \endverbatim
138*
139* Authors:
140* ========
141*
142*> \author Univ. of Tennessee
143*> \author Univ. of California Berkeley
144*> \author Univ. of Colorado Denver
145*> \author NAG Ltd.
146*
147*> \ingroup complex16_eig
148*
149* =====================================================================
150 SUBROUTINE zhbt21( UPLO, N, KA, KS, A, LDA, D, E, U, LDU, WORK,
151 $ RWORK, RESULT )
152*
153* -- LAPACK test routine --
154* -- LAPACK is a software package provided by Univ. of Tennessee, --
155* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156*
157* .. Scalar Arguments ..
158 CHARACTER UPLO
159 INTEGER KA, KS, LDA, LDU, N
160* ..
161* .. Array Arguments ..
162 DOUBLE PRECISION D( * ), E( * ), RESULT( 2 ), RWORK( * )
163 COMPLEX*16 A( LDA, * ), U( LDU, * ), WORK( * )
164* ..
165*
166* =====================================================================
167*
168* .. Parameters ..
169 COMPLEX*16 CZERO, CONE
170 parameter( czero = ( 0.0d+0, 0.0d+0 ),
171 $ cone = ( 1.0d+0, 0.0d+0 ) )
172 DOUBLE PRECISION ZERO, ONE
173 parameter( zero = 0.0d+0, one = 1.0d+0 )
174* ..
175* .. Local Scalars ..
176 LOGICAL LOWER
177 CHARACTER CUPLO
178 INTEGER IKA, J, JC, JR
179 DOUBLE PRECISION ANORM, ULP, UNFL, WNORM
180* ..
181* .. External Functions ..
182 LOGICAL LSAME
183 DOUBLE PRECISION DLAMCH, ZLANGE, ZLANHB, ZLANHP
184 EXTERNAL lsame, dlamch, zlange, zlanhb, zlanhp
185* ..
186* .. External Subroutines ..
187 EXTERNAL zgemm, zhpr, zhpr2
188* ..
189* .. Intrinsic Functions ..
190 INTRINSIC dble, dcmplx, max, min
191* ..
192* .. Executable Statements ..
193*
194* Constants
195*
196 result( 1 ) = zero
197 result( 2 ) = zero
198 IF( n.LE.0 )
199 $ RETURN
200*
201 ika = max( 0, min( n-1, ka ) )
202*
203 IF( lsame( uplo, 'U' ) ) THEN
204 lower = .false.
205 cuplo = 'U'
206 ELSE
207 lower = .true.
208 cuplo = 'L'
209 END IF
210*
211 unfl = dlamch( 'Safe minimum' )
212 ulp = dlamch( 'Epsilon' )*dlamch( 'Base' )
213*
214* Some Error Checks
215*
216* Do Test 1
217*
218* Norm of A:
219*
220 anorm = max( zlanhb( '1', cuplo, n, ika, a, lda, rwork ), unfl )
221*
222* Compute error matrix: Error = A - U S U**H
223*
224* Copy A from SB to SP storage format.
225*
226 j = 0
227 DO 50 jc = 1, n
228 IF( lower ) THEN
229 DO 10 jr = 1, min( ika+1, n+1-jc )
230 j = j + 1
231 work( j ) = a( jr, jc )
232 10 CONTINUE
233 DO 20 jr = ika + 2, n + 1 - jc
234 j = j + 1
235 work( j ) = zero
236 20 CONTINUE
237 ELSE
238 DO 30 jr = ika + 2, jc
239 j = j + 1
240 work( j ) = zero
241 30 CONTINUE
242 DO 40 jr = min( ika, jc-1 ), 0, -1
243 j = j + 1
244 work( j ) = a( ika+1-jr, jc )
245 40 CONTINUE
246 END IF
247 50 CONTINUE
248*
249 DO 60 j = 1, n
250 CALL zhpr( cuplo, n, -d( j ), u( 1, j ), 1, work )
251 60 CONTINUE
252*
253 IF( n.GT.1 .AND. ks.EQ.1 ) THEN
254 DO 70 j = 1, n - 1
255 CALL zhpr2( cuplo, n, -dcmplx( e( j ) ), u( 1, j ), 1,
256 $ u( 1, j+1 ), 1, work )
257 70 CONTINUE
258 END IF
259 wnorm = zlanhp( '1', cuplo, n, work, rwork )
260*
261 IF( anorm.GT.wnorm ) THEN
262 result( 1 ) = ( wnorm / anorm ) / ( n*ulp )
263 ELSE
264 IF( anorm.LT.one ) THEN
265 result( 1 ) = ( min( wnorm, n*anorm ) / anorm ) / ( n*ulp )
266 ELSE
267 result( 1 ) = min( wnorm / anorm, dble( n ) ) / ( n*ulp )
268 END IF
269 END IF
270*
271* Do Test 2
272*
273* Compute U U**H - I
274*
275 CALL zgemm( 'N', 'C', n, n, n, cone, u, ldu, u, ldu, czero, work,
276 $ n )
277*
278 DO 80 j = 1, n
279 work( ( n+1 )*( j-1 )+1 ) = work( ( n+1 )*( j-1 )+1 ) - cone
280 80 CONTINUE
281*
282 result( 2 ) = min( zlange( '1', n, n, work, n, rwork ),
283 $ dble( n ) ) / ( n*ulp )
284*
285 RETURN
286*
287* End of ZHBT21
288*
289 END
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
subroutine zhpr2(uplo, n, alpha, x, incx, y, incy, ap)
ZHPR2
Definition zhpr2.f:145
subroutine zhpr(uplo, n, alpha, x, incx, ap)
ZHPR
Definition zhpr.f:130
subroutine zhbt21(uplo, n, ka, ks, a, lda, d, e, u, ldu, work, rwork, result)
ZHBT21
Definition zhbt21.f:152