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