SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
pielset.f
Go to the documentation of this file.
1 SUBROUTINE pielset( A, IA, JA, DESCA, ALPHA )
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 INTEGER ALPHA, IA, JA
10* ..
11* .. Array arguments ..
12 INTEGER A( * ), DESCA( * )
13* ..
14*
15* Purpose
16* =======
17*
18* PIELSET sets the distributed matrix entry A( IA, JA ) to ALPHA.
19*
20* Notes
21* =====
22*
23* Each global data object is described by an associated description
24* vector. This vector stores the information required to establish
25* the mapping between an object element and its corresponding process
26* and memory location.
27*
28* Let A be a generic term for any 2D block cyclicly distributed array.
29* Such a global array has an associated description vector DESCA.
30* In the following comments, the character _ should be read as
31* "of the global array".
32*
33* NOTATION STORED IN EXPLANATION
34* --------------- -------------- --------------------------------------
35* DTYPE_A(global) DESCA( DTYPE_ )The descriptor type. In this case,
36* DTYPE_A = 1.
37* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
38* the BLACS process grid A is distribu-
39* ted over. The context itself is glo-
40* bal, but the handle (the integer
41* value) may vary.
42* M_A (global) DESCA( M_ ) The number of rows in the global
43* array A.
44* N_A (global) DESCA( N_ ) The number of columns in the global
45* array A.
46* MB_A (global) DESCA( MB_ ) The blocking factor used to distribute
47* the rows of the array.
48* NB_A (global) DESCA( NB_ ) The blocking factor used to distribute
49* the columns of the array.
50* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
51* row of the array A is distributed.
52* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
53* first column of the array A is
54* distributed.
55* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
56* array. LLD_A >= MAX(1,LOCr(M_A)).
57*
58* Let K be the number of rows or columns of a distributed matrix,
59* and assume that its process grid has dimension p x q.
60* LOCr( K ) denotes the number of elements of K that a process
61* would receive if K were distributed over the p processes of its
62* process column.
63* Similarly, LOCc( K ) denotes the number of elements of K that a
64* process would receive if K were distributed over the q processes of
65* its process row.
66* The values of LOCr() and LOCc() may be determined via a call to the
67* ScaLAPACK tool function, NUMROC:
68* LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
69* LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
70* An upper bound for these quantities may be computed by:
71* LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
72* LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
73*
74* Arguments
75* =========
76*
77* A (local output) @(typec) pointer into the local memory
78* to an array of dimension (LLD_A,*) containing the local
79* pieces of the distributed matrix A.
80*
81* IA (global input) INTEGER
82* The row index in the global array A indicating the first
83* row of sub( A ).
84*
85* JA (global input) INTEGER
86* The column index in the global array A indicating the
87* first column of sub( A ).
88*
89* DESCA (global and local input) INTEGER array of dimension DLEN_.
90* The array descriptor for the distributed matrix A.
91*
92* ALPHA (local input) @(typec)
93* The scalar alpha.
94*
95* =====================================================================
96*
97* .. Parameters ..
98 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
99 $ LLD_, MB_, M_, NB_, N_, RSRC_
100 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
101 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
102 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
103* ..
104* .. Local Scalars ..
105 INTEGER IACOL, IAROW, IIA, JJA, MYCOL, MYROW, NPCOL,
106 $ NPROW
107* ..
108* .. External Subroutines ..
109 EXTERNAL blacs_gridinfo, infog2l
110* ..
111* .. Executable Statements ..
112*
113* Get grid parameters.
114*
115 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
116*
117 CALL infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia, jja,
118 $ iarow, iacol )
119*
120 IF( myrow.EQ.iarow .AND. mycol.EQ.iacol )
121 $ a( iia+(jja-1)*desca( lld_ ) ) = alpha
122*
123 RETURN
124*
125* End of PIELSET
126*
127 END
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)
Definition infog2l.f:3
subroutine pielset(a, ia, ja, desca, alpha)
Definition pielset.f:2