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

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

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


Revision 1.3 - (hide annotations) (download)
Sun Jul 24 01:35:06 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.2: +26 -14 lines
filling of face-corner halo regions is now optional (ifdef W2_FILL_NULL_REGIONS)
 and using a filling value (non necessary zero, for testing purpose).
Default is #undef W2_FILL_NULL_REGIONS

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

  ViewVC Help
Powered by ViewVC 1.1.22