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