LAPACK 3.12.1
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 111 of file zlacon.f.

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