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