LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zlacn2 ( integer  N,
complex*16, dimension( * )  V,
complex*16, dimension( * )  X,
double precision  EST,
integer  KASE,
integer, dimension( 3 )  ISAVE 
)

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

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

Purpose:
 ZLACN2 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*16 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*16 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 ZLACN2 must be
         re-called with all the other parameters unchanged.
[in,out]EST
          EST is DOUBLE PRECISION
         On entry with KASE = 1 or 2 and ISAVE(1) = 3, EST should be
         unchanged from the previous call to ZLACN2.
         On exit, EST is an estimate (a lower bound) for norm(A). 
[in,out]KASE
          KASE is INTEGER
         On the initial call to ZLACN2, 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 ZLACN2, KASE will again be 0.
[in,out]ISAVE
          ISAVE is INTEGER array, dimension (3)
         ISAVE is used to save variables between calls to ZLACN2
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

  This is a thread safe version of ZLACON, which uses the array ISAVE
  in place of a SAVE statement, as follows:

     ZLACON     ZLACN2
      JUMP     ISAVE(1)
      J        ISAVE(2)
      ITER     ISAVE(3)
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 135 of file zlacn2.f.

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  DOUBLE PRECISION est
144 * ..
145 * .. Array Arguments ..
146  INTEGER isave( 3 )
147  COMPLEX*16 v( * ), x( * )
148 * ..
149 *
150 * =====================================================================
151 *
152 * .. Parameters ..
153  INTEGER itmax
154  parameter ( itmax = 5 )
155  DOUBLE PRECISION one, two
156  parameter ( one = 1.0d0, two = 2.0d0 )
157  COMPLEX*16 czero, cone
158  parameter ( czero = ( 0.0d0, 0.0d0 ),
159  $ cone = ( 1.0d0, 0.0d0 ) )
160 * ..
161 * .. Local Scalars ..
162  INTEGER i, jlast
163  DOUBLE PRECISION absxi, altsgn, estold, safmin, temp
164 * ..
165 * .. External Functions ..
166  INTEGER izmax1
167  DOUBLE PRECISION dlamch, dzsum1
168  EXTERNAL izmax1, dlamch, dzsum1
169 * ..
170 * .. External Subroutines ..
171  EXTERNAL zcopy
172 * ..
173 * .. Intrinsic Functions ..
174  INTRINSIC abs, dble, dcmplx, dimag
175 * ..
176 * .. Executable Statements ..
177 *
178  safmin = dlamch( 'Safe minimum' )
179  IF( kase.EQ.0 ) THEN
180  DO 10 i = 1, n
181  x( i ) = dcmplx( one / dble( 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 = dzsum1( n, x, 1 )
201 *
202  DO 30 i = 1, n
203  absxi = abs( x( i ) )
204  IF( absxi.GT.safmin ) THEN
205  x( i ) = dcmplx( dble( x( i ) ) / absxi,
206  $ dimag( 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 ) = izmax1( 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 zcopy( n, x, 1, v, 1 )
238  estold = est
239  est = dzsum1( 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 ) = dcmplx( dble( x( i ) ) / absxi,
249  $ dimag( 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 ) = izmax1( 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 ) = dcmplx( altsgn*( one+dble( i-1 ) / dble( 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*( dzsum1( n, x, 1 ) / dble( 3*n ) )
287  IF( temp.GT.est ) THEN
288  CALL zcopy( n, x, 1, v, 1 )
289  est = temp
290  END IF
291 *
292  130 CONTINUE
293  kase = 0
294  RETURN
295 *
296 * End of ZLACN2
297 *
integer function izmax1(N, ZX, INCX)
IZMAX1 finds the index of the first vector element of maximum absolute value.
Definition: izmax1.f:83
subroutine zcopy(N, ZX, INCX, ZY, INCY)
ZCOPY
Definition: zcopy.f:52
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
double precision function dzsum1(N, CX, INCX)
DZSUM1 forms the 1-norm of the complex vector using the true absolute value.
Definition: dzsum1.f:83

Here is the call graph for this function:

Here is the caller graph for this function: