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

Annotation of /MITgcm/eesupp/src/exch_rx.template

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


Revision 1.8 - (hide annotations) (download)
Wed May 19 01:56:54 2010 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.7: +1 -1 lines
FILE REMOVED
remove old version (renamed exch1_* without argument "simulationMode")

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_rx.template,v 1.7 2010/05/17 02:29:00 jmc Exp $
2 cnh 1.3 C $Name: $
3 adcroft 1.2
4     #include "CPP_EEOPTIONS.h"
5    
6 cnh 1.3 CBOP
7    
8     C !ROUTINE: EXCH_RX
9    
10     C !INTERFACE:
11 jmc 1.6 SUBROUTINE EXCH_RX(
12 adcroft 1.2 U array,
13     I myOLw, myOLe, myOLs, myOLn, myNz,
14     I exchWidthX, exchWidthY,
15     I simulationMode, cornerMode, myThid )
16     IMPLICIT NONE
17    
18 cnh 1.3 C !DESCRIPTION:
19     C *==========================================================*
20 jmc 1.6 C | SUBROUTINE EXCH_RX
21     C | o Control edge exchanges for RX array.
22 cnh 1.3 C *==========================================================*
23 jmc 1.6 C |
24     C | Controlling routine for exchange of XY edges of an array
25     C | distributed in X and Y. The routine interfaces to
26     C | communication routines that can use messages passing
27     C | exchanges, put type exchanges or get type exchanges.
28     C | This allows anything from MPI to raw memory channel to
29     C | memmap segments to be used as a inter-process and/or
30     C | inter-thread communiation and synchronisation
31     C | mechanism.
32     C | Notes --
33     C | 1. Some low-level mechanisms such as raw memory-channel
34     C | or SGI/CRAY shmem put do not have direct Fortran bindings
35     C | and are invoked through C stub routines.
36     C | 2. Although this routine is fairly general but it does
37     C | require nSx and nSy are the same for all innvocations.
38     C | There are many common data structures ( myByLo,
39     C | westCommunicationMode, mpiIdW etc... ) tied in with
40     C | (nSx,nSy). To support arbitray nSx and nSy would require
41     C | general forms of these.
42 cnh 1.3 C | 3. RX arrays are used to generate code for both _RL and
43 jmc 1.6 C | _RS forms.
44 cnh 1.3 C *==========================================================*
45    
46     C !USES:
47 adcroft 1.2 C == Global data ==
48     #include "SIZE.h"
49     #include "EEPARAMS.h"
50     #include "EESUPPORT.h"
51     #include "EXCH.h"
52    
53 cnh 1.3 C !INPUT/OUTPUT PARAMETERS:
54 adcroft 1.2 C == Routine arguments ==
55 cnh 1.3 C array :: Array with edges to exchange.
56     C myOLw :: West, East, North and South overlap region sizes.
57 adcroft 1.2 C myOLe
58     C myOLn
59     C myOLs
60 cnh 1.3 C exchWidthX :: Width of data region exchanged in X.
61     C exchWidthY :: Width of data region exchanged in Y.
62 jmc 1.6 C Note --
63 cnh 1.3 C 1. In theory one could have a send width and
64     C a receive width for each face of each tile. The only
65     C restriction woul be that the send width of one
66     C face should equal the receive width of the sent to
67 jmc 1.6 C tile face. Dont know if this would be useful. I
68     C have left it out for now as it requires additional
69 cnh 1.3 C bookeeping.
70 jmc 1.6 C simulationMode :: Forward or reverse mode exchange ( provides
71 cnh 1.3 C support for adjoint integration of code. )
72 jmc 1.6 C cornerMode :: Flag indicating whether corner updates are
73 cnh 1.3 C needed.
74     C myThid :: Thread number of this instance of S/R EXCH...
75 adcroft 1.2 INTEGER myOLw
76     INTEGER myOLe
77     INTEGER myOLs
78     INTEGER myOLn
79     INTEGER myNz
80     INTEGER exchWidthX
81     INTEGER exchWidthY
82     INTEGER simulationMode
83     INTEGER cornerMode
84     INTEGER myThid
85     _RX array(1-myOLw:sNx+myOLe,
86 jmc 1.6 & 1-myOLs:sNy+myOLn,
87 adcroft 1.2 & myNZ, nSx, nSy)
88    
89 cnh 1.3 C !LOCAL VARIABLES:
90 adcroft 1.2 C == Local variables ==
91 cnh 1.3 C theSimulationMode :: Holds working copy of simulation mode
92     C theCornerMode :: Holds working copy of corner mode
93 jmc 1.6 C i,j,k,bi,bj :: Loop counters
94 adcroft 1.2 INTEGER theSimulationMode
95     INTEGER theCornerMode
96 jmc 1.6 INTEGER i,j,k,bi,bj
97 cnh 1.3 CEOP
98 adcroft 1.2
99     theSimulationMode = simulationMode
100     theCornerMode = cornerMode
101    
102     C-- Error checks
103 jmc 1.6 IF ( exchWidthX .GT. myOLw )
104 adcroft 1.2 & STOP ' S/R EXCH_RX: exchWidthX .GT. myOLw'
105 jmc 1.6 IF ( exchWidthX .GT. myOLe )
106 adcroft 1.2 & STOP ' S/R EXCH_RX: exchWidthX .GT. myOLe'
107 jmc 1.6 IF ( exchWidthY .GT. myOLs )
108 adcroft 1.2 & STOP ' S/R EXCH_RX: exchWidthY .GT. myOLs'
109 jmc 1.6 IF ( exchWidthY .GT. myOLn )
110 adcroft 1.2 & STOP ' S/R EXCH_RX: exchWidthY .GT. myOLn'
111 jmc 1.6 IF ( myOLw .GT. MAX_OLX_EXCH )
112 adcroft 1.2 & STOP ' S/R EXCH_RX: myOLw .GT. MAX_OLX_EXCH'
113 jmc 1.6 IF ( myOLe .GT. MAX_OLX_EXCH )
114 adcroft 1.2 & STOP ' S/R EXCH_RX: myOLe .GT. MAX_OLX_EXCH'
115 jmc 1.6 IF ( myOLn .GT. MAX_OLX_EXCH )
116 adcroft 1.2 & STOP ' S/R EXCH_RX: myOLn .GT. MAX_OLY_EXCH'
117 jmc 1.6 IF ( myOLs .GT. MAX_OLY_EXCH )
118 adcroft 1.2 & STOP ' S/R EXCH_RX: myOLs .GT. MAX_OLY_EXCH'
119 jmc 1.6 IF ( myNZ .GT. MAX_NR_EXCH )
120 adcroft 1.2 & STOP ' S/R EXCH_RX: myNZ .GT. MAX_NR_EXCH '
121     IF ( theSimulationMode .NE. FORWARD_SIMULATION
122     & .AND. theSimulationMode .NE. REVERSE_SIMULATION
123     & ) STOP ' S/R EXCH_RX: Unrecognised simulationMode '
124     IF ( theCornerMode .NE. EXCH_IGNORE_CORNERS
125     & .AND. theCornerMode .NE. EXCH_UPDATE_CORNERS
126     & ) STOP ' S/R EXCH_RX: Unrecognised cornerMode '
127    
128     C-- Cycle edge buffer level
129     CALL EXCH_CYCLE_EBL( myThid )
130    
131 jmc 1.6 IF ( theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
132    
133     IF ( Nx .EQ. 1 ) THEN
134     C Special case for zonal average model i.e. case where Nx == 1
135     C In this case a reverse mode exchange simply add values from all i <> 1
136     C to i=1 element and reset to zero.
137     DO bj=myByLo(myThid),myByHi(myThid)
138     DO bi=myBxLo(myThid),myBxHi(myThid)
139     DO k = 1,myNz
140     DO j = 1-myOLs,sNy+myOLn
141     DO i = 1-myOLw,0
142     array(1,j,k,bi,bj) = array(1,j,k,bi,bj)
143     & + array(i,j,k,bi,bj)
144     array(i,j,k,bi,bj) = 0.
145     ENDDO
146     DO i = sNx+1,sNx+myOLe
147     array(1,j,k,bi,bj) = array(1,j,k,bi,bj)
148     & + array(i,j,k,bi,bj)
149     array(i,j,k,bi,bj) = 0.
150     ENDDO
151     ENDDO
152     ENDDO
153     ENDDO
154     ENDDO
155     ENDIF
156    
157     IF ( Ny .EQ. 1 ) THEN
158     C Special case for X-slice domain i.e. case where Ny == 1
159     C In this case a reverse mode exchange simply add values from all j <> 1
160     C to j=1 element and reset to zero.
161     DO bj=myByLo(myThid),myByHi(myThid)
162     DO bi=myBxLo(myThid),myBxHi(myThid)
163     DO k = 1,myNz
164     DO j = 1-myOLs,0
165     DO i = 1-myOLw,sNx+myOLe
166     array(i,1,k,bi,bj) = array(i,1,k,bi,bj)
167     & + array(i,j,k,bi,bj)
168     array(i,j,k,bi,bj) = 0.
169     ENDDO
170     ENDDO
171     DO j = sNy+1,sNy+myOLn
172     DO i = 1-myOLw,sNx+myOLe
173     array(i,1,k,bi,bj) = array(i,1,k,bi,bj)
174     & + array(i,j,k,bi,bj)
175     array(i,j,k,bi,bj) = 0.
176     ENDDO
177     ENDDO
178     ENDDO
179     ENDDO
180     ENDDO
181     ENDIF
182    
183     C-- end of special cases of forward exch
184     ENDIF
185    
186 adcroft 1.2 IF ( theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
187     C-- "Put" east and west edges.
188     CALL EXCH_RX_SEND_PUT_X( array,
189     I myOLw, myOLe, myOLs, myOLn, myNz,
190     I exchWidthX, exchWidthY,
191     I theSimulationMode, theCornerMode, myThid )
192 jmc 1.6 C-- If corners are important then sync and update east and west edges
193 adcroft 1.2 C-- before doing north and south exchanges.
194     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
195     CALL EXCH_RX_RECV_GET_X( array,
196     I myOLw, myOLe, myOLs, myOLn, myNz,
197     I exchWidthX, exchWidthY,
198     I theSimulationMode, theCornerMode, myThid )
199     ENDIF
200     C "Put" north and south edges.
201     CALL EXCH_RX_SEND_PUT_Y( array,
202     I myOLw, myOLe, myOLs, myOLn, myNz,
203     I exchWidthX, exchWidthY,
204     I theSimulationMode, theCornerMode, myThid )
205     C-- Sync and update north, south (and east, west if corner updating
206     C-- not active).
207     IF ( theCornerMode .NE. EXCH_UPDATE_CORNERS ) THEN
208     CALL EXCH_RX_RECV_GET_X( array,
209     I myOLw, myOLe, myOLs, myOLn, myNz,
210     I exchWidthX, exchWidthY,
211     I theSimulationMode, theCornerMode, myThid )
212     ENDIF
213     CALL EXCH_RX_RECV_GET_Y( array,
214     I myOLw, myOLe, myOLs, myOLn, myNz,
215     I exchWidthX, exchWidthY,
216     I theSimulationMode, theCornerMode, myThid )
217     ENDIF
218    
219     IF ( theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
220     C "Put" north and south edges.
221     CALL EXCH_RX_SEND_PUT_Y( array,
222     I myOLw, myOLe, myOLs, myOLn, myNz,
223     I exchWidthX, exchWidthY,
224     I theSimulationMode, theCornerMode, myThid )
225     C-- If corners are important then sync and update east and west edges
226     C-- before doing north and south exchanges.
227     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
228     CALL EXCH_RX_RECV_GET_Y( array,
229     I myOLw, myOLe, myOLs, myOLn, myNz,
230     I exchWidthX, exchWidthY,
231     I theSimulationMode, theCornerMode, myThid )
232     ENDIF
233     C-- "Put" east and west edges.
234     CALL EXCH_RX_SEND_PUT_X( array,
235     I myOLw, myOLe, myOLs, myOLn, myNz,
236     I exchWidthX, exchWidthY,
237     I theSimulationMode, theCornerMode, myThid )
238     C-- Sync and update east, west (and north, south if corner updating
239     C-- not active).
240     IF ( theCornerMode .NE. EXCH_UPDATE_CORNERS ) THEN
241     CALL EXCH_RX_RECV_GET_Y( array,
242     I myOLw, myOLe, myOLs, myOLn, myNz,
243     I exchWidthX, exchWidthY,
244     I theSimulationMode, theCornerMode, myThid )
245     ENDIF
246     CALL EXCH_RX_RECV_GET_X( array,
247     I myOLw, myOLe, myOLs, myOLn, myNz,
248     I exchWidthX, exchWidthY,
249     I theSimulationMode, theCornerMode, myThid )
250     ENDIF
251 jmc 1.6
252     IF ( theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
253    
254     IF ( Nx .EQ. 1 ) THEN
255 jmc 1.4 C Special case for zonal average model i.e. case where Nx == 1
256 adcroft 1.2 C In this case a forward mode exchange simply sets array to
257     C the i=1 value for all i.
258 jmc 1.6 DO bj=myByLo(myThid),myByHi(myThid)
259     DO bi=myBxLo(myThid),myBxHi(myThid)
260     DO k = 1,myNz
261     DO j = 1-myOLs,sNy+myOLn
262     DO i = 1-myOLw,sNx+myOLe
263     array(i,j,k,bi,bj) = array(1,j,k,bi,bj)
264     ENDDO
265 jmc 1.4 ENDDO
266     ENDDO
267     ENDDO
268     ENDDO
269 jmc 1.6 ENDIF
270    
271     IF ( Ny .EQ. 1 ) THEN
272 jmc 1.4 C Special case for X-slice domain i.e. case where Ny == 1
273     C In this case a forward mode exchange simply sets array to
274     C the j=1 value for all j.
275 jmc 1.6 DO bj=myByLo(myThid),myByHi(myThid)
276     DO bi=myBxLo(myThid),myBxHi(myThid)
277     DO k = 1,myNz
278     DO j = 1-myOLs,sNy+myOLn
279     DO i = 1-myOLw,sNx+myOLe
280     array(i,j,k,bi,bj) = array(i,1,k,bi,bj)
281     ENDDO
282 adcroft 1.2 ENDDO
283     ENDDO
284     ENDDO
285     ENDDO
286 jmc 1.6 ENDIF
287    
288     C-- end of special cases of forward exch
289 adcroft 1.2 ENDIF
290    
291     RETURN
292     END

  ViewVC Help
Powered by ViewVC 1.1.22