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