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