001:       SUBROUTINE DLACN2( N, V, X, ISGN, EST, KASE, ISAVE )
002: *
003: *  -- LAPACK auxiliary routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            KASE, N
010:       DOUBLE PRECISION   EST
011: *     ..
012: *     .. Array Arguments ..
013:       INTEGER            ISGN( * ), ISAVE( 3 )
014:       DOUBLE PRECISION   V( * ), X( * )
015: *     ..
016: *
017: *  Purpose
018: *  =======
019: *
020: *  DLACN2 estimates the 1-norm of a square, real matrix A.
021: *  Reverse communication is used for evaluating matrix-vector products.
022: *
023: *  Arguments
024: *  =========
025: *
026: *  N      (input) INTEGER
027: *         The order of the matrix.  N >= 1.
028: *
029: *  V      (workspace) DOUBLE PRECISION array, dimension (N)
030: *         On the final return, V = A*W,  where  EST = norm(V)/norm(W)
031: *         (W is not returned).
032: *
033: *  X      (input/output) DOUBLE PRECISION array, dimension (N)
034: *         On an intermediate return, X should be overwritten by
035: *               A * X,   if KASE=1,
036: *               A' * X,  if KASE=2,
037: *         and DLACN2 must be re-called with all the other parameters
038: *         unchanged.
039: *
040: *  ISGN   (workspace) INTEGER array, dimension (N)
041: *
042: *  EST    (input/output) DOUBLE PRECISION
043: *         On entry with KASE = 1 or 2 and ISAVE(1) = 3, EST should be
044: *         unchanged from the previous call to DLACN2.
045: *         On exit, EST is an estimate (a lower bound) for norm(A). 
046: *
047: *  KASE   (input/output) INTEGER
048: *         On the initial call to DLACN2, KASE should be 0.
049: *         On an intermediate return, KASE will be 1 or 2, indicating
050: *         whether X should be overwritten by A * X  or A' * X.
051: *         On the final return from DLACN2, KASE will again be 0.
052: *
053: *  ISAVE  (input/output) INTEGER array, dimension (3)
054: *         ISAVE is used to save variables between calls to DLACN2
055: *
056: *  Further Details
057: *  ======= =======
058: *
059: *  Contributed by Nick Higham, University of Manchester.
060: *  Originally named SONEST, dated March 16, 1988.
061: *
062: *  Reference: N.J. Higham, "FORTRAN codes for estimating the one-norm of
063: *  a real or complex matrix, with applications to condition estimation",
064: *  ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.
065: *
066: *  This is a thread safe version of DLACON, which uses the array ISAVE
067: *  in place of a SAVE statement, as follows:
068: *
069: *     DLACON     DLACN2
070: *      JUMP     ISAVE(1)
071: *      J        ISAVE(2)
072: *      ITER     ISAVE(3)
073: *
074: *  =====================================================================
075: *
076: *     .. Parameters ..
077:       INTEGER            ITMAX
078:       PARAMETER          ( ITMAX = 5 )
079:       DOUBLE PRECISION   ZERO, ONE, TWO
080:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
081: *     ..
082: *     .. Local Scalars ..
083:       INTEGER            I, JLAST
084:       DOUBLE PRECISION   ALTSGN, ESTOLD, TEMP
085: *     ..
086: *     .. External Functions ..
087:       INTEGER            IDAMAX
088:       DOUBLE PRECISION   DASUM
089:       EXTERNAL           IDAMAX, DASUM
090: *     ..
091: *     .. External Subroutines ..
092:       EXTERNAL           DCOPY
093: *     ..
094: *     .. Intrinsic Functions ..
095:       INTRINSIC          ABS, DBLE, NINT, SIGN
096: *     ..
097: *     .. Executable Statements ..
098: *
099:       IF( KASE.EQ.0 ) THEN
100:          DO 10 I = 1, N
101:             X( I ) = ONE / DBLE( N )
102:    10    CONTINUE
103:          KASE = 1
104:          ISAVE( 1 ) = 1
105:          RETURN
106:       END IF
107: *
108:       GO TO ( 20, 40, 70, 110, 140 )ISAVE( 1 )
109: *
110: *     ................ ENTRY   (ISAVE( 1 ) = 1)
111: *     FIRST ITERATION.  X HAS BEEN OVERWRITTEN BY A*X.
112: *
113:    20 CONTINUE
114:       IF( N.EQ.1 ) THEN
115:          V( 1 ) = X( 1 )
116:          EST = ABS( V( 1 ) )
117: *        ... QUIT
118:          GO TO 150
119:       END IF
120:       EST = DASUM( N, X, 1 )
121: *
122:       DO 30 I = 1, N
123:          X( I ) = SIGN( ONE, X( I ) )
124:          ISGN( I ) = NINT( X( I ) )
125:    30 CONTINUE
126:       KASE = 2
127:       ISAVE( 1 ) = 2
128:       RETURN
129: *
130: *     ................ ENTRY   (ISAVE( 1 ) = 2)
131: *     FIRST ITERATION.  X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
132: *
133:    40 CONTINUE
134:       ISAVE( 2 ) = IDAMAX( N, X, 1 )
135:       ISAVE( 3 ) = 2
136: *
137: *     MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
138: *
139:    50 CONTINUE
140:       DO 60 I = 1, N
141:          X( I ) = ZERO
142:    60 CONTINUE
143:       X( ISAVE( 2 ) ) = ONE
144:       KASE = 1
145:       ISAVE( 1 ) = 3
146:       RETURN
147: *
148: *     ................ ENTRY   (ISAVE( 1 ) = 3)
149: *     X HAS BEEN OVERWRITTEN BY A*X.
150: *
151:    70 CONTINUE
152:       CALL DCOPY( N, X, 1, V, 1 )
153:       ESTOLD = EST
154:       EST = DASUM( N, V, 1 )
155:       DO 80 I = 1, N
156:          IF( NINT( SIGN( ONE, X( I ) ) ).NE.ISGN( I ) )
157:      $      GO TO 90
158:    80 CONTINUE
159: *     REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
160:       GO TO 120
161: *
162:    90 CONTINUE
163: *     TEST FOR CYCLING.
164:       IF( EST.LE.ESTOLD )
165:      $   GO TO 120
166: *
167:       DO 100 I = 1, N
168:          X( I ) = SIGN( ONE, X( I ) )
169:          ISGN( I ) = NINT( X( I ) )
170:   100 CONTINUE
171:       KASE = 2
172:       ISAVE( 1 ) = 4
173:       RETURN
174: *
175: *     ................ ENTRY   (ISAVE( 1 ) = 4)
176: *     X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
177: *
178:   110 CONTINUE
179:       JLAST = ISAVE( 2 )
180:       ISAVE( 2 ) = IDAMAX( N, X, 1 )
181:       IF( ( X( JLAST ).NE.ABS( X( ISAVE( 2 ) ) ) ) .AND.
182:      $    ( ISAVE( 3 ).LT.ITMAX ) ) THEN
183:          ISAVE( 3 ) = ISAVE( 3 ) + 1
184:          GO TO 50
185:       END IF
186: *
187: *     ITERATION COMPLETE.  FINAL STAGE.
188: *
189:   120 CONTINUE
190:       ALTSGN = ONE
191:       DO 130 I = 1, N
192:          X( I ) = ALTSGN*( ONE+DBLE( I-1 ) / DBLE( N-1 ) )
193:          ALTSGN = -ALTSGN
194:   130 CONTINUE
195:       KASE = 1
196:       ISAVE( 1 ) = 5
197:       RETURN
198: *
199: *     ................ ENTRY   (ISAVE( 1 ) = 5)
200: *     X HAS BEEN OVERWRITTEN BY A*X.
201: *
202:   140 CONTINUE
203:       TEMP = TWO*( DASUM( N, X, 1 ) / DBLE( 3*N ) )
204:       IF( TEMP.GT.EST ) THEN
205:          CALL DCOPY( N, X, 1, V, 1 )
206:          EST = TEMP
207:       END IF
208: *
209:   150 CONTINUE
210:       KASE = 0
211:       RETURN
212: *
213: *     End of DLACN2
214: *
215:       END
216: