112 SUBROUTINE slacon( N, V, X, ISGN, EST, KASE )
131 parameter( itmax = 5 )
133 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
136 INTEGER I, ITER, J, JLAST, JUMP
137 REAL ALTSGN, ESTOLD, TEMP
142 EXTERNAL isamax, sasum
148 INTRINSIC abs, nint, real, sign
157 x( i ) = one / real( n )
164 GO TO ( 20, 40, 70, 110, 140 )jump
176 est = sasum( n, x, 1 )
179 x( i ) = sign( one, x( i ) )
180 isgn( i ) = nint( x( i ) )
190 j = isamax( n, x, 1 )
208 CALL scopy( n, x, 1, v, 1 )
210 est = sasum( n, v, 1 )
212 IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
224 x( i ) = sign( one, x( i ) )
225 isgn( i ) = nint( x( i ) )
236 j = isamax( n, x, 1 )
237 IF( ( x( jlast ).NE.abs( x( j ) ) ) .AND. ( iter.LT.itmax ) )
THEN
247 x( i ) = altsgn*( one+real( i-1 ) / real( n-1 ) )
258 temp = two*( sasum( n, x, 1 ) / real( 3*n ) )
259 IF( temp.GT.est )
THEN
260 CALL scopy( n, x, 1, v, 1 )
subroutine slacon(n, v, x, isgn, est, kase)
SLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...