ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pzlacon.f
Go to the documentation of this file.
1  SUBROUTINE pzlacon( N, V, IV, JV, DESCV, X, IX, JX, DESCX, EST,
2  $ 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( * )
15  COMPLEX*16 V( * ), X( * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * PZLACON estimates the 1-norm of a square, complex distributed matrix
22 * A. Reverse communication is used for evaluating matrix-vector
23 * products. X and V are aligned with the distributed matrix A, this
24 * information 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) COMPLEX*16 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) COMPLEX*16 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 * where A' is the conjugate transpose of A, and PZLACON must
109 * be re-called with all the other parameters 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 *
123 * EST (global output) DOUBLE PRECISION
124 * An estimate (a lower bound) for norm(A).
125 *
126 * KASE (local input/local output) INTEGER
127 * On the initial call to PZLACON, KASE should be 0.
128 * On an intermediate return, KASE will be 1 or 2, indicating
129 * whether X should be overwritten by A * X or A' * X.
130 * On the final return from PZLACON, KASE will again be 0.
131 *
132 * Further Details
133 * ===============
134 *
135 * The serial version ZLACON has been contributed by Nick Higham,
136 * University of Manchester. It was originally named SONEST, dated
137 * March 16, 1988.
138 *
139 * Reference: N.J. Higham, "FORTRAN codes for estimating the one-norm of
140 * a real or complex matrix, with applications to condition estimation",
141 * ACM Trans. Math. Soft., vol. 14, no. 4, pp. 381-396, December 1988.
142 *
143 * =====================================================================
144 *
145 * .. Parameters ..
146  INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
147  $ lld_, mb_, m_, nb_, n_, rsrc_
148  parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
149  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
150  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
151  INTEGER ITMAX
152  parameter( itmax = 5 )
153  DOUBLE PRECISION ONE, TWO
154  parameter( one = 1.0d+0, two = 2.0d+0 )
155  COMPLEX*16 CZERO, CONE
156  parameter( czero = ( 0.0d+0, 0.0d+0 ),
157  $ cone = ( 1.0d+0, 0.0d+0 ) )
158 * ..
159 * .. Local Scalars ..
160  INTEGER I, ICTXT, IIVX, IMAXROW, IOFFVX, IROFF, ITER,
161  $ ivxcol, ivxrow, j, jlast, jjvx, jump, k,
162  $ mycol, myrow, np, npcol, nprow
163  DOUBLE PRECISION ALTSGN, ESTOLD, SAFMIN, TEMP
164  COMPLEX*16 JLMAX, XMAX
165 * ..
166 * .. Local Arrays ..
167  COMPLEX*16 WORK( 2 )
168 * ..
169 * .. External Subroutines ..
170  EXTERNAL blacs_gridinfo, infog2l, dgebr2d,
171  $ dgebs2d, pdzsum1, pzelget,
172  $ pzmax1, zcopy, zgebr2d, zgebs2d
173 * ..
174 * .. External Functions ..
175  INTEGER INDXG2L, INDXG2P, INDXL2G, NUMROC
176  DOUBLE PRECISION PDLAMCH
177  EXTERNAL indxg2l, indxg2p, indxl2g, numroc, pdlamch
178 * ..
179 * .. Intrinsic Functions ..
180  INTRINSIC abs, dble, dcmplx
181 * ..
182 * .. Save statement ..
183  SAVE
184 * ..
185 * .. Executable Statements ..
186 *
187 * Get grid parameters.
188 *
189  ictxt = descx( ctxt_ )
190  CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
191 *
192  CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol,
193  $ iivx, jjvx, ivxrow, ivxcol )
194  IF( mycol.NE.ivxcol )
195  $ RETURN
196  iroff = mod( ix-1, descx( mb_ ) )
197  np = numroc( n+iroff, descx( mb_ ), myrow, ivxrow, nprow )
198  IF( myrow.EQ.ivxrow )
199  $ np = np - iroff
200  ioffvx = iivx + (jjvx-1)*descx( lld_ )
201 *
202  safmin = pdlamch( ictxt, 'Safe minimum' )
203  IF( kase.EQ.0 ) THEN
204  DO 10 i = ioffvx, ioffvx+np-1
205  x( i ) = dcmplx( one / dble( n ) )
206  10 CONTINUE
207  kase = 1
208  jump = 1
209  RETURN
210  END IF
211 *
212  GO TO ( 20, 40, 70, 90, 120 )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  est = abs( v( ioffvx ) )
222  CALL dgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
223  ELSE
224  CALL dgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
225  $ ivxrow, mycol )
226  END IF
227 * ... QUIT
228  GO TO 130
229  END IF
230  CALL pdzsum1( n, est, x, ix, jx, descx, 1 )
231  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
232  IF( myrow.EQ.ivxrow ) THEN
233  CALL dgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
234  ELSE
235  CALL dgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
236  $ ivxrow, mycol )
237  END IF
238  END IF
239 *
240  DO 30 i = ioffvx, ioffvx+np-1
241  IF( abs( x( i ) ).GT.safmin ) THEN
242  x( i ) = x( i ) / dcmplx( abs( x( i ) ) )
243  ELSE
244  x( i ) = cone
245  END IF
246  30 CONTINUE
247  kase = 2
248  jump = 2
249  RETURN
250 *
251 * ................ ENTRY (JUMP = 2)
252 * FIRST ITERATION. X HAS BEEN OVERWRITTEN BY CTRANS(A)*X
253 *
254  40 CONTINUE
255  CALL pzmax1( n, xmax, j, x, ix, jx, descx, 1 )
256  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
257  IF( myrow.EQ.ivxrow ) THEN
258  work( 1 ) = xmax
259  work( 2 ) = dcmplx( dble( j ) )
260  CALL zgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
261  ELSE
262  CALL zgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
263  $ ivxrow, mycol )
264  xmax = work( 1 )
265  j = nint( dble( work( 2 ) ) )
266  END IF
267  END IF
268  iter = 2
269 *
270 * MAIN LOOP - ITERATIONS 2, 3,...,ITMAX
271 *
272  50 CONTINUE
273  DO 60 i = ioffvx, ioffvx+np-1
274  x( i ) = czero
275  60 CONTINUE
276  imaxrow = indxg2p( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
277  IF( myrow.EQ.imaxrow ) THEN
278  i = indxg2l( j, descx( mb_ ), myrow, descx( rsrc_ ), nprow )
279  x( i ) = cone
280  END IF
281  kase = 1
282  jump = 3
283  RETURN
284 *
285 * ................ ENTRY (JUMP = 3)
286 * X HAS BEEN OVERWRITTEN BY A*X
287 *
288  70 CONTINUE
289  CALL zcopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
290  estold = est
291  CALL pdzsum1( n, est, v, iv, jv, descv, 1 )
292  IF( descv( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
293  IF( myrow.EQ.ivxrow ) THEN
294  CALL dgebs2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1 )
295  ELSE
296  CALL dgebr2d( ictxt, 'Columnwise', ' ', 1, 1, est, 1,
297  $ ivxrow, mycol )
298  END IF
299  END IF
300 *
301 * TEST FOR CYCLING
302  IF( est.LE.estold )
303  $ GO TO 100
304 *
305  DO 80 i = ioffvx, ioffvx+np-1
306  IF( abs( x( i ) ).GT.safmin ) THEN
307  x( i ) = x( i ) / dcmplx( abs( x( i ) ) )
308  ELSE
309  x( i ) = cone
310  END IF
311  80 CONTINUE
312  kase = 2
313  jump = 4
314  RETURN
315 *
316 * ................ ENTRY (JUMP = 4)
317 * X HAS BEEN OVERWRITTEN BY CTRANS(A)*X
318 *
319  90 CONTINUE
320  jlast = j
321  CALL pzmax1( n, xmax, j, x, ix, jx, descx, 1 )
322  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
323  IF( myrow.EQ.ivxrow ) THEN
324  work( 1 ) = xmax
325  work( 2 ) = dcmplx( dble( j ) )
326  CALL zgebs2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2 )
327  ELSE
328  CALL zgebr2d( ictxt, 'Columnwise', ' ', 2, 1, work, 2,
329  $ ivxrow, mycol )
330  xmax = work( 1 )
331  j = nint( dble( work( 2 ) ) )
332  END IF
333  END IF
334  CALL pzelget( 'Columnwise', ' ', jlmax, x, jlast, jx, descx )
335  IF( ( dble( jlmax ).NE.abs( dble( xmax ) ) ).AND.
336  $ ( iter.LT.itmax ) ) THEN
337  iter = iter + 1
338  GO TO 50
339  END IF
340 *
341 * ITERATION COMPLETE. FINAL STAGE.
342 *
343  100 CONTINUE
344  DO 110 i = ioffvx, ioffvx+np-1
345  k = indxl2g( i-ioffvx+iivx, descx( mb_ ), myrow,
346  $ descx( rsrc_ ), nprow )-ix+1
347  IF( mod( k, 2 ).EQ.0 ) THEN
348  altsgn = -one
349  ELSE
350  altsgn = one
351  END IF
352  x( i ) = dcmplx( altsgn*( one+dble( k-1 ) / dble( n-1 ) ) )
353  110 CONTINUE
354  kase = 1
355  jump = 5
356  RETURN
357 *
358 * ................ ENTRY (JUMP = 5)
359 * X HAS BEEN OVERWRITTEN BY A*X
360 *
361  120 CONTINUE
362  CALL pdzsum1( n, temp, x, ix, jx, descx, 1 )
363  IF( descx( m_ ).EQ.1 .AND. n.EQ.1 ) THEN
364  IF( myrow.EQ.ivxrow ) THEN
365  CALL dgebs2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1 )
366  ELSE
367  CALL dgebr2d( ictxt, 'Columnwise', ' ', 1, 1, temp, 1,
368  $ ivxrow, mycol )
369  END IF
370  END IF
371  temp = two*( temp / dble( 3*n ) )
372  IF( temp.GT.est ) THEN
373  CALL zcopy( np, x( ioffvx ), 1, v( ioffvx ), 1 )
374  est = temp
375  END IF
376 *
377  130 CONTINUE
378  kase = 0
379 *
380  RETURN
381 *
382 * End of PZLACON
383 *
384  END
pzelget
subroutine pzelget(SCOPE, TOP, ALPHA, A, IA, JA, DESCA)
Definition: pzelget.f:2
infog2l
subroutine infog2l(GRINDX, GCINDX, DESC, NPROW, NPCOL, MYROW, MYCOL, LRINDX, LCINDX, RSRC, CSRC)
Definition: infog2l.f:3
pdzsum1
subroutine pdzsum1(N, ASUM, X, IX, JX, DESCX, INCX)
Definition: pdzsum1.f:2
pzlacon
subroutine pzlacon(N, V, IV, JV, DESCV, X, IX, JX, DESCX, EST, KASE)
Definition: pzlacon.f:3
pzmax1
subroutine pzmax1(N, AMAX, INDX, X, IX, JX, DESCX, INCX)
Definition: pzmax1.f:2