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