/[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.7 - (show annotations) (download)
Mon Sep 3 19:36:29 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.6: +13 -11 lines
add "if usingMPI" test where needed (+ start to remove ALWAYS_USE_MPI)

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/scatter_2d_rx.template,v 1.6 2009/06/28 01:02:17 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 np, pId
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 IF ( usingMPI ) THEN
68
69 lbuff = sNx*nSx*sNy*nSy
70 isource = 0
71 itag = 0
72
73 IF( mpiMyId .EQ. 0 ) THEN
74
75 C-- Process 0 sends local arrays to all other processes
76 DO np = 2, nPx*nPy
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 pId = np - 1
142 CALL MPI_SEND (temp, lbuff, _MPI_TYPE_RX,
143 & pId, itag, MPI_COMM_MODEL, ierr)
144
145 C- end loop on np
146 ENDDO
147
148 ELSE
149
150 C-- All proceses except 0 receive local array from process 0
151 CALL MPI_RECV (myField, lbuff, _MPI_TYPE_RX,
152 & isource, itag, MPI_COMM_MODEL, istatus, ierr)
153
154 ENDIF
155
156 ENDIF
157 #endif /* ALLOW_USE_MPI */
158
159 IF( myProcId .EQ. 0 ) THEN
160 C-- Process 0 fills-in its local data
161
162 #ifdef ALLOW_EXCH2
163 IF ( useExch2GlobLayOut ) THEN
164
165 DO bj=1,nSy
166 DO bi=1,nSx
167 tN = W2_myTileList(bi,bj)
168 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
169 C- face x-size larger than glob-size : fold it
170 iGjLoc = 0
171 jGjLoc = exch2_mydNx(tN) / xSize
172 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
173 C- tile y-size larger than glob-size : make a long line
174 iGjLoc = exch2_mydNx(tN)
175 jGjLoc = 0
176 ELSE
177 C- default (face fit into global-IO-array)
178 iGjLoc = 0
179 jGjLoc = 1
180 ENDIF
181
182 DO j=1,sNy
183 #ifdef TARGET_NEC_SX
184 !cdir novector
185 #endif
186 iG=exch2_txGlobalo(tN)+iGjLoc*(j-1)-1
187 jG=exch2_tyGlobalo(tN)+jGjLoc*(j-1)
188 DO i=1,sNx
189 myField(i,j,bi,bj) = gloBuff(iG+i,jG)
190 ENDDO
191 ENDDO
192
193 ENDDO
194 ENDDO
195
196 C-- After the copy from the buffer, reset to zero.
197 C An alternative to zeroBuff when writing to file,
198 C which could be faster if we do less read than write.
199 IF ( zeroBuff ) THEN
200 DO j=1,ySize
201 DO i=1,xSize
202 gloBuff(i,j) = 0.
203 ENDDO
204 ENDDO
205 ENDIF
206
207 ELSE
208 #else /* ALLOW_EXCH2 */
209 IF (.TRUE.) THEN
210 #endif /* ALLOW_EXCH2 */
211
212 iBase = myXGlobalLo-1
213 jBase = myYGlobalLo-1
214
215 DO bj=1,nSy
216 DO bi=1,nSx
217 DO j=1,sNy
218 #ifdef TARGET_NEC_SX
219 !cdir novector
220 #endif
221 iG = iBase+(bi-1)*sNx
222 jG = jBase+(bj-1)*sNy+j
223 DO i=1,sNx
224 myField(i,j,bi,bj) = gloBuff(iG+i,jG)
225 ENDDO
226 ENDDO
227 ENDDO
228 ENDDO
229
230 C end if-else useExch2GlobLayOut
231 ENDIF
232
233 C- end if myProcId = 0
234 ENDIF
235
236 _END_MASTER( myThid )
237
238 RETURN
239 END
240 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22