ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pslacon.f
Go to the documentation of this file.
1  SUBROUTINE pslacon( N, V, IV, JV, DESCV, X, IX, JX, DESCX, ISGN,
2  $ EST, KASE )
3 *
4 * -- ScaLAPACK auxiliary routine (version 1.7) --
5 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6 * and University of California, Berkeley.
7 * May 1, 1997
8 *
9 * .. Scalar Arguments ..
10  INTEGER IV, IX, JV, JX, KASE, N
11  REAL EST
12 * ..
13 * .. Array Arguments ..
14  INTEGER DESCV( * ), DESCX( * ), ISGN( * )
15  REAL V( * ), X( * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * PSLACON estimates the 1-norm of a square, real distributed matrix A.
22 * Reverse communication is used for evaluating matrix-vector products.
23 * X and V are aligned with the distributed matrix A, this information
24 * is implicitly contained within IV, IX, DESCV, and DESCX.
25 *
26 * Notes
27 * =====
28 *
29 * Each global data object is described by an associated description
30 * vector. This vector stores the information required to establish
31 * the mapping between an object element and its corresponding process
32 * and memory location.
33 *
34 * Let A be a generic term for any 2D block cyclicly distributed array.
35 * Such a global array has an associated description vector DESCA.
36 * In the following comments, the character _ should be read as
37 * "of the global array".
38 *
39 * NOTATION STORED IN EXPLANATION
40 * --------------- -------------- --------------------------------------
41 * DTYPE_A(global) DESCA( DTYPE_ )The descriptor type. In this case,
42 * DTYPE_A = 1.
43 * CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
44 * the BLACS process grid A is distribu-
45 * ted over. The context itself is glo-
46 * bal, but the handle (the integer
47 * value) may vary.
48 * M_A (global) DESCA( M_ ) The number of rows in the global
49 * array A.
50 * N_A (global) DESCA( N_ ) The number of columns in the global
51 * array A.
52 * MB_A (global) DESCA( MB_ ) The blocking factor used to distribute
53 * the rows of the array.
54 * NB_A (global) DESCA( NB_ ) The blocking factor used to distribute
55 * the columns of the array.
56 * RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
57 * row of the array A is distributed.
58 * CSRC_A (global) DESCA( CSRC_ ) The process column over which the
59 * first column of the array A is
60 * distributed.
61 * LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
62 * array. LLD_A >= MAX(1,LOCr(M_A)).
63 *
64 * Let K be the number of rows or columns of a distributed matrix,
65 * and assume that its process grid has dimension p x q.
66 * LOCr( K ) denotes the number of elements of K that a process
67 * would receive if K were distributed over the p processes of its
68 * process column.
69 * Similarly, LOCc( K ) denotes the number of elements of K that a
70 * process would receive if K were distributed over the q processes of
71 * its process row.
72 * The values of LOCr() and LOCc() may be determined via a call to the
73 * ScaLAPACK tool function, NUMROC:
74 * LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
75 * LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
76 * An upper bound for these quantities may be computed by:
77 * LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
78 * LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
79 *
80 * Arguments
81 * =========
82 *
83 * N (global input) INTEGER
84 * The length of the distributed vectors V and X. N >= 0.
85 *
86 * V (local workspace) REAL pointer into the local
87 * memory to an array of dimension LOCr(N+MOD(IV-1,MB_V)). On
88 * the final return, V = A*W, where EST = norm(V)/norm(W)
89 * (W is not returned).
90 *
91 * IV (global input) INTEGER
92 * The row index in the global array V indicating the first
93 * row of sub( V ).
94 *
95 * JV (global input) INTEGER
96 * The column index in the global array V indicating the
97 * first column of sub( V ).
98 *
99 * DESCV (global and local input) INTEGER array of dimension DLEN_.
100 * The array descriptor for the distributed matrix V.
101 *
102 * X (local input/local output) REAL pointer into the
103 * local memory to an array of dimension
104 * LOCr(N+MOD(IX-1,MB_X)). On an intermediate return, X
105 * should be overwritten by
106 * A * X, if KASE=1,
107 * A' * X, if KASE=2,
108 * PSLACON must be re-called with all the other parameters
109 * unchanged.
110 *
111 * IX (global input) INTEGER
112 * The row index in the global array X indicating the first
113 * row of sub( X ).
114 *
115 * JX (global input) INTEGER
116 * The column index in the global array X indicating the
117 * first column of sub( X ).
118 *
119 * DESCX (global and local input) INTEGER array of dimension DLEN_.
120 * The array descriptor for the distributed matrix X.
121 *
122 * ISGN (local workspace) INTEGER array, dimension
123 * LOCr(N+MOD(IX-1,MB_X)). ISGN is aligned with X and V.
124 *
125 *
126 * EST (global output) REAL
127 * An estimate (a lower bound) for norm(A).
128 *
129 * KASE (local input/local output) INTEGER
130 * On the initial call to PSLACON, KASE should be 0.
131 * On an intermediate return, KASE will be 1 or 2, indicating
132 * whether X should be overwritten by A * X or A' * X.
133 * On the final return from PSLACON, KASE will again be 0.
134 *
135 * Further Details
136 * ===============
137 *
138 * The serial version SLACON has been contributed by Nick Higham,
139 * University of Manchester. It was originally named SONEST, dated
140 * March 16, 1988.
141 *
142 * Reference: N.J. Higham, "FORTRAN codes for estimating the one-norm of
143 * a real or complex matrix, with applications to condition estimation",
144 * ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.
145 *
146 * =====================================================================
147 *
148 * .. Parameters ..
149  INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
150  $ lld_, mb_, m_, nb_, n_, rsrc_
151  parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
152  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
153  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
154  INTEGER ITMAX
155  parameter( itmax = 5 )
156  REAL ZERO, ONE, TWO
157  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
158 * ..
159 * .. Local Scalars ..
160  INTEGER I, ICTXT, IFLAG, IIVX, IMAXROW, IOFFVX, IROFF,
161  $ iter, ivxcol, ivxrow, j, jlast, jjvx, jump,
162  $ k, mycol, myrow, np, npcol, nprow
163  REAL ALTSGN, ESTOLD, JLMAX, TEMP, XMAX
164 * ..
165 * .. Local Arrays ..
166  REAL WORK( 2 )
167 * ..
168 * .. External Subroutines ..
169  EXTERNAL blacs_gridinfo, igsum2d, infog2l, psamax,
170  $ psasum, pselget, sgebr2d,
171  $ sgebs2d, scopy
172 * ..
173 * .. External Functions ..
174  INTEGER INDXG2L, INDXG2P, INDXL2G, NUMROC
175  EXTERNAL indxg2l, indxg2p, indxl2g, numroc
176 * ..
177 * .. Intrinsic Functions ..
178  INTRINSIC abs, mod, nint, real, sign
179 * ..
180 * .. Save statement ..
181  SAVE
182 * ..
183 * .. Executable Statements ..
184 *
185 * Get grid parameters.
186 *
187  ictxt = descx( ctxt_ )
188  CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
189 *
190  CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol,
191  $ iivx, jjvx, ivxrow, ivxcol )
192  IF( mycol.NE.ivxcol )
193  $ RETURN
194  iroff = mod( ix-1, descx( mb_ ) )
195  np = numroc( n+iroff, descx( mb_ ), myrow, ivxrow, nprow )
196  IF( myrow.EQ.ivxrow )
197  $ np = np - iroff
198  ioffvx = iivx + (jjvx-1)*descx( lld_ )
199 *
200  IF( kase.EQ.0 ) THEN
201  DO 10 i = ioffvx, ioffvx+np-1
202  x( i ) = one / real( n )
203  10 CONTINUE
204  kase = 1
205  jump = 1
206  RETURN
207  END IF
208 *
209  GO TO ( 20, 40, 70, 110, 140 )jump
210 *
211 * ................ ENTRY (JUMP = 1)
212 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X
213 *
214  20 CONTINUE
215  IF( n.EQ.1 ) THEN
216  IF( myrow.EQ.ivxrow ) THEN
217  v( ioffvx ) = x( ioffvx )
218  est = abs( v( ioffvx ) )
219  CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
220  ELSE
221  CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
222  $ ivxrow, mycol )
223  END IF
224 * ... QUIT
225  GO TO 150
226  END IF
227  CALL psasum( n, est, x, ix, jx, descx, 1 )
228  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
229  IF( myrow.EQ.ivxrow ) THEN
230  CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
231  ELSE
232  CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
233  $ ivxrow, mycol )
234  END IF
235  END IF
236 *
237  DO 30 i = ioffvx, ioffvx+np-1
238  x( i ) = sign( one, x( i ) )
239  isgn( i ) = nint( x( i ) )
240  30 CONTINUE
241  kase = 2
242  jump = 2
243  RETURN
244 *
245 * ................ ENTRY (JUMP = 2)
246 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X
247 *
248  40 CONTINUE
249  CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
250  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
251  IF( myrow.EQ.ivxrow ) THEN
252  work( 1 ) = xmax
253  work( 2 ) = real( j )
254  CALL sgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
255  ELSE
256  CALL sgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
257  $ ivxrow, mycol )
258  xmax = work( 1 )
259  j = nint( work( 2 ) )
260  END IF
261  END IF
262  iter = 2
263 *
264 * MAIN LOOP - ITERATIONS 2, 3,...,ITMAX
265 *
266  50 CONTINUE
267  DO 60 i = ioffvx, ioffvx+np-1
268  x( i ) = zero
269  60 CONTINUE
270  imaxrow = indxg2p( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
271  IF( myrow.EQ.imaxrow ) THEN
272  i = indxg2l( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
273  x( i ) = one
274  END IF
275  kase = 1
276  jump = 3
277  RETURN
278 *
279 * ................ ENTRY (JUMP = 3)
280 * X HAS BEEN OVERWRITTEN BY A*X
281 *
282  70 CONTINUE
283  CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
284  estold = est
285  CALL psasum( n, est, v, iv, jv, descv, 1 )
286  IF( descv( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
287  IF( myrow.EQ.ivxrow ) THEN
288  CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
289  ELSE
290  CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
291  $ ivxrow, mycol )
292  END IF
293  END IF
294  iflag = 0
295  DO 80 i = ioffvx, ioffvx+np-1
296  IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) ) THEN
297  iflag = 1
298  GO TO 90
299  END IF
300  80 CONTINUE
301 *
302  90 CONTINUE
303  CALL igsum2d( ictxt, 'C', ' ', 1, 1, iflag, 1, -1, mycol )
304 *
305 * REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
306 * ALONG WITH IT, TEST FOR CYCLING.
307 *
308  IF( iflag.EQ.0 .OR. est.LE.estold )
309  $ GO TO 120
310 *
311  DO 100 i = ioffvx, ioffvx+np-1
312  x( i ) = sign( one, x( i ) )
313  isgn( i ) = nint( x( i ) )
314  100 CONTINUE
315  kase = 2
316  jump = 4
317  RETURN
318 *
319 * ................ ENTRY (JUMP = 4)
320 * X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X
321 *
322  110 CONTINUE
323  jlast = j
324  CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
325  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
326  IF( myrow.EQ.ivxrow ) THEN
327  work( 1 ) = xmax
328  work( 2 ) = real( j )
329  CALL sgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
330  ELSE
331  CALL sgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
332  $ ivxrow, mycol )
333  xmax = work( 1 )
334  j = nint( work( 2 ) )
335  END IF
336  END IF
337  CALL pselget( 'Columnwise', ' ', jlmax, x, jlast, jx, descx )
338  IF( ( jlmax.NE.abs( xmax ) ).AND.( iter.LT.itmax ) ) THEN
339  iter = iter + 1
340  GO TO 50
341  END IF
342 *
343 * ITERATION COMPLETE. FINAL STAGE.
344 *
345  120 CONTINUE
346  DO 130 i = ioffvx, ioffvx+np-1
347  k = indxl2g( i-ioffvx+iivx, descx( mb_ ), myrow,
348  $ descx( rsrc_ ), nprow )-ix+1
349  IF( mod( k, 2 ).EQ.0 ) THEN
350  altsgn = -one
351  ELSE
352  altsgn = one
353  END IF
354  x( i ) = altsgn*( one+real( k-1 ) / real( n-1 ) )
355  130 CONTINUE
356  kase = 1
357  jump = 5
358  RETURN
359 *
360 * ................ ENTRY (JUMP = 5)
361 * X HAS BEEN OVERWRITTEN BY A*X
362 *
363  140 CONTINUE
364  CALL psasum( n, temp, x, ix, jx, descx, 1 )
365  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
366  IF( myrow.EQ.ivxrow ) THEN
367  CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1 )
368  ELSE
369  CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1,
370  $ ivxrow, mycol )
371  END IF
372  END IF
373  temp = two*( temp / real( 3*n ) )
374  IF( temp.GT.est ) THEN
375  CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
376  est = temp
377  END IF
378 *
379  150 CONTINUE
380  kase = 0
381 *
382  RETURN
383 *
384 * End of PSLACON
385 *
386  END
infog2l
subroutine infog2l(GRINDX, GCINDX, DESC, NPROW, NPCOL, MYROW, MYCOL, LRINDX, LCINDX, RSRC, CSRC)
Definition: infog2l.f:3
pslacon
subroutine pslacon(N, V, IV, JV, DESCV, X, IX, JX, DESCX, ISGN, EST, KASE)
Definition: pslacon.f:3
pselget
subroutine pselget(SCOPE, TOP, ALPHA, A, IA, JA, DESCA)
Definition: pselget.f:2