PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
slacn2.f
Go to the documentation of this file.
1  SUBROUTINE slacn2( N, V, X, ISGN, EST, KASE, ISAVE )
2 *
3 * -- LAPACK auxiliary routine (version 3.2) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
6 *
7 * .. Scalar Arguments ..
8  INTEGER kase, n
9  REAL est
10 * ..
11 * .. Array Arguments ..
12  INTEGER isgn( * ), isave( 3 )
13  REAL v( * ), x( * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * SLACN2 estimates the 1-norm of a square, real matrix A.
20 * Reverse communication is used for evaluating matrix-vector products.
21 *
22 * Arguments
23 * =========
24 *
25 * N (input) INTEGER
26 * The order of the matrix. N >= 1.
27 *
28 * V (workspace) REAL array, dimension (N)
29 * On the final return, V = A*W, where EST = norm(V)/norm(W)
30 * (W is not returned).
31 *
32 * X (input/output) REAL array, dimension (N)
33 * On an intermediate return, X should be overwritten by
34 * A * X, if KASE=1,
35 * A' * X, if KASE=2,
36 * and SLACN2 must be re-called with all the other parameters
37 * unchanged.
38 *
39 * ISGN (workspace) INTEGER array, dimension (N)
40 *
41 * EST (input/output) REAL
42 * On entry with KASE = 1 or 2 and ISAVE(1) = 3, EST should be
43 * unchanged from the previous call to SLACN2.
44 * On exit, EST is an estimate (a lower bound) for norm(A).
45 *
46 * KASE (input/output) INTEGER
47 * On the initial call to SLACN2, KASE should be 0.
48 * On an intermediate return, KASE will be 1 or 2, indicating
49 * whether X should be overwritten by A * X or A' * X.
50 * On the final return from SLACN2, KASE will again be 0.
51 *
52 * ISAVE (input/output) INTEGER array, dimension (3)
53 * ISAVE is used to save variables between calls to SLACN2
54 *
55 * Further Details
56 * ======= =======
57 *
58 * Contributed by Nick Higham, University of Manchester.
59 * Originally named SONEST, dated March 16, 1988.
60 *
61 * Reference: N.J. Higham, "FORTRAN codes for estimating the one-norm of
62 * a real or complex matrix, with applications to condition estimation",
63 * ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.
64 *
65 * This is a thread safe version of SLACON, which uses the array ISAVE
66 * in place of a SAVE statement, as follows:
67 *
68 * SLACON SLACN2
69 * JUMP ISAVE(1)
70 * J ISAVE(2)
71 * ITER ISAVE(3)
72 *
73 * =====================================================================
74 *
75 * .. Parameters ..
76  INTEGER itmax
77  parameter( itmax = 5 )
78  REAL zero, one, two
79  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
80 * ..
81 * .. Local Scalars ..
82  INTEGER i, jlast
83  REAL altsgn, estold, temp
84 * ..
85 * .. External Functions ..
86  INTEGER isamax
87  REAL sasum
88  EXTERNAL isamax, sasum
89 * ..
90 * .. External Subroutines ..
91  EXTERNAL scopy
92 * ..
93 * .. Intrinsic Functions ..
94  INTRINSIC abs, nint, REAL, sign
95 * ..
96 * .. Executable Statements ..
97 *
98  IF( kase.EQ.0 ) THEN
99  DO 10 i = 1, n
100  x( i ) = one / REAL( n )
101  10 continue
102  kase = 1
103  isave( 1 ) = 1
104  return
105  END IF
106 *
107  go to( 20, 40, 70, 110, 140 )isave( 1 )
108 *
109 * ................ ENTRY (ISAVE( 1 ) = 1)
110 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X.
111 *
112  20 continue
113  IF( n.EQ.1 ) THEN
114  v( 1 ) = x( 1 )
115  est = abs( v( 1 ) )
116 * ... QUIT
117  go to 150
118  END IF
119  est = sasum( n, x, 1 )
120 *
121  DO 30 i = 1, n
122  x( i ) = sign( one, x( i ) )
123  isgn( i ) = nint( x( i ) )
124  30 continue
125  kase = 2
126  isave( 1 ) = 2
127  return
128 *
129 * ................ ENTRY (ISAVE( 1 ) = 2)
130 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
131 *
132  40 continue
133  isave( 2 ) = isamax( n, x, 1 )
134  isave( 3 ) = 2
135 *
136 * MAIN LOOP - ITERATIONS 2,3,...,ITMAX.
137 *
138  50 continue
139  DO 60 i = 1, n
140  x( i ) = zero
141  60 continue
142  x( isave( 2 ) ) = one
143  kase = 1
144  isave( 1 ) = 3
145  return
146 *
147 * ................ ENTRY (ISAVE( 1 ) = 3)
148 * X HAS BEEN OVERWRITTEN BY A*X.
149 *
150  70 continue
151  CALL scopy( n, x, 1, v, 1 )
152  estold = est
153  est = sasum( n, v, 1 )
154  DO 80 i = 1, n
155  IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) )
156  $ go to 90
157  80 continue
158 * REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
159  go to 120
160 *
161  90 continue
162 * TEST FOR CYCLING.
163  IF( est.LE.estold )
164  $ go to 120
165 *
166  DO 100 i = 1, n
167  x( i ) = sign( one, x( i ) )
168  isgn( i ) = nint( x( i ) )
169  100 continue
170  kase = 2
171  isave( 1 ) = 4
172  return
173 *
174 * ................ ENTRY (ISAVE( 1 ) = 4)
175 * X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X.
176 *
177  110 continue
178  jlast = isave( 2 )
179  isave( 2 ) = isamax( n, x, 1 )
180  IF( ( x( jlast ).NE.abs( x( isave( 2 ) ) ) ) .AND.
181  $ ( isave( 3 ).LT.itmax ) ) THEN
182  isave( 3 ) = isave( 3 ) + 1
183  go to 50
184  END IF
185 *
186 * ITERATION COMPLETE. FINAL STAGE.
187 *
188  120 continue
189  altsgn = one
190  DO 130 i = 1, n
191  x( i ) = altsgn*( one+REAL( I-1 ) / REAL( N-1 ) )
192  altsgn = -altsgn
193  130 continue
194  kase = 1
195  isave( 1 ) = 5
196  return
197 *
198 * ................ ENTRY (ISAVE( 1 ) = 5)
199 * X HAS BEEN OVERWRITTEN BY A*X.
200 *
201  140 continue
202  temp = two*( sasum( n, x, 1 ) / REAL( 3*N ) )
203  IF( temp.GT.est ) THEN
204  CALL scopy( n, x, 1, v, 1 )
205  est = temp
206  END IF
207 *
208  150 continue
209  kase = 0
210  return
211 *
212 * End of SLACN2
213 *
214  END