LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine clacon ( integer  N,
complex, dimension( n )  V,
complex, dimension( n )  X,
real  EST,
integer  KASE 
)

CLACON estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vector products.

Download CLACON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CLACON estimates the 1-norm of a square, complex matrix A.
 Reverse communication is used for evaluating matrix-vector products.
Parameters
[in]N
          N is INTEGER
         The order of the matrix.  N >= 1.
[out]V
          V is COMPLEX array, dimension (N)
         On the final return, V = A*W,  where  EST = norm(V)/norm(W)
         (W is not returned).
[in,out]X
          X is COMPLEX array, dimension (N)
         On an intermediate return, X should be overwritten by
               A * X,   if KASE=1,
               A**H * X,  if KASE=2,
         where A**H is the conjugate transpose of A, and CLACON must be
         re-called with all the other parameters unchanged.
[in,out]EST
          EST is REAL
         On entry with KASE = 1 or 2 and JUMP = 3, EST should be
         unchanged from the previous call to CLACON.
         On exit, EST is an estimate (a lower bound) for norm(A). 
[in,out]KASE
          KASE is INTEGER
         On the initial call to CLACON, KASE should be 0.
         On an intermediate return, KASE will be 1 or 2, indicating
         whether X should be overwritten by A * X  or A**H * X.
         On the final return from CLACON, KASE will again be 0.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012
Further Details:
Originally named CONEST, dated March 16, 1988.
Last modified: April, 1999
Contributors:
Nick Higham, University of Manchester
References:
N.J. Higham, "FORTRAN codes for estimating the one-norm of a real or complex matrix, with applications to condition estimation", ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.

Definition at line 116 of file clacon.f.

116 *
117 * -- LAPACK auxiliary routine (version 3.4.2) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120 * September 2012
121 *
122 * .. Scalar Arguments ..
123  INTEGER kase, n
124  REAL est
125 * ..
126 * .. Array Arguments ..
127  COMPLEX v( n ), x( n )
128 * ..
129 *
130 * =====================================================================
131 *
132 * .. Parameters ..
133  INTEGER itmax
134  parameter ( itmax = 5 )
135  REAL one, two
136  parameter ( one = 1.0e0, two = 2.0e0 )
137  COMPLEX czero, cone
138  parameter ( czero = ( 0.0e0, 0.0e0 ),
139  $ cone = ( 1.0e0, 0.0e0 ) )
140 * ..
141 * .. Local Scalars ..
142  INTEGER i, iter, j, jlast, jump
143  REAL absxi, altsgn, estold, safmin, temp
144 * ..
145 * .. External Functions ..
146  INTEGER icmax1
147  REAL scsum1, slamch
148  EXTERNAL icmax1, scsum1, slamch
149 * ..
150 * .. External Subroutines ..
151  EXTERNAL ccopy
152 * ..
153 * .. Intrinsic Functions ..
154  INTRINSIC abs, aimag, cmplx, real
155 * ..
156 * .. Save statement ..
157  SAVE
158 * ..
159 * .. Executable Statements ..
160 *
161  safmin = slamch( 'Safe minimum' )
162  IF( kase.EQ.0 ) THEN
163  DO 10 i = 1, n
164  x( i ) = cmplx( one / REAL( N ) )
165  10 CONTINUE
166  kase = 1
167  jump = 1
168  RETURN
169  END IF
170 *
171  GO TO ( 20, 40, 70, 90, 120 )jump
172 *
173 * ................ ENTRY (JUMP = 1)
174 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X.
175 *
176  20 CONTINUE
177  IF( n.EQ.1 ) THEN
178  v( 1 ) = x( 1 )
179  est = abs( v( 1 ) )
180 * ... QUIT
181  GO TO 130
182  END IF
183  est = scsum1( n, x, 1 )
184 *
185  DO 30 i = 1, n
186  absxi = abs( x( i ) )
187  IF( absxi.GT.safmin ) THEN
188  x( i ) = cmplx( REAL( X( I ) ) / absxi,
189  $ aimag( x( i ) ) / absxi )
190  ELSE
191  x( i ) = cone
192  END IF
193  30 CONTINUE
194  kase = 2
195  jump = 2
196  RETURN
197 *
198 * ................ ENTRY (JUMP = 2)
199 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY CTRANS(A)*X.
200 *
201  40 CONTINUE
202  j = icmax1( n, x, 1 )
203  iter = 2
204 *
205 * MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
206 *
207  50 CONTINUE
208  DO 60 i = 1, n
209  x( i ) = czero
210  60 CONTINUE
211  x( j ) = cone
212  kase = 1
213  jump = 3
214  RETURN
215 *
216 * ................ ENTRY (JUMP = 3)
217 * X HAS BEEN OVERWRITTEN BY A*X.
218 *
219  70 CONTINUE
220  CALL ccopy( n, x, 1, v, 1 )
221  estold = est
222  est = scsum1( n, v, 1 )
223 *
224 * TEST FOR CYCLING.
225  IF( est.LE.estold )
226  $ GO TO 100
227 *
228  DO 80 i = 1, n
229  absxi = abs( x( i ) )
230  IF( absxi.GT.safmin ) THEN
231  x( i ) = cmplx( REAL( X( I ) ) / absxi,
232  $ aimag( x( i ) ) / absxi )
233  ELSE
234  x( i ) = cone
235  END IF
236  80 CONTINUE
237  kase = 2
238  jump = 4
239  RETURN
240 *
241 * ................ ENTRY (JUMP = 4)
242 * X HAS BEEN OVERWRITTEN BY CTRANS(A)*X.
243 *
244  90 CONTINUE
245  jlast = j
246  j = icmax1( n, x, 1 )
247  IF( ( abs( x( jlast ) ).NE.abs( x( j ) ) ) .AND.
248  $ ( iter.LT.itmax ) ) THEN
249  iter = iter + 1
250  GO TO 50
251  END IF
252 *
253 * ITERATION COMPLETE. FINAL STAGE.
254 *
255  100 CONTINUE
256  altsgn = one
257  DO 110 i = 1, n
258  x( i ) = cmplx( altsgn*( one+REAL( I-1 ) / REAL( N-1 ) ) )
259  altsgn = -altsgn
260  110 CONTINUE
261  kase = 1
262  jump = 5
263  RETURN
264 *
265 * ................ ENTRY (JUMP = 5)
266 * X HAS BEEN OVERWRITTEN BY A*X.
267 *
268  120 CONTINUE
269  temp = two*( scsum1( n, x, 1 ) / REAL( 3*N ) )
270  IF( temp.GT.est ) THEN
271  CALL ccopy( n, x, 1, v, 1 )
272  est = temp
273  END IF
274 *
275  130 CONTINUE
276  kase = 0
277  RETURN
278 *
279 * End of CLACON
280 *
integer function icmax1(N, CX, INCX)
ICMAX1 finds the index of the first vector element of maximum absolute value.
Definition: icmax1.f:83
real function scsum1(N, CX, INCX)
SCSUM1 forms the 1-norm of the complex vector using the true absolute value.
Definition: scsum1.f:83
subroutine ccopy(N, CX, INCX, CY, INCY)
CCOPY
Definition: ccopy.f:52
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the call graph for this function: