LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cstt22.f
Go to the documentation of this file.
1 *> \brief \b CSTT22
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 CSTT22( N, M, KBAND, AD, AE, SD, SE, U, LDU, WORK,
12 * LDWORK, RWORK, RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER KBAND, LDU, LDWORK, M, N
16 * ..
17 * .. Array Arguments ..
18 * REAL AD( * ), AE( * ), RESULT( 2 ), RWORK( * ),
19 * $ SD( * ), SE( * )
20 * COMPLEX U( LDU, * ), WORK( LDWORK, * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> CSTT22 checks a set of M eigenvalues and eigenvectors,
30 *>
31 *> A U = U S
32 *>
33 *> where A is Hermitian tridiagonal, the columns of U are unitary,
34 *> and S is diagonal (if KBAND=0) or Hermitian tridiagonal (if KBAND=1).
35 *> Two tests are performed:
36 *>
37 *> RESULT(1) = | U* A U - S | / ( |A| m ulp )
38 *>
39 *> RESULT(2) = | I - U*U | / ( m ulp )
40 *> \endverbatim
41 *
42 * Arguments:
43 * ==========
44 *
45 *> \param[in] N
46 *> \verbatim
47 *> N is INTEGER
48 *> The size of the matrix. If it is zero, CSTT22 does nothing.
49 *> It must be at least zero.
50 *> \endverbatim
51 *>
52 *> \param[in] M
53 *> \verbatim
54 *> M is INTEGER
55 *> The number of eigenpairs to check. If it is zero, CSTT22
56 *> does nothing. It must be at least zero.
57 *> \endverbatim
58 *>
59 *> \param[in] KBAND
60 *> \verbatim
61 *> KBAND is INTEGER
62 *> The bandwidth of the matrix S. It may only be zero or one.
63 *> If zero, then S is diagonal, and SE is not referenced. If
64 *> one, then S is Hermitian tri-diagonal.
65 *> \endverbatim
66 *>
67 *> \param[in] AD
68 *> \verbatim
69 *> AD is REAL array, dimension (N)
70 *> The diagonal of the original (unfactored) matrix A. A is
71 *> assumed to be Hermitian tridiagonal.
72 *> \endverbatim
73 *>
74 *> \param[in] AE
75 *> \verbatim
76 *> AE is REAL array, dimension (N)
77 *> The off-diagonal of the original (unfactored) matrix A. A
78 *> is assumed to be Hermitian tridiagonal. AE(1) is ignored,
79 *> AE(2) is the (1,2) and (2,1) element, etc.
80 *> \endverbatim
81 *>
82 *> \param[in] SD
83 *> \verbatim
84 *> SD is REAL array, dimension (N)
85 *> The diagonal of the (Hermitian tri-) diagonal matrix S.
86 *> \endverbatim
87 *>
88 *> \param[in] SE
89 *> \verbatim
90 *> SE is REAL array, dimension (N)
91 *> The off-diagonal of the (Hermitian tri-) diagonal matrix S.
92 *> Not referenced if KBSND=0. If KBAND=1, then AE(1) is
93 *> ignored, SE(2) is the (1,2) and (2,1) element, etc.
94 *> \endverbatim
95 *>
96 *> \param[in] U
97 *> \verbatim
98 *> U is REAL array, dimension (LDU, N)
99 *> The unitary matrix in the decomposition.
100 *> \endverbatim
101 *>
102 *> \param[in] LDU
103 *> \verbatim
104 *> LDU is INTEGER
105 *> The leading dimension of U. LDU must be at least N.
106 *> \endverbatim
107 *>
108 *> \param[out] WORK
109 *> \verbatim
110 *> WORK is COMPLEX array, dimension (LDWORK, M+1)
111 *> \endverbatim
112 *>
113 *> \param[in] LDWORK
114 *> \verbatim
115 *> LDWORK is INTEGER
116 *> The leading dimension of WORK. LDWORK must be at least
117 *> max(1,M).
118 *> \endverbatim
119 *>
120 *> \param[out] RWORK
121 *> \verbatim
122 *> RWORK is REAL array, dimension (N)
123 *> \endverbatim
124 *>
125 *> \param[out] RESULT
126 *> \verbatim
127 *> RESULT is REAL array, dimension (2)
128 *> The values computed by the two tests described above. The
129 *> values are currently limited to 1/ulp, to avoid overflow.
130 *> \endverbatim
131 *
132 * Authors:
133 * ========
134 *
135 *> \author Univ. of Tennessee
136 *> \author Univ. of California Berkeley
137 *> \author Univ. of Colorado Denver
138 *> \author NAG Ltd.
139 *
140 *> \date November 2011
141 *
142 *> \ingroup complex_eig
143 *
144 * =====================================================================
145  SUBROUTINE cstt22( N, M, KBAND, AD, AE, SD, SE, U, LDU, WORK,
146  $ ldwork, rwork, result )
147 *
148 * -- LAPACK test routine (version 3.4.0) --
149 * -- LAPACK is a software package provided by Univ. of Tennessee, --
150 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
151 * November 2011
152 *
153 * .. Scalar Arguments ..
154  INTEGER KBAND, LDU, LDWORK, M, N
155 * ..
156 * .. Array Arguments ..
157  REAL AD( * ), AE( * ), RESULT( 2 ), RWORK( * ),
158  $ sd( * ), se( * )
159  COMPLEX U( ldu, * ), WORK( ldwork, * )
160 * ..
161 *
162 * =====================================================================
163 *
164 * .. Parameters ..
165  REAL ZERO, ONE
166  parameter ( zero = 0.0e0, one = 1.0e0 )
167  COMPLEX CZERO, CONE
168  parameter ( czero = ( 0.0e+0, 0.0e+0 ),
169  $ cone = ( 1.0e+0, 0.0e+0 ) )
170 * ..
171 * .. Local Scalars ..
172  INTEGER I, J, K
173  REAL ANORM, ULP, UNFL, WNORM
174  COMPLEX AUKJ
175 * ..
176 * .. External Functions ..
177  REAL CLANGE, CLANSY, SLAMCH
178  EXTERNAL clange, clansy, slamch
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL cgemm
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC abs, max, min, real
185 * ..
186 * .. Executable Statements ..
187 *
188  result( 1 ) = zero
189  result( 2 ) = zero
190  IF( n.LE.0 .OR. m.LE.0 )
191  $ RETURN
192 *
193  unfl = slamch( 'Safe minimum' )
194  ulp = slamch( 'Epsilon' )
195 *
196 * Do Test 1
197 *
198 * Compute the 1-norm of A.
199 *
200  IF( n.GT.1 ) THEN
201  anorm = abs( ad( 1 ) ) + abs( ae( 1 ) )
202  DO 10 j = 2, n - 1
203  anorm = max( anorm, abs( ad( j ) )+abs( ae( j ) )+
204  $ abs( ae( j-1 ) ) )
205  10 CONTINUE
206  anorm = max( anorm, abs( ad( n ) )+abs( ae( n-1 ) ) )
207  ELSE
208  anorm = abs( ad( 1 ) )
209  END IF
210  anorm = max( anorm, unfl )
211 *
212 * Norm of U*AU - S
213 *
214  DO 40 i = 1, m
215  DO 30 j = 1, m
216  work( i, j ) = czero
217  DO 20 k = 1, n
218  aukj = ad( k )*u( k, j )
219  IF( k.NE.n )
220  $ aukj = aukj + ae( k )*u( k+1, j )
221  IF( k.NE.1 )
222  $ aukj = aukj + ae( k-1 )*u( k-1, j )
223  work( i, j ) = work( i, j ) + u( k, i )*aukj
224  20 CONTINUE
225  30 CONTINUE
226  work( i, i ) = work( i, i ) - sd( i )
227  IF( kband.EQ.1 ) THEN
228  IF( i.NE.1 )
229  $ work( i, i-1 ) = work( i, i-1 ) - se( i-1 )
230  IF( i.NE.n )
231  $ work( i, i+1 ) = work( i, i+1 ) - se( i )
232  END IF
233  40 CONTINUE
234 *
235  wnorm = clansy( '1', 'L', m, work, m, rwork )
236 *
237  IF( anorm.GT.wnorm ) THEN
238  result( 1 ) = ( wnorm / anorm ) / ( m*ulp )
239  ELSE
240  IF( anorm.LT.one ) THEN
241  result( 1 ) = ( min( wnorm, m*anorm ) / anorm ) / ( m*ulp )
242  ELSE
243  result( 1 ) = min( wnorm / anorm, REAL( M ) ) / ( M*ULP )
244  END IF
245  END IF
246 *
247 * Do Test 2
248 *
249 * Compute U*U - I
250 *
251  CALL cgemm( 'T', 'N', m, m, n, cone, u, ldu, u, ldu, czero, work,
252  $ m )
253 *
254  DO 50 j = 1, m
255  work( j, j ) = work( j, j ) - one
256  50 CONTINUE
257 *
258  result( 2 ) = min( REAL( M ), CLANGE( '1', m, m, work, m,
259  $ rwork ) ) / ( m*ulp )
260 *
261  RETURN
262 *
263 * End of CSTT22
264 *
265  END
subroutine cstt22(N, M, KBAND, AD, AE, SD, SE, U, LDU, WORK, LDWORK, RWORK, RESULT)
CSTT22
Definition: cstt22.f:147
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189