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

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

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


Revision 1.4 - (hide annotations) (download)
Thu Sep 17 18:09:05 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62, checkpoint62b, checkpoint61z, checkpoint61v, checkpoint61w, checkpoint61x, checkpoint61y
Changes since 1.3: +43 -31 lines
add a stop if wrong tiling

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_z_rx_cube.template,v 1.3 2001/09/21 03:55:50 cnh 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_Z_RX_CUBE
9    
10     C !INTERFACE:
11 jmc 1.4 SUBROUTINE EXCH_Z_RX_CUBE(
12 adcroft 1.2 U array,
13     I myOLw, myOLe, myOLn, myOLs, myNz,
14     I exchWidthX, exchWidthY,
15     I simulationMode, cornerMode, myThid )
16     IMPLICIT NONE
17 cnh 1.3 C !DESCRIPTION:
18     C *==========================================================*
19 jmc 1.4 C | SUBROUTINE EXCH_Z_RX_CUBE
20     C | o Control edge exchanges for RX zeta point array on CS
21 cnh 1.3 C *==========================================================*
22 jmc 1.4 C |
23     C | Controlling routine for exchange of XY edges of an array
24     C | distributed in X and Y. The routine interfaces to
25     C | communication routines that can use messages passing
26     C | exchanges, put type exchanges or get type exchanges.
27     C | This allows anything from MPI to raw memory channel to
28     C | memmap segments to be used as a inter-process and/or
29     C | inter-thread communiation and synchronisation
30     C | mechanism.
31     C | Notes --
32     C | 1. Some low-level mechanisms such as raw memory-channel
33     C | or SGI/CRAY shmem put do not have direct Fortran bindings
34     C | and are invoked through C stub routines.
35     C | 2. Although this routine is fairly general but it does
36     C | require nSx and nSy are the same for all innvocations.
37     C | There are many common data structures ( myByLo,
38     C | westCommunicationMode, mpiIdW etc... ) tied in with
39     C | (nSx,nSy). To support arbitray nSx and nSy would require
40     C | general forms of these.
41     C | 3. zeta coord exchange operation for cube sphere grid
42     C |
43 cnh 1.3 C *==========================================================*
44 adcroft 1.2
45 cnh 1.3 C !USES:
46 adcroft 1.2 C == Global data ==
47     #include "SIZE.h"
48     #include "EEPARAMS.h"
49     #include "EESUPPORT.h"
50     #include "EXCH.h"
51    
52 cnh 1.3 C !INPUT/OUTPUT PARAMETERS:
53 adcroft 1.2 C == Routine arguments ==
54 cnh 1.3 C array :: Array with edges to exchange.
55     C myOLw :: West, East, North and South overlap region sizes.
56 adcroft 1.2 C myOLe
57     C myOLn
58     C myOLs
59 cnh 1.3 C exchWidthX :: Width of data region exchanged in X.
60     C exchWidthY :: Width of data region exchanged in Y.
61 jmc 1.4 C Note --
62 cnh 1.3 C 1. In theory one could have a send width and
63     C a receive width for each face of each tile. The only
64     C restriction woul be that the send width of one
65     C face should equal the receive width of the sent to
66 jmc 1.4 C tile face. Dont know if this would be useful. I
67     C have left it out for now as it requires additional
68 cnh 1.3 C bookeeping.
69 jmc 1.4 C simulationMode :: Forward or reverse mode exchange ( provides
70 cnh 1.3 C support for adjoint integration of code. )
71 jmc 1.4 C cornerMode :: Flag indicating whether corner updates are
72 cnh 1.3 C needed.
73     C myThid :: Thread number of this instance of S/R EXCH...
74 adcroft 1.2 INTEGER myOLw
75     INTEGER myOLe
76     INTEGER myOLs
77     INTEGER myOLn
78     INTEGER myNz
79     INTEGER exchWidthX
80     INTEGER exchWidthY
81     INTEGER simulationMode
82     INTEGER cornerMode
83     INTEGER myThid
84     _RX array(1-myOLw:sNx+myOLe,
85 jmc 1.4 & 1-myOLs:sNy+myOLn,
86 adcroft 1.2 & myNZ, nSx, nSy)
87    
88 cnh 1.3 C !LOCAL VARIABLES:
89 adcroft 1.2 C == Local variables ==
90 cnh 1.3 C theSimulationMode :: Holds working copy of simulation mode
91     C theCornerMode :: Holds working copy of corner mode
92     C I,J,K,repeat :: Loop counters and index
93     C bl,bt,bn,bs,be,bw
94 jmc 1.4 CHARACTER*(MAX_LEN_MBUF) msgBuf
95 adcroft 1.2 INTEGER theSimulationMode
96     INTEGER theCornerMode
97     INTEGER I,J,K,repeat
98     INTEGER bl,bt,bn,bs,be,bw
99     C == Statement function ==
100     INTEGER tilemod
101     tilemod(I)=1+mod(I-1+6,6)
102 cnh 1.3 CEOP
103 adcroft 1.2
104 jmc 1.4 IF ( sNx.NE.sNy .OR.
105     & nSx.NE.6 .OR. nSy.NE.1 .OR.
106     & nPx.NE.1 .OR. nPy.NE.1 ) THEN
107     WRITE(msgBuf,'(2A)') 'EXCH_Z_RX_CUBE: Wrong Tiling'
108     CALL PRINT_ERROR( msgBuf, myThid )
109     WRITE(msgBuf,'(2A)') 'EXCH_Z_RX_CUBE: ',
110     & 'works only with sNx=sNy & nSx=6 & nSy=nPx=nPy=1'
111     CALL PRINT_ERROR( msgBuf, myThid )
112     STOP 'ABNORMAL END: EXCH_Z_RX_CUBE: Wrong Tiling'
113     ENDIF
114    
115 adcroft 1.2 theSimulationMode = simulationMode
116     theCornerMode = cornerMode
117    
118     C For now tile<->tile exchanges are sequentialised through
119     C thread 1. This is a temporary feature for preliminary testing until
120     C general tile decomposistion is in place (CNH April 11, 2001)
121     CALL BAR2( myThid )
122     IF ( myThid .EQ. 1 ) THEN
123    
124     DO repeat=1,2
125    
126     DO bl = 1, 5, 2
127    
128     bt = bl
129     bn=tilemod(bt+2)
130     bs=tilemod(bt-1)
131     be=tilemod(bt+1)
132     bw=tilemod(bt-2)
133    
134     DO K = 1, myNz
135     DO J = 1, sNy+1
136     DO I = 0, exchWidthX-1
137    
138     C Tile Odd:Odd+2 [get] [North<-West]
139     array(J,sNy+I+1,K,bt,1) = array(I+1,sNy+2-J,K,bn,1)
140     C Tile Odd:Odd+1 [get] [East<-West]
141     array(sNx+I+1,J,K,bt,1) = array(I+1,J,K,be,1)
142    
143     cs- these above loop should really have the same range the lower one
144     ENDDO
145     DO I = 1, exchWidthX-0
146     cs- but this replaces the missing I/O routines for now
147    
148     C Tile Odd:Odd-1 [get] [South<-North]
149     array(J,1-I,K,bt,1) = array(J,sNy+1-I,K,bs,1)
150     C Tile Odd:Odd-2 [get] [West<-North]
151     array(1-I,J,K,bt,1) = array(sNx+2-J,sNy+1-I,K,bw,1)
152    
153     ENDDO
154     ENDDO
155     ENDDO
156    
157     bt = bl+1
158     bn=tilemod(bt+1)
159     bs=tilemod(bt-2)
160     be=tilemod(bt+2)
161     bw=tilemod(bt-1)
162    
163     DO K = 1, myNz
164     DO J = 1, sNy+1
165     DO I = 0, exchWidthX-1
166    
167     C Tile Even:Even+1 [get] [North<-South]
168     array(J,sNy+I+1,K,bt,1) = array(J,I+1,K,bn,1)
169     C Tile Even:Even+2 [get] [East<-South]
170     array(sNx+I+1,J,K,bt,1) = array(sNx+2-J,I+1,K,be,1)
171    
172     cs- these above loop should really have the same range the lower one
173     ENDDO
174     DO I = 1, exchWidthX-0
175     cs- but this replaces the missing I/O routines for now
176    
177     C Tile Even:Even-2 [get] [South<-East]
178     array(J,1-I,K,bt,1) = array(sNx+1-I,sNy+2-J,K,bs,1)
179     C Tile Even:Even-1 [get] [West<-East]
180     array(1-I,J,K,bt,1) = array(sNx+1-I,J,K,bw,1)
181    
182     ENDDO
183     ENDDO
184     ENDDO
185    
186     ENDDO
187    
188     ENDDO
189    
190     ENDIF
191     CALL BAR2(myThid)
192    
193     RETURN
194     END

  ViewVC Help
Powered by ViewVC 1.1.22