131 SUBROUTINE csteqr( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
142 REAL D( * ), E( * ), WORK( * )
149 REAL ZERO, ONE, TWO, THREE
150 parameter( zero = 0.0e0, one = 1.0e0, two = 2.0e0,
153 parameter( czero = ( 0.0e0, 0.0e0 ),
154 $ cone = ( 1.0e0, 0.0e0 ) )
156 parameter( maxit = 30 )
159 INTEGER I, ICOMPZ, II, ISCALE, J, JTOT, K, L, L1, LEND,
160 $ LENDM1, LENDP1, LENDSV, LM1, LSV, M, MM, MM1,
162 REAL ANORM, B, C, EPS, EPS2, F, G, P, R, RT1, RT2,
163 $ S, SAFMAX, SAFMIN, SSFMAX, SSFMIN, TST
167 REAL SLAMCH, SLANST, SLAPY2
168 EXTERNAL lsame, slamch, slanst, slapy2
175 INTRINSIC abs, max, sign, sqrt
183 IF( lsame( compz,
'N' ) )
THEN
185 ELSE IF( lsame( compz,
'V' ) )
THEN
187 ELSE IF( lsame( compz,
'I' ) )
THEN
192 IF( icompz.LT.0 )
THEN
194 ELSE IF( n.LT.0 )
THEN
196 ELSE IF( ( ldz.LT.1 ) .OR. ( icompz.GT.0 .AND. ldz.LT.max( 1,
201 CALL xerbla(
'CSTEQR', -info )
220 safmin = slamch(
'S' )
221 safmax = one / safmin
222 ssfmax = sqrt( safmax ) / three
223 ssfmin = sqrt( safmin ) / eps2
229 $
CALL claset(
'Full', n, n, czero, cone, z, ldz )
251 IF( tst.LE.( sqrt( abs( d( m ) ) )*sqrt( abs( d( m+
252 $ 1 ) ) ) )*eps )
THEN
271 anorm = slanst(
'I', lend-l+1, d( l ), e( l ) )
275 IF( anorm.GT.ssfmax )
THEN
277 CALL slascl(
'G', 0, 0, anorm, ssfmax, lend-l+1, 1, d( l ), n,
279 CALL slascl(
'G', 0, 0, anorm, ssfmax, lend-l, 1, e( l ), n,
281 ELSE IF( anorm.LT.ssfmin )
THEN
283 CALL slascl(
'G', 0, 0, anorm, ssfmin, lend-l+1, 1, d( l ), n,
285 CALL slascl(
'G', 0, 0, anorm, ssfmin, lend-l, 1, e( l ), n,
291 IF( abs( d( lend ) ).LT.abs( d( l ) ) )
THEN
306 tst = abs( e( m ) )**2
307 IF( tst.LE.( eps2*abs( d( m ) ) )*abs( d( m+1 ) )+
325 IF( icompz.GT.0 )
THEN
326 CALL slaev2( d( l ), e( l ), d( l+1 ), rt1, rt2, c, s )
329 CALL clasr(
'R',
'V',
'B', n, 2, work( l ),
330 $ work( n-1+l ), z( 1, l ), ldz )
332 CALL slae2( d( l ), e( l ), d( l+1 ), rt1, rt2 )
349 g = ( d( l+1 )-p ) / ( two*e( l ) )
351 g = d( m ) - p + ( e( l ) / ( g+sign( r, g ) ) )
363 CALL slartg( g, f, c, s, r )
367 r = ( d( i )-g )*s + two*c*b
374 IF( icompz.GT.0 )
THEN
383 IF( icompz.GT.0 )
THEN
385 CALL clasr(
'R',
'V',
'B', n, mm, work( l ), work( n-1+l ),
412 DO 100 m = l, lendp1, -1
413 tst = abs( e( m-1 ) )**2
414 IF( tst.LE.( eps2*abs( d( m ) ) )*abs( d( m-1 ) )+
432 IF( icompz.GT.0 )
THEN
433 CALL slaev2( d( l-1 ), e( l-1 ), d( l ), rt1, rt2, c, s )
436 CALL clasr(
'R',
'V',
'F', n, 2, work( m ),
437 $ work( n-1+m ), z( 1, l-1 ), ldz )
439 CALL slae2( d( l-1 ), e( l-1 ), d( l ), rt1, rt2 )
456 g = ( d( l-1 )-p ) / ( two*e( l-1 ) )
458 g = d( m ) - p + ( e( l-1 ) / ( g+sign( r, g ) ) )
470 CALL slartg( g, f, c, s, r )
474 r = ( d( i+1 )-g )*s + two*c*b
481 IF( icompz.GT.0 )
THEN
490 IF( icompz.GT.0 )
THEN
492 CALL clasr(
'R',
'V',
'F', n, mm, work( m ), work( n-1+m ),
515 IF( iscale.EQ.1 )
THEN
516 CALL slascl(
'G', 0, 0, ssfmax, anorm, lendsv-lsv+1, 1,
517 $ d( lsv ), n, info )
518 CALL slascl(
'G', 0, 0, ssfmax, anorm, lendsv-lsv, 1, e( lsv ),
520 ELSE IF( iscale.EQ.2 )
THEN
521 CALL slascl(
'G', 0, 0, ssfmin, anorm, lendsv-lsv+1, 1,
522 $ d( lsv ), n, info )
523 CALL slascl(
'G', 0, 0, ssfmin, anorm, lendsv-lsv, 1, e( lsv ),
530 IF( jtot.EQ.nmaxit )
THEN
542 IF( icompz.EQ.0 )
THEN
546 CALL slasrt(
'I', n, d, info )
557 IF( d( j ).LT.p )
THEN
565 CALL cswap( n, z( 1, i ), 1, z( 1, k ), 1 )
subroutine xerbla(srname, info)
subroutine slae2(a, b, c, rt1, rt2)
SLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix.
subroutine slaev2(a, b, c, rt1, rt2, cs1, sn1)
SLAEV2 computes the eigenvalues and eigenvectors of a 2-by-2 symmetric/Hermitian matrix.
subroutine slartg(f, g, c, s, r)
SLARTG generates a plane rotation with real cosine and real sine.
subroutine slascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
SLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine clasr(side, pivot, direct, m, n, c, s, a, lda)
CLASR applies a sequence of plane rotations to a general rectangular matrix.
subroutine slasrt(id, n, d, info)
SLASRT sorts numbers in increasing or decreasing order.
subroutine csteqr(compz, n, d, e, z, ldz, work, info)
CSTEQR
subroutine cswap(n, cx, incx, cy, incy)
CSWAP