/[MITgcm]/MITgcm/pkg/exch2/exch2_get_uv_bounds.F
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_get_uv_bounds.F

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


Revision 1.3 - (hide annotations) (download)
Mon Mar 26 19:13:15 2012 UTC (12 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o
Changes since 1.2: +39 -3 lines
add argument "updateCorners" to S/R exch2_get_uv_bounds (enable to
switch to EXCH_IGNORE_CORNERS in vector EXCH S/R)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_get_uv_bounds.F,v 1.2 2009/05/30 21:22:13 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     CBOP
5     C !ROUTINE: EXCH2_GET_UV_BOUNDS
6    
7     C !INTERFACE:
8     SUBROUTINE EXCH2_GET_UV_BOUNDS(
9 jmc 1.3 I fCode, eWdth, updateCorners,
10 jmc 1.2 I tgTile, tgNb,
11     O tIlo1, tIhi1, tJlo1, tJhi1,
12     O tIlo2, tIhi2, tJlo2, tJhi2,
13     O tiStride, tjStride,
14     O e2_oi1, e2_oj1, e2_oi2, e2_oj2,
15     I myThid )
16 jmc 1.1
17     C !DESCRIPTION:
18 jmc 1.2 C Return the index range & step of the part of the array (overlap-region)
19     C which is going to be updated by the exchange with 1 neighbour.
20     C 2 components vector field (UV) version.
21    
22 jmc 1.1
23     C !USES:
24     IMPLICIT NONE
25     C == Global data ==
26 jmc 1.2 #include "SIZE.h"
27     #include "W2_EXCH2_SIZE.h"
28     #include "W2_EXCH2_TOPOLOGY.h"
29 jmc 1.1
30     C !INPUT/OUTPUT PARAMETERS:
31 jmc 1.2 C fCode :: field code (position on staggered grid)
32     C eWdth :: width of data region to exchange
33     C updateCorners :: flag, do update corner halo region if true
34     C tgTile :: target tile
35     C tgNb :: target Neighbour entry
36     C tIlo1, tIhi1 :: index range in I that will be filled in 1rst comp. array
37     C tJlo1, tJhi1 :: index range in J that will be filled in 1rst comp. array
38     C tIlo2, tIhi2 :: index range in I that will be filled in 2nd comp. array
39     C tJlo2, tJhi2 :: index range in J that will be filled in 2nd comp. array
40     C tiStride :: index step in I that will be filled in target arrays
41     C tjStride :: index step in J that will be filled in target arrays
42     C e2_oi1 :: index offset in target to source-1 index relation
43     C e2_oj1 :: index offset in target to source-1 index relation
44     C e2_oi2 :: index offset in target to source-2 index relation
45     C e2_oj2 :: index offset in target to source-2 index relation
46     C myThid :: my Thread Id. number
47 jmc 1.1
48     CHARACTER*2 fCode
49     INTEGER eWdth
50 jmc 1.3 LOGICAL updateCorners
51 jmc 1.2 INTEGER tgTile, tgNb
52 jmc 1.1 INTEGER tIlo1, tIhi1, tJlo1, tJhi1
53     INTEGER tIlo2, tIhi2, tJlo2, tJhi2
54     INTEGER tiStride, tjStride
55     INTEGER e2_oi1, e2_oj1
56     INTEGER e2_oi2, e2_oj2
57     INTEGER myThid
58     C
59     C !LOCAL VARIABLES:
60 jmc 1.2 C soTile :: source tile
61     C soNb :: source Neighbour entry
62     INTEGER soTile
63     INTEGER soNb
64     INTEGER tIlo, tIhi, tJlo, tJhi
65     INTEGER i, e2_pij(4)
66 jmc 1.1
67     C--- exch2 target to source index relation:
68     C is = pij(1)*it + pij(2)*jt + oi
69     C js = pij(3)*it + pij(4)*jt + oj
70    
71 jmc 1.2 C--- Initialise index range from Topology values:
72     tIlo = exch2_iLo(tgNb,tgTile)
73     tIhi = exch2_iHi(tgNb,tgTile)
74     tJlo = exch2_jLo(tgNb,tgTile)
75     tJhi = exch2_jHi(tgNb,tgTile)
76     soNb = exch2_opposingSend(tgNb,tgTile)
77     soTile = exch2_neighbourId(tgNb,tgTile)
78     e2_oi1 = exch2_oi(soNb,soTile)
79     e2_oj1 = exch2_oj(soNb,soTile)
80     DO i=1,4
81     e2_pij(i) = exch2_pij(i,soNb,soTile)
82     ENDDO
83 jmc 1.1
84     C--- Expand index range according to exchange-Width "eWdth"
85     IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
86 jmc 1.2 C Filling a west edge overlap
87 jmc 1.1 tIlo1 = 1-eWdth
88     tIhi1 = 0
89 jmc 1.2 tiStride = 1
90 jmc 1.1 IF ( tJlo.LE.tJhi ) THEN
91     tjStride=1
92     ELSE
93     tjStride=-1
94     ENDIF
95 jmc 1.3 IF ( updateCorners ) THEN
96 jmc 1.2 tJlo1 = tJlo-tjStride*(eWdth-1)
97     tJhi1 = tJhi+tjStride*(eWdth-1)
98 jmc 1.3 ELSE
99     tJlo1 = tJlo+tjStride
100     tJhi1 = tJhi-tjStride
101     ENDIF
102 jmc 1.1 ENDIF
103     IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
104 jmc 1.2 C Filling an east edge overlap
105     tIlo1 = tIlo
106 jmc 1.1 tIhi1 = tIhi+eWdth-1
107 jmc 1.2 tiStride = 1
108 jmc 1.1 IF ( tJlo.LE.tJhi ) THEN
109 jmc 1.2 tjStride = 1
110 jmc 1.1 ELSE
111 jmc 1.2 tjStride =-1
112 jmc 1.1 ENDIF
113 jmc 1.3 IF ( updateCorners ) THEN
114 jmc 1.2 tJlo1 = tJlo-tjStride*(eWdth-1)
115     tJhi1 = tJhi+tjStride*(eWdth-1)
116 jmc 1.3 ELSE
117     tJlo1 = tJlo+tjStride
118     tJhi1 = tJhi-tjStride
119     ENDIF
120 jmc 1.1 ENDIF
121     IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
122 jmc 1.2 C Filling a south edge overlap
123 jmc 1.1 tJlo1 = 1-eWdth
124     tJhi1 = 0
125 jmc 1.2 tjStride = 1
126 jmc 1.1 IF ( tIlo .LE. tIhi ) THEN
127 jmc 1.2 tiStride = 1
128 jmc 1.1 ELSE
129 jmc 1.2 tiStride =-1
130 jmc 1.1 ENDIF
131 jmc 1.3 IF ( updateCorners ) THEN
132 jmc 1.2 tIlo1 = tIlo-tiStride*(eWdth-1)
133     tIhi1 = tIhi+tiStride*(eWdth-1)
134 jmc 1.3 ELSE
135     tIlo1 = tIlo+tiStride
136     tIhi1 = tIhi-tiStride
137     ENDIF
138 jmc 1.1 ENDIF
139     IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
140 jmc 1.2 C Filling a north edge overlap
141     tJlo1 = tJlo
142 jmc 1.1 tJhi1 = tJhi+eWdth-1
143 jmc 1.2 tjStride = 1
144 jmc 1.1 IF ( tIlo.LE.tIhi ) THEN
145 jmc 1.2 tiStride = 1
146 jmc 1.1 ELSE
147 jmc 1.2 tiStride =-1
148 jmc 1.1 ENDIF
149 jmc 1.3 IF ( updateCorners ) THEN
150 jmc 1.2 tIlo1 = tIlo-tiStride*(eWdth-1)
151     tIhi1 = tIhi+tiStride*(eWdth-1)
152 jmc 1.3 ELSE
153     tIlo1 = tIlo+tiStride
154     tIhi1 = tIhi-tiStride
155     ENDIF
156 jmc 1.1 ENDIF
157    
158     C--- copy to 2nd set of indices
159     tIlo2 = tIlo1
160     tIhi2 = tIhi1
161     tJlo2 = tJlo1
162     tJhi2 = tJhi1
163     e2_oi2 = e2_oi1
164     e2_oj2 = e2_oj1
165    
166     IF ( fCode.EQ.'Cg' ) THEN
167     C--- UV C-Grid specific code: start here
168    
169     C--- half grid-cell location with inverse index relation
170     C => increase the offset by 1 (relative to tracer cell-centered offset)
171     C if pij(1) is -1 then +i in source aligns with -i in target
172     C if pij(3) is -1 then +j in source aligns with -i in target
173     IF ( e2_pij(1) .EQ. -1 ) THEN
174     e2_oi1 = e2_oi1 + 1
175     ENDIF
176     IF ( e2_pij(3) .EQ. -1 ) THEN
177     e2_oj1 = e2_oj1 + 1
178     ENDIF
179     C if pij(2) is -1 then +i in source aligns with -j in target
180     C if pij(4) is -1 then +j in source aligns with -j in target
181     IF ( e2_pij(2) .EQ. -1 ) THEN
182     e2_oi2 = e2_oi2 + 1
183     ENDIF
184     IF ( e2_pij(4) .EQ. -1 ) THEN
185     e2_oj2 = e2_oj2 + 1
186     ENDIF
187 jmc 1.3
188     C--- adjust index lower and upper bounds (fct of updateCorners):
189     IF ( updateCorners ) THEN
190    
191 jmc 1.1 C-- as a consequence, need also to increase the index lower bound
192     C (avoid "out-of bounds" problems ; formerly itlreduce,jtlreduce)
193     IF ( e2_pij(1).EQ.-1 .OR. e2_pij(3).EQ.-1 ) tIlo1 = tIlo1+1
194     IF ( e2_pij(2).EQ.-1 .OR. e2_pij(4).EQ.-1 ) tJlo2 = tJlo2+1
195    
196     C--- Avoid updating (some) tile-corner halo region if across faces
197     c IF ( tIlo.EQ.tIhi .AND. tIlo.EQ.0 ) THEN
198 jmc 1.2 c IF ( exch2_isSedge(tgTile).EQ.1 ) THEN
199 jmc 1.1 C- West edge is touching the face S edge
200     c tJlo1 = tJlo+1
201     c tJlo2 = tJlo+1
202     c ENDIF
203 jmc 1.2 c IF ( exch2_isNedge(tgTile).EQ.1 ) THEN
204 jmc 1.1 C- West edge is touching the face N edge
205     c tJhi1 = tJhi-1
206     c tJhi2 = tJhi
207     c ENDIF
208     c ENDIF
209     IF ( tIlo.EQ.tIhi .AND. tIlo.GT.1 ) THEN
210 jmc 1.2 IF ( exch2_isSedge(tgTile).EQ.1 ) THEN
211 jmc 1.1 C- East edge is touching the face S edge
212     tJlo1 = tJlo+1
213     tJlo2 = tJlo+1
214     ENDIF
215 jmc 1.2 IF ( exch2_isNedge(tgTile).EQ.1 ) THEN
216 jmc 1.1 C- East edge is touching the face N edge
217     tJhi1 = tJhi-1
218     tJhi2 = tJhi
219     ENDIF
220     ENDIF
221     c IF ( tJlo.EQ.tJhi .AND. tJlo.EQ.0 ) THEN
222 jmc 1.2 c IF ( exch2_isWedge(tgTile).EQ.1 ) THEN
223 jmc 1.1 C- South edge is touching the face W edge
224     c tIlo1 = tIlo+1
225     c tIlo2 = tIlo+1
226     c ENDIF
227 jmc 1.2 c IF ( exch2_isEedge(tgTile).EQ.1 ) THEN
228 jmc 1.1 C- South Edge is touching the face E edge
229     c tIhi1 = tIhi
230     c tIhi2 = tIhi-1
231     c ENDIF
232     c ENDIF
233     IF ( tJlo.EQ.tJhi .AND. tJlo.GT.1 ) THEN
234 jmc 1.2 IF ( exch2_isWedge(tgTile).EQ.1 ) THEN
235 jmc 1.1 C- North edge is touching the face W edge
236     tIlo1 = tIlo+1
237     tIlo2 = tIlo+1
238     ENDIF
239 jmc 1.2 IF ( exch2_isEedge(tgTile).EQ.1 ) THEN
240 jmc 1.1 C- North Edge is touching the face E edge
241     tIhi1 = tIhi
242     tIhi2 = tIhi-1
243     ENDIF
244     ENDIF
245    
246 jmc 1.3 ELSE
247     C--- adjust index lower and upper bounds (updateCorners = F case):
248     IF ( e2_pij(1).EQ.-1 .OR. e2_pij(3).EQ.-1 ) THEN
249     tIlo1 = tIlo1+1
250     tIhi1 = tIhi1+1
251     ENDIF
252     IF ( e2_pij(2).EQ.-1 .OR. e2_pij(4).EQ.-1 ) THEN
253     tJlo2 = tJlo2+1
254     tJhi2 = tJhi2+1
255     ENDIF
256     ENDIF
257    
258 jmc 1.1 C--- UV C-Grid specific code: end
259    
260     ELSEIF ( fCode.NE.'Ag' ) THEN
261     STOP 'ABNORMAL END: S/R EXCH2_GET_UV_BOUNDS (wrong fCode)'
262     ENDIF
263    
264     RETURN
265     END

  ViewVC Help
Powered by ViewVC 1.1.22