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