/[MITgcm]/MITgcm/pkg/exch2/exch2_3d_rx.template
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_3d_rx.template

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


Revision 1.3 - (hide annotations) (download)
Sat Jul 28 16:07:35 2007 UTC (16 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.2: +2 -2 lines
Comment a bunch of EESUPPORT.h includes which are not necessary
and interfere with parallel exch2 adjoint ('cph-mpi').

1 heimbach 1.3 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_3d_rx.template,v 1.2 2006/11/18 01:09:00 heimbach Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: EXCH2_3D_RX
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_3D_RX(
12     U phi,
13     I myNz, myThid )
14    
15     C !DESCRIPTION:
16     C *==========================================================*
17     C | SUBROUTINE EXCH2_3D_RX
18     C | o Handle exchanges for _RX, three-dim scalar arrays.
19     C *==========================================================*
20     C | Invoke appropriate exchange routine depending on type
21     C | of grid (cube or globally indexed) to be operated on.
22     C *==========================================================*
23    
24     C !USES:
25     IMPLICIT NONE
26     C === Global data ===
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29 heimbach 1.3 cph-mpi#include "EESUPPORT.h"
30 jmc 1.1 #include "W2_EXCH2_TOPOLOGY.h"
31     #include "W2_EXCH2_PARAMS.h"
32    
33     C !INPUT/OUTPUT PARAMETERS:
34     C === Routine arguments ===
35     C phi :: Array with overlap regions are to be exchanged
36     C myNz :: 3rd dimension of array to exchange
37     C myThid :: My thread id.
38     INTEGER myNz
39     _RX phi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
40     INTEGER myThid
41    
42     C !LOCAL VARIABLES:
43     C == Local variables ==
44     C OL[wens] :: Overlap extents in west, east, north, south.
45     C exchWidth[XY] :: Extent of regions that will be exchanged.
46     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
47     #ifdef W2_FILL_NULL_REGIONS
48     INTEGER bi, bj, myTile, i, j, k
49     #endif
50    
51     CEOP
52    
53     OLw = OLx
54     OLe = OLx
55     OLn = OLy
56     OLs = OLy
57     exchWidthX = OLx
58     exchWidthY = OLy
59     C ** NOTE ** The exchange routine we use here does not
60     C require the preceeding and following barriers.
61     C However, the slow, simple exchange interface
62     C that is calling it here is meant to ensure
63     C that threads are synchronised before exchanges
64     C begine.
65    
66     IF (useCubedSphereExchange) THEN
67    
68     CALL EXCH2_RX1_CUBE( phi, 'T ',
69     I OLw, OLe, OLs, OLn, myNz,
70     I exchWidthX, exchWidthY,
71     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
72    
73     #ifdef W2_FILL_NULL_REGIONS
74     DO bj=myByLo(myThid),myByHi(myThid)
75     DO bi=myBxLo(myThid),myBxHi(myThid)
76     myTile = W2_myTileList(bi)
77     C South-east corner
78     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
79     & exch2_isSedge(myTile) .EQ. 1 ) THEN
80     DO j=1-OLy,0
81     DO i=sNx+1,sNx+OLx
82     DO k=1,myNz
83     phi(i,j,k,bi,bj)=e2FillValue_RX
84     ENDDO
85     ENDDO
86     ENDDO
87     ENDIF
88     C North-east corner
89     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
90     & exch2_isNedge(myTile) .EQ. 1 ) THEN
91     DO j=sNy+1,sNy+OLy
92     DO i=sNx+1,sNx+OLx
93     DO k=1,myNz
94     phi(i,j,k,bi,bj)=e2FillValue_RX
95     ENDDO
96     ENDDO
97     ENDDO
98     ENDIF
99     C South-west corner
100     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
101     & exch2_isSedge(myTile) .EQ. 1 ) THEN
102     DO j=1-OLy,0
103     DO i=1-OLx,0
104     DO k=1,myNz
105     phi(i,j,k,bi,bj)=e2FillValue_RX
106     ENDDO
107     ENDDO
108     ENDDO
109     ENDIF
110     C North-west corner
111     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
112     & exch2_isNedge(myTile) .EQ. 1 ) THEN
113     DO j=sNy+1,sNy+OLy
114     DO i=1-OLx,0
115     DO k=1,myNz
116     phi(i,j,k,bi,bj)=e2FillValue_RX
117     ENDDO
118     ENDDO
119     ENDDO
120     ENDIF
121     ENDDO
122     ENDDO
123     #endif /* W2_FILL_NULL_REGIONS */
124    
125     CALL EXCH2_RX1_CUBE( phi, 'T ',
126     I OLw, OLe, OLs, OLn, myNz,
127     I exchWidthX, exchWidthY,
128     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
129    
130     #ifdef W2_FILL_NULL_REGIONS
131     DO bj=myByLo(myThid),myByHi(myThid)
132     DO bi=myBxLo(myThid),myBxHi(myThid)
133     myTile = W2_myTileList(bi)
134     C South-east corner
135     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
136     & exch2_isSedge(myTile) .EQ. 1 ) THEN
137     DO j=1-OLy,0
138     DO i=sNx+1,sNx+OLx
139     DO k=1,myNz
140     phi(i,j,k,bi,bj)=e2FillValue_RX
141     ENDDO
142     ENDDO
143     ENDDO
144     ENDIF
145     C North-east corner
146     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
147     & exch2_isNedge(myTile) .EQ. 1 ) THEN
148     DO j=sNy+1,sNy+OLy
149     DO i=sNx+1,sNx+OLx
150     DO k=1,myNz
151     phi(i,j,k,bi,bj)=e2FillValue_RX
152     ENDDO
153     ENDDO
154     ENDDO
155     ENDIF
156     C South-west corner
157     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
158     & exch2_isSedge(myTile) .EQ. 1 ) THEN
159     DO j=1-OLy,0
160     DO i=1-OLx,0
161     DO k=1,myNz
162     phi(i,j,k,bi,bj)=e2FillValue_RX
163     ENDDO
164     ENDDO
165     ENDDO
166     ENDIF
167     C North-west corner
168     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
169     & exch2_isNedge(myTile) .EQ. 1 ) THEN
170     DO j=sNy+1,sNy+OLy
171     DO i=1-OLx,0
172     DO k=1,myNz
173     phi(i,j,k,bi,bj)=e2FillValue_RX
174     ENDDO
175     ENDDO
176     ENDDO
177     ENDIF
178     ENDDO
179     ENDDO
180     #endif /* W2_FILL_NULL_REGIONS */
181    
182     ELSE
183    
184 heimbach 1.2 #ifndef AUTODIFF_EXCH2
185 jmc 1.1 CALL EXCH_RX( phi,
186     I OLw, OLe, OLs, OLn, myNz,
187     I exchWidthX, exchWidthY,
188     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
189 heimbach 1.2 #endif
190 jmc 1.1
191     ENDIF
192    
193     RETURN
194     END
195    
196     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
197    
198     CEH3 ;;; Local Variables: ***
199     CEH3 ;;; mode:fortran ***
200     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22