/[MITgcm]/MITgcm/eesupp/src/scatter_2d_rx.template
ViewVC logotype

Contents of /MITgcm/eesupp/src/scatter_2d_rx.template

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.6 - (show annotations) (download)
Sun Jun 28 01:02:17 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.5: +7 -9 lines
add bj in exch2 arrays and S/R

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/scatter_2d_rx.template,v 1.5 2009/06/08 03:34:03 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_EEOPTIONS.h"
6
7 CBOP
8 C !ROUTINE: SCATTER_2D_RX
9 C !INTERFACE:
10 SUBROUTINE SCATTER_2D_RX(
11 I gloBuff,
12 O myField,
13 I xSize, ySize,
14 I useExch2GlobLayOut,
15 I zeroBuff,
16 I myThid )
17 C !DESCRIPTION:
18 C Scatter elements of a global 2-D array from mpi process 0 to all processes.
19 C Note: done by Master-Thread ; might need barrier calls before and after
20 C this S/R call.
21
22 C !USES:
23 IMPLICIT NONE
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "EESUPPORT.h"
27 #ifdef ALLOW_EXCH2
28 #include "W2_EXCH2_SIZE.h"
29 #include "W2_EXCH2_TOPOLOGY.h"
30 #endif /* ALLOW_EXCH2 */
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C gloBuff ( _RX ) :: full-domain 2D IO-buffer array (Input)
34 C myField ( _RX ) :: tiled, local (i.e. my Proc. tiles) 2D array (Output)
35 C xSize (integer):: global buffer 1rst dim (x)
36 C ySize (integer):: global buffer 2nd dim (y)
37 C useExch2GlobLayOut:: =T: Use Exch2 global-map layout (only with EXCH2)
38 C zeroBuff (logical):: =T: reset the buffer to zero after copy
39 C myThid (integer):: my Thread Id number
40
41 INTEGER xSize, ySize
42 _RX gloBuff(xSize,ySize)
43 _RX myField(1:sNx,1:sNy,nSx,nSy)
44 LOGICAL useExch2GlobLayOut
45 LOGICAL zeroBuff
46 INTEGER myThid
47 CEOP
48
49 C !LOCAL VARIABLES:
50 INTEGER i,j, bi,bj
51 INTEGER iG, jG
52 INTEGER iBase, jBase
53 #ifdef ALLOW_EXCH2
54 INTEGER iGjLoc, jGjLoc
55 INTEGER tN
56 #endif /* ALLOW_EXCH2 */
57 #ifdef ALLOW_USE_MPI
58 INTEGER np0, np
59 _RX temp(1:sNx,1:sNy,nSx,nSy)
60 INTEGER istatus(MPI_STATUS_SIZE), ierr
61 INTEGER lbuff, isource, itag
62 #endif /* ALLOW_USE_MPI */
63
64 _BEGIN_MASTER( myThid )
65
66 #ifdef ALLOW_USE_MPI
67
68 lbuff = sNx*nSx*sNy*nSy
69 isource = 0
70 itag = 0
71
72 IF( mpiMyId .EQ. 0 ) THEN
73
74 C-- Process 0 sends local arrays to all other processes
75 DO np = 2, numberOfProcs
76 np0 = np - 1
77
78 C-- Process 0 extract the local arrays from the global buffer.
79
80 #ifdef ALLOW_EXCH2
81 IF ( useExch2GlobLayOut ) THEN
82
83 DO bj=1,nSy
84 DO bi=1,nSx
85 tN = W2_procTileList(bi,bj,np)
86 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
87 C- face x-size larger than glob-size : fold it
88 iGjLoc = 0
89 jGjLoc = exch2_mydNx(tN) / xSize
90 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
91 C- tile y-size larger than glob-size : make a long line
92 iGjLoc = exch2_mydNx(tN)
93 jGjLoc = 0
94 ELSE
95 C- default (face fit into global-IO-array)
96 iGjLoc = 0
97 jGjLoc = 1
98 ENDIF
99
100 DO j=1,sNy
101 #ifdef TARGET_NEC_SX
102 !cdir novector
103 #endif
104 iG=exch2_txGlobalo(tN)+iGjLoc*(j-1)-1
105 jG=exch2_tyGlobalo(tN)+jGjLoc*(j-1)
106 DO i=1,sNx
107 temp(i,j,bi,bj) = gloBuff(iG+i,jG)
108 ENDDO
109 ENDDO
110
111 ENDDO
112 ENDDO
113
114 ELSE
115 #else /* ALLOW_EXCH2 */
116 IF (.TRUE.) THEN
117 #endif /* ALLOW_EXCH2 */
118
119 iBase = mpi_myXGlobalLo(np)-1
120 jBase = mpi_myYGlobalLo(np)-1
121
122 DO bj=1,nSy
123 DO bi=1,nSx
124 DO j=1,sNy
125 #ifdef TARGET_NEC_SX
126 !cdir novector
127 #endif
128 iG = iBase+(bi-1)*sNx
129 jG = jBase+(bj-1)*sNy+j
130 DO i=1,sNx
131 temp(i,j,bi,bj) = gloBuff(iG+i,jG)
132 ENDDO
133 ENDDO
134 ENDDO
135 ENDDO
136
137 C end if-else useExch2GlobLayOut
138 ENDIF
139
140 C-- Process 0 sends local arrays to all other processes
141 CALL MPI_SEND (temp, lbuff, _MPI_TYPE_RX,
142 & np0, itag, MPI_COMM_MODEL, ierr)
143
144 C- end loop on np
145 ENDDO
146
147 ELSE
148
149 C-- All proceses except 0 receive local array from process 0
150 CALL MPI_RECV (myField, lbuff, _MPI_TYPE_RX,
151 & isource, itag, MPI_COMM_MODEL, istatus, ierr)
152
153 ENDIF
154
155 #endif /* ALLOW_USE_MPI */
156
157 IF( myProcId .EQ. 0 ) THEN
158 C-- Process 0 fills-in its local data
159
160 #ifdef ALLOW_EXCH2
161 IF ( useExch2GlobLayOut ) THEN
162
163 DO bj=1,nSy
164 DO bi=1,nSx
165 tN = W2_myTileList(bi,bj)
166 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
167 C- face x-size larger than glob-size : fold it
168 iGjLoc = 0
169 jGjLoc = exch2_mydNx(tN) / xSize
170 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
171 C- tile y-size larger than glob-size : make a long line
172 iGjLoc = exch2_mydNx(tN)
173 jGjLoc = 0
174 ELSE
175 C- default (face fit into global-IO-array)
176 iGjLoc = 0
177 jGjLoc = 1
178 ENDIF
179
180 DO j=1,sNy
181 #ifdef TARGET_NEC_SX
182 !cdir novector
183 #endif
184 iG=exch2_txGlobalo(tN)+iGjLoc*(j-1)-1
185 jG=exch2_tyGlobalo(tN)+jGjLoc*(j-1)
186 DO i=1,sNx
187 myField(i,j,bi,bj) = gloBuff(iG+i,jG)
188 ENDDO
189 ENDDO
190
191 ENDDO
192 ENDDO
193
194 C-- After the copy from the buffer, reset to zero.
195 C An alternative to zeroBuff when writing to file,
196 C which could be faster if we do less read than write.
197 IF ( zeroBuff ) THEN
198 DO j=1,ySize
199 DO i=1,xSize
200 gloBuff(i,j) = 0.
201 ENDDO
202 ENDDO
203 ENDIF
204
205 ELSE
206 #else /* ALLOW_EXCH2 */
207 IF (.TRUE.) THEN
208 #endif /* ALLOW_EXCH2 */
209
210 iBase = myXGlobalLo-1
211 jBase = myYGlobalLo-1
212
213 DO bj=1,nSy
214 DO bi=1,nSx
215 DO j=1,sNy
216 #ifdef TARGET_NEC_SX
217 !cdir novector
218 #endif
219 iG = iBase+(bi-1)*sNx
220 jG = jBase+(bj-1)*sNy+j
221 DO i=1,sNx
222 myField(i,j,bi,bj) = gloBuff(iG+i,jG)
223 ENDDO
224 ENDDO
225 ENDDO
226 ENDDO
227
228 C end if-else useExch2GlobLayOut
229 ENDIF
230
231 C- end if myProcId = 0
232 ENDIF
233
234 _END_MASTER( myThid )
235
236 RETURN
237 END
238 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22