114 SUBROUTINE slacon( N, V, X, ISGN, EST, KASE )
133 parameter( itmax = 5 )
135 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
138 INTEGER I, ITER, J, JLAST, JUMP
139 REAL ALTSGN, ESTOLD, TEMP
144 EXTERNAL isamax, sasum
150 INTRINSIC abs, nint, real, sign
159 x( i ) = one / real( n )
166 GO TO ( 20, 40, 70, 110, 140 )jump
178 est = sasum( n, x, 1 )
181 x( i ) = sign( one, x( i ) )
182 isgn( i ) = nint( x( i ) )
192 j = isamax( n, x, 1 )
210 CALL scopy( n, x, 1, v, 1 )
212 est = sasum( n, v, 1 )
214 IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
226 x( i ) = sign( one, x( i ) )
227 isgn( i ) = nint( x( i ) )
238 j = isamax( n, x, 1 )
239 IF( ( x( jlast ).NE.abs( x( j ) ) ) .AND. ( iter.LT.itmax ) )
THEN
249 x( i ) = altsgn*( one+real( i-1 ) / real( n-1 ) )
260 temp = two*( sasum( n, x, 1 ) / real( 3*n ) )
261 IF( temp.GT.est )
THEN
262 CALL scopy( n, x, 1, v, 1 )
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine slacon(n, v, x, isgn, est, kase)
SLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...