SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
pselget.f
Go to the documentation of this file.
1 SUBROUTINE pselget( SCOPE, TOP, ALPHA, A, IA, JA, DESCA )
2*
3* -- ScaLAPACK tools routine (version 1.7) --
4* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5* and University of California, Berkeley.
6* May 1, 1997
7*
8* .. Scalar Arguments ..
9 CHARACTER*1 SCOPE, TOP
10 INTEGER IA, JA
11 REAL ALPHA
12* ..
13* .. Array arguments ..
14 INTEGER DESCA( * )
15 REAL A( * )
16* ..
17*
18* Purpose
19* =======
20*
21* PSELGET sets alpha to the distributed matrix entry A( IA, JA ).
22* The value of alpha is set according to the scope.
23*
24* Notes
25* =====
26*
27* Each global data object is described by an associated description
28* vector. This vector stores the information required to establish
29* the mapping between an object element and its corresponding process
30* and memory location.
31*
32* Let A be a generic term for any 2D block cyclicly distributed array.
33* Such a global array has an associated description vector DESCA.
34* In the following comments, the character _ should be read as
35* "of the global array".
36*
37* NOTATION STORED IN EXPLANATION
38* --------------- -------------- --------------------------------------
39* DTYPE_A(global) DESCA( DTYPE_ )The descriptor type. In this case,
40* DTYPE_A = 1.
41* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
42* the BLACS process grid A is distribu-
43* ted over. The context itself is glo-
44* bal, but the handle (the integer
45* value) may vary.
46* M_A (global) DESCA( M_ ) The number of rows in the global
47* array A.
48* N_A (global) DESCA( N_ ) The number of columns in the global
49* array A.
50* MB_A (global) DESCA( MB_ ) The blocking factor used to distribute
51* the rows of the array.
52* NB_A (global) DESCA( NB_ ) The blocking factor used to distribute
53* the columns of the array.
54* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
55* row of the array A is distributed.
56* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
57* first column of the array A is
58* distributed.
59* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
60* array. LLD_A >= MAX(1,LOCr(M_A)).
61*
62* Let K be the number of rows or columns of a distributed matrix,
63* and assume that its process grid has dimension p x q.
64* LOCr( K ) denotes the number of elements of K that a process
65* would receive if K were distributed over the p processes of its
66* process column.
67* Similarly, LOCc( K ) denotes the number of elements of K that a
68* process would receive if K were distributed over the q processes of
69* its process row.
70* The values of LOCr() and LOCc() may be determined via a call to the
71* ScaLAPACK tool function, NUMROC:
72* LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
73* LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
74* An upper bound for these quantities may be computed by:
75* LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
76* LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
77*
78* Arguments
79* =========
80*
81* SCOPE (global input) CHARACTER*1
82* The BLACS scope in which alpha is updated.
83* If SCOPE = 'R', alpha is updated only in the process row
84* containing A( IA, JA ),
85* If SCOPE = 'C', alpha is updated only in the process column
86* containing A( IA, JA ),
87* If SCOPE = 'A', alpha is updated in all the processes of the
88* grid,
89* otherwise alpha is updated only in the process containing
90* A( IA, JA ).
91*
92* TOP (global input) CHARACTER*1
93* The topology to be used if broadcast is needed.
94*
95* ALPHA (global output) REAL, the scalar alpha.
96*
97* A (local input) REAL pointer into the local memory
98* to an array of dimension (LLD_A,*) containing the local
99* pieces of the distributed matrix A.
100*
101* IA (global input) INTEGER
102* The row index in the global array A indicating the first
103* row of sub( A ).
104*
105* JA (global input) INTEGER
106* The column index in the global array A indicating the
107* first column of sub( A ).
108*
109* DESCA (global and local input) INTEGER array of dimension DLEN_.
110* The array descriptor for the distributed matrix A.
111*
112* =====================================================================
113*
114* .. Parameters ..
115 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
116 $ LLD_, MB_, M_, NB_, N_, RSRC_
117 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
118 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
119 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
120 REAL ZERO
121 parameter( zero = 0.0e+0 )
122* ..
123* .. Local Scalars ..
124 INTEGER IACOL, IAROW, ICTXT, IIA, IOFFA, JJA, MYCOL,
125 $ MYROW, NPCOL, NPROW
126* ..
127* .. External Subroutines ..
128 EXTERNAL blacs_gridinfo, infog2l, sgebr2d, sgebs2d
129* ..
130* .. External Functions ..
131 LOGICAL LSAME
132 EXTERNAL lsame
133* ..
134* .. Executable Statements ..
135*
136* Get grid parameters.
137*
138 ictxt = desca( ctxt_ )
139 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
140*
141 CALL infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia, jja,
142 $ iarow, iacol )
143*
144 alpha = zero
145*
146 IF( lsame( scope, 'R' ) ) THEN
147 IF( myrow.EQ.iarow ) THEN
148 IF( mycol.EQ.iacol ) THEN
149 ioffa = iia+(jja-1)*desca( lld_ )
150 CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
151 alpha = a( ioffa )
152 ELSE
153 CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
154 $ iarow, iacol )
155 END IF
156 END IF
157 ELSE IF( lsame( scope, 'C' ) ) THEN
158 IF( mycol.EQ.iacol ) THEN
159 IF( myrow.EQ.iarow ) THEN
160 ioffa = iia+(jja-1)*desca( lld_ )
161 CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
162 alpha = a( ioffa )
163 ELSE
164 CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
165 $ iarow, iacol )
166 END IF
167 END IF
168 ELSE IF( lsame( scope, 'A' ) ) THEN
169 IF( ( myrow.EQ.iarow ).AND.( mycol.EQ.iacol ) ) THEN
170 ioffa = iia+(jja-1)*desca( lld_ )
171 CALL sgebs2d( ictxt, scope, top, 1, 1, a( ioffa ), 1 )
172 alpha = a( ioffa )
173 ELSE
174 CALL sgebr2d( ictxt, scope, top, 1, 1, alpha, 1,
175 $ iarow, iacol )
176 END IF
177 ELSE
178 IF( myrow.EQ.iarow .AND. mycol.EQ.iacol )
179 $ alpha = a( iia+(jja-1)*desca( lld_ ) )
180 END IF
181*
182 RETURN
183*
184* End of PSELGET
185*
186 END
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)
Definition infog2l.f:3
subroutine pselget(scope, top, alpha, a, ia, ja, desca)
Definition pselget.f:2