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

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

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

Purpose:
 DLACN2 estimates the 1-norm of a square, real 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (N)
         On an intermediate return, X should be overwritten by
               A * X,   if KASE=1,
               A**T * X,  if KASE=2,
         and DLACN2 must be re-called with all the other parameters
         unchanged.
[out]ISGN
          ISGN is INTEGER array, dimension (N)
[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 DLACN2.
         On exit, EST is an estimate (a lower bound) for norm(A). 
[in,out]KASE
          KASE is INTEGER
         On the initial call to DLACN2, 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**T * X.
         On the final return from DLACN2, KASE will again be 0.
[in,out]ISAVE
          ISAVE is INTEGER array, dimension (3)
         ISAVE is used to save variables between calls to DLACN2
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012
Further Details:
  Originally named SONEST, dated March 16, 1988.

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

     DLACON     DLACN2
      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 138 of file dlacn2.f.

138 *
139 * -- LAPACK auxiliary routine (version 3.4.2) --
140 * -- LAPACK is a software package provided by Univ. of Tennessee, --
141 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
142 * September 2012
143 *
144 * .. Scalar Arguments ..
145  INTEGER kase, n
146  DOUBLE PRECISION est
147 * ..
148 * .. Array Arguments ..
149  INTEGER isgn( * ), isave( 3 )
150  DOUBLE PRECISION v( * ), x( * )
151 * ..
152 *
153 * =====================================================================
154 *
155 * .. Parameters ..
156  INTEGER itmax
157  parameter ( itmax = 5 )
158  DOUBLE PRECISION zero, one, two
159  parameter ( zero = 0.0d+0, one = 1.0d+0, two = 2.0d+0 )
160 * ..
161 * .. Local Scalars ..
162  INTEGER i, jlast
163  DOUBLE PRECISION altsgn, estold, temp
164 * ..
165 * .. External Functions ..
166  INTEGER idamax
167  DOUBLE PRECISION dasum
168  EXTERNAL idamax, dasum
169 * ..
170 * .. External Subroutines ..
171  EXTERNAL dcopy
172 * ..
173 * .. Intrinsic Functions ..
174  INTRINSIC abs, dble, nint, sign
175 * ..
176 * .. Executable Statements ..
177 *
178  IF( kase.EQ.0 ) THEN
179  DO 10 i = 1, n
180  x( i ) = one / dble( n )
181  10 CONTINUE
182  kase = 1
183  isave( 1 ) = 1
184  RETURN
185  END IF
186 *
187  GO TO ( 20, 40, 70, 110, 140 )isave( 1 )
188 *
189 * ................ ENTRY (ISAVE( 1 ) = 1)
190 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X.
191 *
192  20 CONTINUE
193  IF( n.EQ.1 ) THEN
194  v( 1 ) = x( 1 )
195  est = abs( v( 1 ) )
196 * ... QUIT
197  GO TO 150
198  END IF
199  est = dasum( n, x, 1 )
200 *
201  DO 30 i = 1, n
202  x( i ) = sign( one, x( i ) )
203  isgn( i ) = nint( x( i ) )
204  30 CONTINUE
205  kase = 2
206  isave( 1 ) = 2
207  RETURN
208 *
209 * ................ ENTRY (ISAVE( 1 ) = 2)
210 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
211 *
212  40 CONTINUE
213  isave( 2 ) = idamax( n, x, 1 )
214  isave( 3 ) = 2
215 *
216 * MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
217 *
218  50 CONTINUE
219  DO 60 i = 1, n
220  x( i ) = zero
221  60 CONTINUE
222  x( isave( 2 ) ) = one
223  kase = 1
224  isave( 1 ) = 3
225  RETURN
226 *
227 * ................ ENTRY (ISAVE( 1 ) = 3)
228 * X HAS BEEN OVERWRITTEN BY A*X.
229 *
230  70 CONTINUE
231  CALL dcopy( n, x, 1, v, 1 )
232  estold = est
233  est = dasum( n, v, 1 )
234  DO 80 i = 1, n
235  IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
236  $ GO TO 90
237  80 CONTINUE
238 * REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
239  GO TO 120
240 *
241  90 CONTINUE
242 * TEST FOR CYCLING.
243  IF( est.LE.estold )
244  $ GO TO 120
245 *
246  DO 100 i = 1, n
247  x( i ) = sign( one, x( i ) )
248  isgn( i ) = nint( x( i ) )
249  100 CONTINUE
250  kase = 2
251  isave( 1 ) = 4
252  RETURN
253 *
254 * ................ ENTRY (ISAVE( 1 ) = 4)
255 * X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
256 *
257  110 CONTINUE
258  jlast = isave( 2 )
259  isave( 2 ) = idamax( n, x, 1 )
260  IF( ( x( jlast ).NE.abs( x( isave( 2 ) ) ) ) .AND.
261  $ ( isave( 3 ).LT.itmax ) ) THEN
262  isave( 3 ) = isave( 3 ) + 1
263  GO TO 50
264  END IF
265 *
266 * ITERATION COMPLETE. FINAL STAGE.
267 *
268  120 CONTINUE
269  altsgn = one
270  DO 130 i = 1, n
271  x( i ) = altsgn*( one+dble( i-1 ) / dble( n-1 ) )
272  altsgn = -altsgn
273  130 CONTINUE
274  kase = 1
275  isave( 1 ) = 5
276  RETURN
277 *
278 * ................ ENTRY (ISAVE( 1 ) = 5)
279 * X HAS BEEN OVERWRITTEN BY A*X.
280 *
281  140 CONTINUE
282  temp = two*( dasum( n, x, 1 ) / dble( 3*n ) )
283  IF( temp.GT.est ) THEN
284  CALL dcopy( n, x, 1, v, 1 )
285  est = temp
286  END IF
287 *
288  150 CONTINUE
289  kase = 0
290  RETURN
291 *
292 * End of DLACN2
293 *
subroutine dcopy(N, DX, INCX, DY, INCY)
DCOPY
Definition: dcopy.f:53
integer function idamax(N, DX, INCX)
IDAMAX
Definition: idamax.f:53
double precision function dasum(N, DX, INCX)
DASUM
Definition: dasum.f:53

Here is the call graph for this function:

Here is the caller graph for this function: