SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ pslacon()

subroutine pslacon ( integer  n,
real, dimension( * )  v,
integer  iv,
integer  jv,
integer, dimension( * )  descv,
real, dimension( * )  x,
integer  ix,
integer  jx,
integer, dimension( * )  descx,
integer, dimension( * )  isgn,
real  est,
integer  kase 
)

Definition at line 1 of file pslacon.f.

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, XMAX
164* ..
165* .. Local Arrays ..
166 REAL WORK( 2 )
167 REAL ESTWORK( 1 )
168 REAL TEMP( 1 )
169* ..
170* .. External Subroutines ..
171 EXTERNAL blacs_gridinfo, igsum2d, infog2l, psamax,
172 $ psasum, pselget, sgebr2d,
173 $ sgebs2d, scopy
174* ..
175* .. External Functions ..
176 INTEGER INDXG2L, INDXG2P, INDXL2G, NUMROC
177 EXTERNAL indxg2l, indxg2p, indxl2g, numroc
178* ..
179* .. Intrinsic Functions ..
180 INTRINSIC abs, mod, nint, real, sign
181* ..
182* .. Save statement ..
183 SAVE
184* ..
185* .. Executable Statements ..
186*
187* Get grid parameters.
188*
189 estwork( 1 ) = est
190 ictxt = descx( ctxt_ )
191 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
192*
193 CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol,
194 $ iivx, jjvx, ivxrow, ivxcol )
195 IF( mycol.NE.ivxcol )
196 $ RETURN
197 iroff = mod( ix-1, descx( mb_ ) )
198 np = numroc( n+iroff, descx( mb_ ), myrow, ivxrow, nprow )
199 IF( myrow.EQ.ivxrow )
200 $ np = np - iroff
201 ioffvx = iivx + (jjvx-1)*descx( lld_ )
202*
203 IF( kase.EQ.0 ) THEN
204 DO 10 i = ioffvx, ioffvx+np-1
205 x( i ) = one / real( n )
206 10 CONTINUE
207 kase = 1
208 jump = 1
209 RETURN
210 END IF
211*
212 GO TO ( 20, 40, 70, 110, 140 )jump
213*
214* ................ ENTRY (JUMP = 1)
215* FIRST ITERATION. X HAS BEEN OVERWRITTEN BY A*X
216*
217 20 CONTINUE
218 IF( n.EQ.1 ) THEN
219 IF( myrow.EQ.ivxrow ) THEN
220 v( ioffvx ) = x( ioffvx )
221 estwork( 1 ) = abs( v( ioffvx ) )
222 CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1 )
223 ELSE
224 CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1,
225 $ ivxrow, mycol )
226 END IF
227* ... QUIT
228 GO TO 150
229 END IF
230 CALL psasum( n, estwork( 1 ), x, ix, jx, descx, 1 )
231 IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
232 IF( myrow.EQ.ivxrow ) THEN
233 CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1 )
234 ELSE
235 CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1,
236 $ ivxrow, mycol )
237 END IF
238 END IF
239*
240 DO 30 i = ioffvx, ioffvx+np-1
241 x( i ) = sign( one, x( i ) )
242 isgn( i ) = nint( x( i ) )
243 30 CONTINUE
244 kase = 2
245 jump = 2
246 RETURN
247*
248* ................ ENTRY (JUMP = 2)
249* FIRST ITERATION. X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X
250*
251 40 CONTINUE
252 CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
253 IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
254 IF( myrow.EQ.ivxrow ) THEN
255 work( 1 ) = xmax
256 work( 2 ) = real( j )
257 CALL sgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
258 ELSE
259 CALL sgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
260 $ ivxrow, mycol )
261 xmax = work( 1 )
262 j = nint( work( 2 ) )
263 END IF
264 END IF
265 iter = 2
266*
267* MAIN LOOP - ITERATIONS 2, 3,...,ITMAX
268*
269 50 CONTINUE
270 DO 60 i = ioffvx, ioffvx+np-1
271 x( i ) = zero
272 60 CONTINUE
273 imaxrow = indxg2p( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
274 IF( myrow.EQ.imaxrow ) THEN
275 i = indxg2l( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
276 x( i ) = one
277 END IF
278 kase = 1
279 jump = 3
280 RETURN
281*
282* ................ ENTRY (JUMP = 3)
283* X HAS BEEN OVERWRITTEN BY A*X
284*
285 70 CONTINUE
286 CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
287 estold = estwork( 1 )
288 CALL psasum( n, estwork( 1 ), v, iv, jv, descv, 1 )
289 IF( descv( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
290 IF( myrow.EQ.ivxrow ) THEN
291 CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1 )
292 ELSE
293 CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, estwork, 1,
294 $ ivxrow, mycol )
295 END IF
296 END IF
297 iflag = 0
298 DO 80 i = ioffvx, ioffvx+np-1
299 IF( nint( sign( one, x( i ) ) ).NE.isgn( i ) ) THEN
300 iflag = 1
301 GO TO 90
302 END IF
303 80 CONTINUE
304*
305 90 CONTINUE
306 CALL igsum2d( ictxt, 'C', ' ', 1, 1, iflag, 1, -1, mycol )
307*
308* REPEATED SIGN VECTOR DETECTED, HENCE ALGORITHM HAS CONVERGED.
309* ALONG WITH IT, TEST FOR CYCLING.
310*
311 IF( iflag.EQ.0 .OR. estwork( 1 ).LE.estold )
312 $ GO TO 120
313*
314 DO 100 i = ioffvx, ioffvx+np-1
315 x( i ) = sign( one, x( i ) )
316 isgn( i ) = nint( x( i ) )
317 100 CONTINUE
318 kase = 2
319 jump = 4
320 RETURN
321*
322* ................ ENTRY (JUMP = 4)
323* X HAS BEEN OVERWRITTEN BY TRANSPOSE(A)*X
324*
325 110 CONTINUE
326 jlast = j
327 CALL psamax( n, xmax, j, x, ix, jx, descx, 1 )
328 IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
329 IF( myrow.EQ.ivxrow ) THEN
330 work( 1 ) = xmax
331 work( 2 ) = real( j )
332 CALL sgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
333 ELSE
334 CALL sgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
335 $ ivxrow, mycol )
336 xmax = work( 1 )
337 j = nint( work( 2 ) )
338 END IF
339 END IF
340 CALL pselget( 'Columnwise', ' ', jlmax, x, jlast, jx, descx )
341 IF( ( jlmax.NE.abs( xmax ) ).AND.( iter.LT.itmax ) ) THEN
342 iter = iter + 1
343 GO TO 50
344 END IF
345*
346* ITERATION COMPLETE. FINAL STAGE.
347*
348 120 CONTINUE
349 DO 130 i = ioffvx, ioffvx+np-1
350 k = indxl2g( i-ioffvx+iivx, descx( mb_ ), myrow,
351 $ descx( rsrc_ ), nprow )-ix+1
352 IF( mod( k, 2 ).EQ.0 ) THEN
353 altsgn = -one
354 ELSE
355 altsgn = one
356 END IF
357 x( i ) = altsgn*( one+real( k-1 ) / real( n-1 ) )
358 130 CONTINUE
359 kase = 1
360 jump = 5
361 RETURN
362*
363* ................ ENTRY (JUMP = 5)
364* X HAS BEEN OVERWRITTEN BY A*X
365*
366 140 CONTINUE
367 CALL psasum( n, temp( 1 ), x, ix, jx, descx, 1 )
368 IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
369 IF( myrow.EQ.ivxrow ) THEN
370 CALL sgebs2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1 )
371 ELSE
372 CALL sgebr2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1,
373 $ ivxrow, mycol )
374 END IF
375 END IF
376 temp( 1 ) = two*( temp( 1 ) / real( 3*n ) )
377 IF( temp( 1 ).GT.estwork( 1 ) ) THEN
378 CALL scopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
379 estwork( 1 ) = temp( 1 )
380 END IF
381*
382 150 CONTINUE
383 kase = 0
384*
385 est = estwork( 1 )
386 RETURN
387*
388* End of PSLACON
389*
integer function indxg2l(indxglob, nb, iproc, isrcproc, nprocs)
Definition indxg2l.f:2
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
Definition indxg2p.f:2
integer function indxl2g(indxloc, nb, iproc, isrcproc, nprocs)
Definition indxl2g.f:2
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)
Definition infog2l.f:3
integer function numroc(n, nb, iproc, isrcproc, nprocs)
Definition numroc.f:2
subroutine pselget(scope, top, alpha, a, ia, ja, desca)
Definition pselget.f:2
Here is the call graph for this function:
Here is the caller graph for this function: