/[MITgcm]/MITgcm/pkg/obcs/obcs_calc.F
ViewVC logotype

Contents of /MITgcm/pkg/obcs/obcs_calc.F

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


Revision 1.7 - (show annotations) (download)
Mon Sep 20 23:22:57 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55a_post
Changes since 1.6: +186 -4 lines
o merged code to
  * prescribe/read time-dependent open boundaries
    (works in conjunction with exf, cal)
  * sponge layer code for open boundaries
  * each boundary N/S/E/W now has its own CPP option
    (healthy for the adjoint)

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_calc.F,v 1.4.8.2 2002/02/09 02:18:03 heimbach Exp $
2 C $Name: $
3
4 #include "OBCS_OPTIONS.h"
5
6 SUBROUTINE OBCS_CALC( bi, bj, futureTime, futureIter,
7 & uVel, vVel, wVel, theta, salt,
8 & myThid )
9 C /==========================================================\
10 C | SUBROUTINE OBCS_CALC |
11 C | o Calculate future boundary data at open boundaries |
12 C | at time = futureTime |
13 C |==========================================================|
14 C | |
15 C \==========================================================/
16 IMPLICIT NONE
17
18 C === Global variables ===
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "GRID.h"
23 #include "OBCS.h"
24
25 C == Routine arguments ==
26 INTEGER bi, bj
27 INTEGER futureIter
28 _RL futureTime
29 _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
30 _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
31 _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
32 _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33 _RL salt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34 INTEGER myThid
35
36 #ifdef ALLOW_OBCS
37
38 C == Local variables ==
39 INTEGER I, J , K, I_obc, J_obc
40 _RL Tr_T, Ar_T, Tr, Ar
41
42 #ifdef ALLOW_OBCS_PRESCRIBE
43 C-- Calculate future values on open boundaries
44 CALL EXF_GETOBCS(futureTime, futureIter, mythid)
45 #endif
46
47 C-- OB values are calculated
48
49 C ------------------------------------------------------------------------------
50
51 #ifdef ALLOW_OBCS_EAST
52 C Eastern OB
53 IF (useOrlanskiEast) THEN
54 #ifdef ALLOW_ORLANSKI
55 CALL ORLANSKI_EAST(
56 & bi, bj, futureTime,
57 & uVel, vVel, wVel, theta, salt,
58 & myThid )
59 #endif
60 ELSE
61 DO K=1,Nr
62 DO J=1-Oly,sNy+Oly
63 I_obc=OB_Ie(J,bi,bj)
64 IF (I_obc.ne.0) THEN
65 OBEu(J,K,bi,bj)=0.
66 OBEv(J,K,bi,bj)=0.
67 OBEt(J,K,bi,bj)=tRef(K)
68 OBEs(J,K,bi,bj)=sRef(K)
69 #ifdef ALLOW_NONHYDROSTATIC
70 OBEw(J,K,bi,bj)=0.
71 #endif
72 #ifdef NONLIN_FRSURF
73 OBEeta(J,bi,bj)=0.
74 #endif
75 ENDIF
76 ENDDO
77 ENDDO
78 ENDIF
79
80 #ifdef ALLOW_OBCS_BALANCE
81
82 IF ( useOBCSbalance) THEN
83
84 Tr_T = 0. _d 0
85 Ar_T = 0. _d 0
86 DO K=1,Nr
87 DO J=1-Oly,sNy+Oly
88 I_obc=OB_Ie(J,bi,bj)
89 IF (I_obc.ne.0) THEN
90 Ar = drF(k)*hFacC(I_obc,j,k,bi,bj)*dyG(I_obc,j,bi,bj)
91 Ar_T = Ar_T + Ar
92 Tr_T = Tr_T + Ar * OBEu(J,K,bi,bj)
93 ENDIF
94 ENDDO
95 ENDDO
96
97 _GLOBAL_SUM_R8( Ar_T , myThid )
98 _GLOBAL_SUM_R8( Tr_T , myThid )
99
100 Tr_T = (0. - Tr_T)/Ar_T
101
102 DO K=1,Nr
103 DO J=1-Oly,sNy+Oly
104 I_obc=OB_Ie(J,bi,bj)
105 IF (I_obc.ne.0) THEN
106 OBEu(J,K,bi,bj) = OBEu(J,K,bi,bj) + Tr_T
107 OBEv(J,K,bi,bj) = 0.
108 ENDIF
109 ENDDO
110 ENDDO
111
112 ENDIF
113
114 #endif /* ALLOW_OBCS_BALANCE */
115
116 #endif
117
118 C ------------------------------------------------------------------------------
119
120 #ifdef ALLOW_OBCS_WEST
121 C Western OB
122 IF (useOrlanskiWest) THEN
123 #ifdef ALLOW_ORLANSKI
124 CALL ORLANSKI_WEST(
125 & bi, bj, futureTime,
126 & uVel, vVel, wVel, theta, salt,
127 & myThid )
128 #endif
129 ELSE
130 DO K=1,Nr
131 DO J=1-Oly,sNy+Oly
132 I_obc=OB_Iw(J,bi,bj)
133 IF (I_obc.ne.0) THEN
134 OBWu(J,K,bi,bj)=0.
135 OBWv(J,K,bi,bj)=0.
136 OBWt(J,K,bi,bj)=tRef(K)
137 OBWs(J,K,bi,bj)=sRef(K)
138 #ifdef ALLOW_NONHYDROSTATIC
139 OBWw(J,K,bi,bj)=0.
140 #endif
141 #ifdef NONLIN_FRSURF
142 OBWeta(J,bi,bj)=0.
143 #endif
144 ENDIF
145 ENDDO
146 ENDDO
147 ENDIF
148
149 #ifdef ALLOW_OBCS_BALANCE
150
151 IF ( useOBCSbalance) THEN
152
153 Tr_T = 0. _d 0
154 Ar_T = 0. _d 0
155 DO K=1,Nr
156 DO J=1-Oly,sNy+Oly
157 I_obc=OB_Iw(J,bi,bj)
158 IF (I_obc.ne.0) THEN
159 Ar = drF(k)*hFacC(I_obc,j,k,bi,bj)*dyG(I_obc,j,bi,bj)
160 Ar_T = Ar_T + Ar
161 Tr_T = Tr_T + Ar * OBWu(J,K,bi,bj)
162 ENDIF
163 ENDDO
164 ENDDO
165
166 _GLOBAL_SUM_R8( Ar_T , myThid )
167 _GLOBAL_SUM_R8( Tr_T , myThid )
168
169 Tr_T = (0. - Tr_T)/Ar_T
170
171 DO K=1,Nr
172 DO J=1-Oly,sNy+Oly
173 I_obc=OB_Iw(J,bi,bj)
174 IF (I_obc.ne.0) THEN
175 OBWu(J,K,bi,bj) = OBWu(J,K,bi,bj) + Tr_T
176 OBWv(J,K,bi,bj) = 0.
177 ENDIF
178 ENDDO
179 ENDDO
180
181 ENDIF
182
183 #endif /* ALLOW_OBCS_BALANCE */
184
185 #endif /* ALLOW_OBCS_WEST */
186
187 C ------------------------------------------------------------------------------
188
189 #ifdef ALLOW_OBCS_NORTH
190 C Northern OB
191 IF (useOrlanskiNorth) THEN
192 #ifdef ALLOW_ORLANSKI
193 CALL ORLANSKI_NORTH(
194 & bi, bj, futureTime,
195 & uVel, vVel, wVel, theta, salt,
196 & myThid )
197 #endif
198 ELSE
199 DO K=1,Nr
200 DO I=1-Olx,sNx+Olx
201 J_obc=OB_Jn(I,bi,bj)
202 IF (J_obc.ne.0) THEN
203 OBNv(I,K,bi,bj)=0.
204 OBNu(I,K,bi,bj)=0.
205 OBNt(I,K,bi,bj)=tRef(K)
206 OBNs(I,K,bi,bj)=sRef(K)
207 #ifdef ALLOW_NONHYDROSTATIC
208 OBNw(I,K,bi,bj)=0.
209 #endif
210 #ifdef NONLIN_FRSURF
211 OBNeta(J,bi,bj)=0.
212 #endif
213 ENDIF
214 ENDDO
215 ENDDO
216 ENDIF
217
218 #ifdef ALLOW_OBCS_BALANCE
219
220 IF ( useOBCSbalance) THEN
221
222 Tr_T = 0. _d 0
223 Ar_T = 0. _d 0
224 DO K=1,Nr
225 DO I=1-Olx,sNx+Olx
226 J_obc=OB_Jn(I,bi,bj)
227 IF (J_obc.ne.0) THEN
228 Ar = drF(k)*hFacC(i,J_obc,k,bi,bj)*dxG(i,J_obc,bi,bj)
229 Ar_T = Ar_T + Ar
230 Tr_T = Tr_T + Ar * OBNv(I,K,bi,bj)
231 ENDIF
232 ENDDO
233 ENDDO
234
235 _GLOBAL_SUM_R8( Ar_T , myThid )
236 _GLOBAL_SUM_R8( Tr_T , myThid )
237
238 Tr_T = (0. - Tr_T)/Ar_T
239
240 DO K=1,Nr
241 DO I=1-Olx,sNx+Olx
242 J_obc=OB_Jn(I,bi,bj)
243 IF (J_obc.ne.0) THEN
244 OBNu(I,K,bi,bj) = 0.
245 OBWv(I,K,bi,bj) = OBNv(I,K,bi,bj) + Tr_T
246 ENDIF
247 ENDDO
248 ENDDO
249
250 ENDIF
251
252 #endif /* ALLOW_OBCS_BALANCE */
253
254 #endif
255
256 C ------------------------------------------------------------------------------
257
258 #ifdef ALLOW_OBCS_SOUTH
259 C Southern OB
260 IF (useOrlanskiSouth) THEN
261 #ifdef ALLOW_ORLANSKI
262 CALL ORLANSKI_SOUTH(
263 & bi, bj, futureTime,
264 & uVel, vVel, wVel, theta, salt,
265 & myThid )
266 #endif
267 ELSE
268 DO K=1,Nr
269 DO I=1-Olx,sNx+Olx
270 J_obc=OB_Js(I,bi,bj)
271 IF (J_obc.ne.0) THEN
272 OBSu(I,K,bi,bj)=0.
273 OBSv(I,K,bi,bj)=0.
274 OBSt(I,K,bi,bj)=tRef(K)
275 OBSs(I,K,bi,bj)=sRef(K)
276 #ifdef ALLOW_NONHYDROSTATIC
277 OBSw(I,K,bi,bj)=0.
278 #endif
279 #ifdef NONLIN_FRSURF
280 OBSeta(J,bi,bj)=0.
281 #endif
282 ENDIF
283 ENDDO
284 ENDDO
285 ENDIF
286
287 #ifdef ALLOW_OBCS_BALANCE
288
289 IF ( useOBCSbalance) THEN
290
291 Tr_T = 0. _d 0
292 Ar_T = 0. _d 0
293 DO K=1,Nr
294 DO I=1-Olx,sNx+Olx
295 J_obc=OB_Js(I,bi,bj)
296 IF (J_obc.ne.0) THEN
297 Ar = drF(k)*hFacC(i,J_obc,k,bi,bj)*dxG(i,J_obc,bi,bj)
298 Ar_T = Ar_T + Ar
299 Tr_T = Tr_T + Ar * OBSv(I,K,bi,bj)
300 ENDIF
301 ENDDO
302 ENDDO
303
304 _GLOBAL_SUM_R8( Ar_T , myThid )
305 _GLOBAL_SUM_R8( Tr_T , myThid )
306
307 Tr_T = (0. - Tr_T)/Ar_T
308
309 DO K=1,Nr
310 DO I=1-Olx,sNx+Olx
311 J_obc=OB_Js(I,bi,bj)
312 IF (J_obc.ne.0) THEN
313 OBSu(I,K,bi,bj) = 0.
314 OBSv(I,K,bi,bj) = OBSv(I,K,bi,bj) + Tr_T
315 ENDIF
316 ENDDO
317 ENDDO
318
319 ENDIF
320
321 #endif /* ALLOW_OBCS_BALANCE */
322
323 #endif
324
325 #endif /* ALLOW_OBCS */
326
327 RETURN
328 END

  ViewVC Help
Powered by ViewVC 1.1.22