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