LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ slacon()

subroutine slacon ( integer  N,
real, dimension( * )  V,
real, dimension( * )  X,
integer, dimension( * )  ISGN,
real  EST,
integer  KASE 
)

SLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vector products.

Download SLACON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 SLACON estimates the 1-norm of a square, real matrix A.
 Reverse communication is used for evaluating matrix-vector products.
Parameters
[in]N
          N is INTEGER
         The order of the matrix.  N >= 1.
[out]V
          V is REAL array, dimension (N)
         On the final return, V = A*W,  where  EST = norm(V)/norm(W)
         (W is not returned).
[in,out]X
          X is REAL array, dimension (N)
         On an intermediate return, X should be overwritten by
               A * X,   if KASE=1,
               A**T * X,  if KASE=2,
         and SLACON must be re-called with all the other parameters
         unchanged.
[out]ISGN
          ISGN is INTEGER array, dimension (N)
[in,out]EST
          EST is REAL
         On entry with KASE = 1 or 2 and JUMP = 3, EST should be
         unchanged from the previous call to SLACON.
         On exit, EST is an estimate (a lower bound) for norm(A).
[in,out]KASE
          KASE is INTEGER
         On the initial call to SLACON, KASE should be 0.
         On an intermediate return, KASE will be 1 or 2, indicating
         whether X should be overwritten by A * X  or A**T * X.
         On the final return from SLACON, KASE will again be 0.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
December 2016
Contributors:
Nick Higham, University of Manchester.
Originally named SONEST, dated March 16, 1988.
References:
N.J. Higham, "FORTRAN codes for estimating the one-norm of a real or complex matrix, with applications to condition estimation", ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.

Definition at line 117 of file slacon.f.

117 *
118 * -- LAPACK auxiliary routine (version 3.7.0) --
119 * -- LAPACK is a software package provided by Univ. of Tennessee, --
120 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
121 * December 2016
122 *
123 * .. Scalar Arguments ..
124  INTEGER KASE, N
125  REAL EST
126 * ..
127 * .. Array Arguments ..
128  INTEGER ISGN( * )
129  REAL V( * ), X( * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  INTEGER ITMAX
136  parameter( itmax = 5 )
137  REAL ZERO, ONE, TWO
138  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
139 * ..
140 * .. Local Scalars ..
141  INTEGER I, ITER, J, JLAST, JUMP
142  REAL ALTSGN, ESTOLD, TEMP
143 * ..
144 * .. External Functions ..
145  INTEGER ISAMAX
146  REAL SASUM
147  EXTERNAL isamax, sasum
148 * ..
149 * .. External Subroutines ..
150  EXTERNAL scopy
151 * ..
152 * .. Intrinsic Functions ..
153  INTRINSIC abs, nint, real, sign
154 * ..
155 * .. Save statement ..
156  SAVE
157 * ..
158 * .. Executable Statements ..
159 *
160  IF( kase.EQ.0 ) THEN
161  DO 10 i = 1, n
162  x( i ) = one / real( n )
163  10 CONTINUE
164  kase = 1
165  jump = 1
166  RETURN
167  END IF
168 *
169  GO TO ( 20, 40, 70, 110, 140 )jump
170 *
171 * ................ ENTRY (JUMP = 1)
172 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X.
173 *
174  20 CONTINUE
175  IF( n.EQ.1 ) THEN
176  v( 1 ) = x( 1 )
177  est = abs( v( 1 ) )
178 * ... QUIT
179  GO TO 150
180  END IF
181  est = sasum( n, x, 1 )
182 *
183  DO 30 i = 1, n
184  x( i ) = sign( one, x( i ) )
185  isgn( i ) = nint( x( i ) )
186  30 CONTINUE
187  kase = 2
188  jump = 2
189  RETURN
190 *
191 * ................ ENTRY (JUMP = 2)
192 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
193 *
194  40 CONTINUE
195  j = isamax( n, x, 1 )
196  iter = 2
197 *
198 * MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
199 *
200  50 CONTINUE
201  DO 60 i = 1, n
202  x( i ) = zero
203  60 CONTINUE
204  x( j ) = one
205  kase = 1
206  jump = 3
207  RETURN
208 *
209 * ................ ENTRY (JUMP = 3)
210 * X HAS BEEN OVERWRITTEN BY A*X.
211 *
212  70 CONTINUE
213  CALL scopy( n, x, 1, v, 1 )
214  estold = est
215  est = sasum( n, v, 1 )
216  DO 80 i = 1, n
217  IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
218  $ GO TO 90
219  80 CONTINUE
220 * REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
221  GO TO 120
222 *
223  90 CONTINUE
224 * TEST FOR CYCLING.
225  IF( est.LE.estold )
226  $ GO TO 120
227 *
228  DO 100 i = 1, n
229  x( i ) = sign( one, x( i ) )
230  isgn( i ) = nint( x( i ) )
231  100 CONTINUE
232  kase = 2
233  jump = 4
234  RETURN
235 *
236 * ................ ENTRY (JUMP = 4)
237 * X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
238 *
239  110 CONTINUE
240  jlast = j
241  j = isamax( n, x, 1 )
242  IF( ( x( jlast ).NE.abs( x( j ) ) ) .AND. ( iter.LT.itmax ) ) THEN
243  iter = iter + 1
244  GO TO 50
245  END IF
246 *
247 * ITERATION COMPLETE. FINAL STAGE.
248 *
249  120 CONTINUE
250  altsgn = one
251  DO 130 i = 1, n
252  x( i ) = altsgn*( one+real( i-1 ) / real( n-1 ) )
253  altsgn = -altsgn
254  130 CONTINUE
255  kase = 1
256  jump = 5
257  RETURN
258 *
259 * ................ ENTRY (JUMP = 5)
260 * X HAS BEEN OVERWRITTEN BY A*X.
261 *
262  140 CONTINUE
263  temp = two*( sasum( n, x, 1 ) / real( 3*n ) )
264  IF( temp.GT.est ) THEN
265  CALL scopy( n, x, 1, v, 1 )
266  est = temp
267  END IF
268 *
269  150 CONTINUE
270  kase = 0
271  RETURN
272 *
273 * End of SLACON
274 *
Here is the call graph for this function:
sasum
real function sasum(N, SX, INCX)
SASUM
Definition: sasum.f:74
isamax
integer function isamax(N, SX, INCX)
ISAMAX
Definition: isamax.f:73
scopy
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:84