LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slacon.f
Go to the documentation of this file.
1*> \brief \b SLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vector products.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SLACON + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slacon.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slacon.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slacon.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SLACON( N, V, X, ISGN, EST, KASE )
20*
21* .. Scalar Arguments ..
22* INTEGER KASE, N
23* REAL EST
24* ..
25* .. Array Arguments ..
26* INTEGER ISGN( * )
27* REAL V( * ), X( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> SLACON estimates the 1-norm of a square, real matrix A.
37*> Reverse communication is used for evaluating matrix-vector products.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] N
44*> \verbatim
45*> N is INTEGER
46*> The order of the matrix. N >= 1.
47*> \endverbatim
48*>
49*> \param[out] V
50*> \verbatim
51*> V is REAL array, dimension (N)
52*> On the final return, V = A*W, where EST = norm(V)/norm(W)
53*> (W is not returned).
54*> \endverbatim
55*>
56*> \param[in,out] X
57*> \verbatim
58*> X is REAL array, dimension (N)
59*> On an intermediate return, X should be overwritten by
60*> A * X, if KASE=1,
61*> A**T * X, if KASE=2,
62*> and SLACON must be re-called with all the other parameters
63*> unchanged.
64*> \endverbatim
65*>
66*> \param[out] ISGN
67*> \verbatim
68*> ISGN is INTEGER array, dimension (N)
69*> \endverbatim
70*>
71*> \param[in,out] EST
72*> \verbatim
73*> EST is REAL
74*> On entry with KASE = 1 or 2 and JUMP = 3, EST should be
75*> unchanged from the previous call to SLACON.
76*> On exit, EST is an estimate (a lower bound) for norm(A).
77*> \endverbatim
78*>
79*> \param[in,out] KASE
80*> \verbatim
81*> KASE is INTEGER
82*> On the initial call to SLACON, KASE should be 0.
83*> On an intermediate return, KASE will be 1 or 2, indicating
84*> whether X should be overwritten by A * X or A**T * X.
85*> On the final return from SLACON, KASE will again be 0.
86*> \endverbatim
87*
88* Authors:
89* ========
90*
91*> \author Univ. of Tennessee
92*> \author Univ. of California Berkeley
93*> \author Univ. of Colorado Denver
94*> \author NAG Ltd.
95*
96*> \ingroup lacon
97*
98*> \par Contributors:
99* ==================
100*>
101*> Nick Higham, University of Manchester. \n
102*> Originally named SONEST, dated March 16, 1988.
103*
104*> \par References:
105* ================
106*>
107*> N.J. Higham, "FORTRAN codes for estimating the one-norm of
108*> a real or complex matrix, with applications to condition estimation",
109*> ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.
110*>
111* =====================================================================
112 SUBROUTINE slacon( N, V, X, ISGN, EST, KASE )
113*
114* -- LAPACK auxiliary routine --
115* -- LAPACK is a software package provided by Univ. of Tennessee, --
116* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117*
118* .. Scalar Arguments ..
119 INTEGER KASE, N
120 REAL EST
121* ..
122* .. Array Arguments ..
123 INTEGER ISGN( * )
124 REAL V( * ), X( * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 INTEGER ITMAX
131 parameter( itmax = 5 )
132 REAL ZERO, ONE, TWO
133 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
134* ..
135* .. Local Scalars ..
136 INTEGER I, ITER, J, JLAST, JUMP
137 REAL ALTSGN, ESTOLD, TEMP
138* ..
139* .. External Functions ..
140 INTEGER ISAMAX
141 REAL SASUM
142 EXTERNAL isamax, sasum
143* ..
144* .. External Subroutines ..
145 EXTERNAL scopy
146* ..
147* .. Intrinsic Functions ..
148 INTRINSIC abs, nint, real, sign
149* ..
150* .. Save statement ..
151 SAVE
152* ..
153* .. Executable Statements ..
154*
155 IF( kase.EQ.0 ) THEN
156 DO 10 i = 1, n
157 x( i ) = one / real( n )
158 10 CONTINUE
159 kase = 1
160 jump = 1
161 RETURN
162 END IF
163*
164 GO TO ( 20, 40, 70, 110, 140 )jump
165*
166* ................ ENTRY (JUMP = 1)
167* FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X.
168*
169 20 CONTINUE
170 IF( n.EQ.1 ) THEN
171 v( 1 ) = x( 1 )
172 est = abs( v( 1 ) )
173* ... QUIT
174 GO TO 150
175 END IF
176 est = sasum( n, x, 1 )
177*
178 DO 30 i = 1, n
179 x( i ) = sign( one, x( i ) )
180 isgn( i ) = nint( x( i ) )
181 30 CONTINUE
182 kase = 2
183 jump = 2
184 RETURN
185*
186* ................ ENTRY (JUMP = 2)
187* FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
188*
189 40 CONTINUE
190 j = isamax( n, x, 1 )
191 iter = 2
192*
193* MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
194*
195 50 CONTINUE
196 DO 60 i = 1, n
197 x( i ) = zero
198 60 CONTINUE
199 x( j ) = one
200 kase = 1
201 jump = 3
202 RETURN
203*
204* ................ ENTRY (JUMP = 3)
205* X HAS BEEN OVERWRITTEN BY A*X.
206*
207 70 CONTINUE
208 CALL scopy( n, x, 1, v, 1 )
209 estold = est
210 est = sasum( n, v, 1 )
211 DO 80 i = 1, n
212 IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
213 $ GO TO 90
214 80 CONTINUE
215* REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
216 GO TO 120
217*
218 90 CONTINUE
219* TEST FOR CYCLING.
220 IF( est.LE.estold )
221 $ GO TO 120
222*
223 DO 100 i = 1, n
224 x( i ) = sign( one, x( i ) )
225 isgn( i ) = nint( x( i ) )
226 100 CONTINUE
227 kase = 2
228 jump = 4
229 RETURN
230*
231* ................ ENTRY (JUMP = 4)
232* X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
233*
234 110 CONTINUE
235 jlast = j
236 j = isamax( n, x, 1 )
237 IF( ( x( jlast ).NE.abs( x( j ) ) ) .AND. ( iter.LT.itmax ) ) THEN
238 iter = iter + 1
239 GO TO 50
240 END IF
241*
242* ITERATION COMPLETE. FINAL STAGE.
243*
244 120 CONTINUE
245 altsgn = one
246 DO 130 i = 1, n
247 x( i ) = altsgn*( one+real( i-1 ) / real( n-1 ) )
248 altsgn = -altsgn
249 130 CONTINUE
250 kase = 1
251 jump = 5
252 RETURN
253*
254* ................ ENTRY (JUMP = 5)
255* X HAS BEEN OVERWRITTEN BY A*X.
256*
257 140 CONTINUE
258 temp = two*( sasum( n, x, 1 ) / real( 3*n ) )
259 IF( temp.GT.est ) THEN
260 CALL scopy( n, x, 1, v, 1 )
261 est = temp
262 END IF
263*
264 150 CONTINUE
265 kase = 0
266 RETURN
267*
268* End of SLACON
269*
270 END
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
Definition scopy.f:82
subroutine slacon(n, v, x, isgn, est, kase)
SLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition slacon.f:113