LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zlacon()

subroutine zlacon ( integer  n,
complex*16, dimension( n )  v,
complex*16, dimension( n )  x,
double precision  est,
integer  kase 
)

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

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

Purpose:
 ZLACON 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 ZLACON 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 JUMP = 3, EST should be
         unchanged from the previous call to ZLACON.
         On exit, EST is an estimate (a lower bound) for norm(A).
[in,out]KASE
          KASE is INTEGER
         On the initial call to ZLACON, 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 ZLACON, KASE will again be 0.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
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 113 of file zlacon.f.

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