LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cstt22()

subroutine cstt22 ( integer  n,
integer  m,
integer  kband,
real, dimension( * )  ad,
real, dimension( * )  ae,
real, dimension( * )  sd,
real, dimension( * )  se,
complex, dimension( ldu, * )  u,
integer  ldu,
complex, dimension( ldwork, * )  work,
integer  ldwork,
real, dimension( * )  rwork,
real, dimension( 2 )  result 
)

CSTT22

Purpose:
 CSTT22  checks a set of M eigenvalues and eigenvectors,

     A U = U S

 where A is Hermitian tridiagonal, the columns of U are unitary,
 and S is diagonal (if KBAND=0) or Hermitian tridiagonal (if KBAND=1).
 Two tests are performed:

    RESULT(1) = | U* A U - S | / ( |A| m ulp )

    RESULT(2) = | I - U*U | / ( m ulp )
Parameters
[in]N
          N is INTEGER
          The size of the matrix.  If it is zero, CSTT22 does nothing.
          It must be at least zero.
[in]M
          M is INTEGER
          The number of eigenpairs to check.  If it is zero, CSTT22
          does nothing.  It must be at least zero.
[in]KBAND
          KBAND is INTEGER
          The bandwidth of the matrix S.  It may only be zero or one.
          If zero, then S is diagonal, and SE is not referenced.  If
          one, then S is Hermitian tri-diagonal.
[in]AD
          AD is REAL array, dimension (N)
          The diagonal of the original (unfactored) matrix A.  A is
          assumed to be Hermitian tridiagonal.
[in]AE
          AE is REAL array, dimension (N)
          The off-diagonal of the original (unfactored) matrix A.  A
          is assumed to be Hermitian tridiagonal.  AE(1) is ignored,
          AE(2) is the (1,2) and (2,1) element, etc.
[in]SD
          SD is REAL array, dimension (N)
          The diagonal of the (Hermitian tri-) diagonal matrix S.
[in]SE
          SE is REAL array, dimension (N)
          The off-diagonal of the (Hermitian tri-) diagonal matrix S.
          Not referenced if KBSND=0.  If KBAND=1, then AE(1) is
          ignored, SE(2) is the (1,2) and (2,1) element, etc.
[in]U
          U is REAL array, dimension (LDU, N)
          The unitary matrix in the decomposition.
[in]LDU
          LDU is INTEGER
          The leading dimension of U.  LDU must be at least N.
[out]WORK
          WORK is COMPLEX array, dimension (LDWORK, M+1)
[in]LDWORK
          LDWORK is INTEGER
          The leading dimension of WORK.  LDWORK must be at least
          max(1,M).
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESULT
          RESULT is REAL array, dimension (2)
          The values computed by the two tests described above.  The
          values are currently limited to 1/ulp, to avoid overflow.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 143 of file cstt22.f.

145*
146* -- LAPACK test routine --
147* -- LAPACK is a software package provided by Univ. of Tennessee, --
148* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149*
150* .. Scalar Arguments ..
151 INTEGER KBAND, LDU, LDWORK, M, N
152* ..
153* .. Array Arguments ..
154 REAL AD( * ), AE( * ), RESULT( 2 ), RWORK( * ),
155 $ SD( * ), SE( * )
156 COMPLEX U( LDU, * ), WORK( LDWORK, * )
157* ..
158*
159* =====================================================================
160*
161* .. Parameters ..
162 REAL ZERO, ONE
163 parameter( zero = 0.0e0, one = 1.0e0 )
164 COMPLEX CZERO, CONE
165 parameter( czero = ( 0.0e+0, 0.0e+0 ),
166 $ cone = ( 1.0e+0, 0.0e+0 ) )
167* ..
168* .. Local Scalars ..
169 INTEGER I, J, K
170 REAL ANORM, ULP, UNFL, WNORM
171 COMPLEX AUKJ
172* ..
173* .. External Functions ..
174 REAL CLANGE, CLANSY, SLAMCH
175 EXTERNAL clange, clansy, slamch
176* ..
177* .. External Subroutines ..
178 EXTERNAL cgemm
179* ..
180* .. Intrinsic Functions ..
181 INTRINSIC abs, max, min, real
182* ..
183* .. Executable Statements ..
184*
185 result( 1 ) = zero
186 result( 2 ) = zero
187 IF( n.LE.0 .OR. m.LE.0 )
188 $ RETURN
189*
190 unfl = slamch( 'Safe minimum' )
191 ulp = slamch( 'Epsilon' )
192*
193* Do Test 1
194*
195* Compute the 1-norm of A.
196*
197 IF( n.GT.1 ) THEN
198 anorm = abs( ad( 1 ) ) + abs( ae( 1 ) )
199 DO 10 j = 2, n - 1
200 anorm = max( anorm, abs( ad( j ) )+abs( ae( j ) )+
201 $ abs( ae( j-1 ) ) )
202 10 CONTINUE
203 anorm = max( anorm, abs( ad( n ) )+abs( ae( n-1 ) ) )
204 ELSE
205 anorm = abs( ad( 1 ) )
206 END IF
207 anorm = max( anorm, unfl )
208*
209* Norm of U*AU - S
210*
211 DO 40 i = 1, m
212 DO 30 j = 1, m
213 work( i, j ) = czero
214 DO 20 k = 1, n
215 aukj = ad( k )*u( k, j )
216 IF( k.NE.n )
217 $ aukj = aukj + ae( k )*u( k+1, j )
218 IF( k.NE.1 )
219 $ aukj = aukj + ae( k-1 )*u( k-1, j )
220 work( i, j ) = work( i, j ) + u( k, i )*aukj
221 20 CONTINUE
222 30 CONTINUE
223 work( i, i ) = work( i, i ) - sd( i )
224 IF( kband.EQ.1 ) THEN
225 IF( i.NE.1 )
226 $ work( i, i-1 ) = work( i, i-1 ) - se( i-1 )
227 IF( i.NE.n )
228 $ work( i, i+1 ) = work( i, i+1 ) - se( i )
229 END IF
230 40 CONTINUE
231*
232 wnorm = clansy( '1', 'L', m, work, m, rwork )
233*
234 IF( anorm.GT.wnorm ) THEN
235 result( 1 ) = ( wnorm / anorm ) / ( m*ulp )
236 ELSE
237 IF( anorm.LT.one ) THEN
238 result( 1 ) = ( min( wnorm, m*anorm ) / anorm ) / ( m*ulp )
239 ELSE
240 result( 1 ) = min( wnorm / anorm, real( m ) ) / ( m*ulp )
241 END IF
242 END IF
243*
244* Do Test 2
245*
246* Compute U*U - I
247*
248 CALL cgemm( 'T', 'N', m, m, n, cone, u, ldu, u, ldu, czero, work,
249 $ m )
250*
251 DO 50 j = 1, m
252 work( j, j ) = work( j, j ) - one
253 50 CONTINUE
254*
255 result( 2 ) = min( real( m ), clange( '1', m, m, work, m,
256 $ rwork ) ) / ( m*ulp )
257*
258 RETURN
259*
260* End of CSTT22
261*
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
Definition cgemm.f:188
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function clange(norm, m, n, a, lda, work)
CLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition clange.f:115
real function clansy(norm, uplo, n, a, lda, work)
CLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition clansy.f:123
Here is the call graph for this function:
Here is the caller graph for this function: