SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
All Classes Files Functions Variables Typedefs Macros
pclacgv.f
Go to the documentation of this file.
1 SUBROUTINE pclacgv( N, X, IX, JX, DESCX, INCX )
2*
3* -- ScaLAPACK auxiliary 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 INCX, IX, JX, N
10* ..
11* .. Array Arguments ..
12 INTEGER DESCX( * )
13 COMPLEX X( * )
14* ..
15*
16* Purpose
17* =======
18*
19* PCLACGV conjugates a complex vector of length N, sub( X ), where
20* sub( X ) denotes X(IX,JX:JX+N-1) if INCX = DESCX( M_ ) and
21* X(IX:IX+N-1,JX) if INCX = 1, and
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* Because vectors may be viewed as a subclass of matrices, a
78* distributed vector is considered to be a distributed matrix.
79*
80* Arguments
81* =========
82*
83* N (global input) INTEGER
84* The length of the distributed vector sub( X ).
85*
86* X (local input/local output) COMPLEX pointer into the
87* local memory to an array of dimension (LLD_X,*).
88* On entry the vector to be conjugated
89* x( i ) = X(IX+(JX-1)*M_X +(i-1)*INCX ), 1 <= i <= N.
90* On exit the conjugated vector.
91*
92* IX (global input) INTEGER
93* The row index in the global array X indicating the first
94* row of sub( X ).
95*
96* JX (global input) INTEGER
97* The column index in the global array X indicating the
98* first column of sub( X ).
99*
100* DESCX (global and local input) INTEGER array of dimension DLEN_.
101* The array descriptor for the distributed matrix X.
102*
103* INCX (global input) INTEGER
104* The global increment for the elements of X. Only two values
105* of INCX are supported in this version, namely 1 and M_X.
106* INCX must not be zero.
107*
108* =====================================================================
109*
110* .. Parameters ..
111 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
112 $ LLD_, MB_, M_, NB_, N_, RSRC_
113 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
114 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
115 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
116* ..
117* .. Local Scalars ..
118 INTEGER I, ICOFFX, ICTXT, IIX, IOFFX, IROFFX, IXCOL,
119 $ IXROW, JJX, LDX, MYCOL, MYROW, NP, NPCOL,
120 $ NPROW, NQ
121* ..
122* .. External Subroutines ..
123 EXTERNAL blacs_gridinfo, infog2l
124* ..
125* .. External Functions ..
126 INTEGER NUMROC
127 EXTERNAL numroc
128* ..
129* .. Intrinsic Functions ..
130 INTRINSIC conjg, mod
131* ..
132* .. Executable Statements ..
133*
134* Get grid parameters.
135*
136 ictxt = descx( ctxt_ )
137 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
138*
139* Figure local indexes
140*
141 CALL infog2l( ix, jx, descx, nprow, npcol, myrow, mycol,
142 $ iix, jjx, ixrow, ixcol )
143*
144 ldx = descx( lld_ )
145 IF( incx.EQ.descx( m_ ) ) THEN
146*
147* sub( X ) is rowwise distributed.
148*
149 IF( myrow.NE.ixrow )
150 $ RETURN
151 icoffx = mod( jx-1, descx( nb_ ) )
152 nq = numroc( n+icoffx, descx( nb_ ), mycol, ixcol, npcol )
153 IF( mycol.EQ.ixcol )
154 $ nq = nq - icoffx
155*
156 IF( nq.GT.0 ) THEN
157 ioffx = iix+(jjx-1)*ldx
158 DO 10 i = 1, nq
159 x( ioffx ) = conjg( x( ioffx ) )
160 ioffx = ioffx + ldx
161 10 CONTINUE
162 END IF
163*
164 ELSE IF( incx.EQ.1 ) THEN
165*
166* sub( X ) is columnwise distributed.
167*
168 IF( mycol.NE.ixcol )
169 $ RETURN
170 iroffx = mod( ix-1, descx( mb_ ) )
171 np = numroc( n+iroffx, descx( mb_ ), myrow, ixrow, nprow )
172 IF( myrow.EQ.ixrow )
173 $ np = np - iroffx
174*
175 IF( np.GT.0 ) THEN
176 ioffx = iix+(jjx-1)*ldx
177 DO 20 i = ioffx, ioffx+np-1
178 x( i ) = conjg( x( i ) )
179 20 CONTINUE
180 END IF
181*
182 END IF
183*
184 RETURN
185*
186* End of PCLACGV
187*
188 END
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)
Definition infog2l.f:3
subroutine pclacgv(n, x, ix, jx, descx, incx)
Definition pclacgv.f:2