/[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.10 - (show annotations) (download)
Tue Oct 12 18:37:38 2004 UTC (19 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55g_post, checkpoint55f_post, checkpoint55e_post
Changes since 1.9: +2 -2 lines
bug fix for balancing OBNv

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_calc.F,v 1.9 2004/09/22 20:44:37 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_EAST
43 C Eastern OB
44 IF (useOrlanskiEast) THEN
45 #ifdef ALLOW_ORLANSKI
46 CALL ORLANSKI_EAST(
47 & bi, bj, futureTime,
48 & uVel, vVel, wVel, theta, salt,
49 & myThid )
50 #endif
51 ELSE
52 DO K=1,Nr
53 DO J=1-Oly,sNy+Oly
54 I_obc=OB_Ie(J,bi,bj)
55 IF (I_obc.ne.0) THEN
56 OBEu(J,K,bi,bj)=0.
57 OBEv(J,K,bi,bj)=0.
58 OBEt(J,K,bi,bj)=tRef(K)
59 OBEs(J,K,bi,bj)=sRef(K)
60 #ifdef ALLOW_NONHYDROSTATIC
61 OBEw(J,K,bi,bj)=0.
62 #endif
63 #ifdef NONLIN_FRSURF
64 OBEeta(J,bi,bj)=0.
65 #endif
66 ENDIF
67 ENDDO
68 ENDDO
69 ENDIF
70 #endif /* ALLOW_OBCS_EAST */
71
72 C ------------------------------------------------------------------------------
73
74 #ifdef ALLOW_OBCS_WEST
75 C Western OB
76 IF (useOrlanskiWest) THEN
77 #ifdef ALLOW_ORLANSKI
78 CALL ORLANSKI_WEST(
79 & bi, bj, futureTime,
80 & uVel, vVel, wVel, theta, salt,
81 & myThid )
82 #endif
83 ELSE
84 DO K=1,Nr
85 DO J=1-Oly,sNy+Oly
86 I_obc=OB_Iw(J,bi,bj)
87 IF (I_obc.ne.0) THEN
88 OBWu(J,K,bi,bj)=0.
89 OBWv(J,K,bi,bj)=0.
90 OBWt(J,K,bi,bj)=tRef(K)
91 OBWs(J,K,bi,bj)=sRef(K)
92 #ifdef ALLOW_NONHYDROSTATIC
93 OBWw(J,K,bi,bj)=0.
94 #endif
95 #ifdef NONLIN_FRSURF
96 OBWeta(J,bi,bj)=0.
97 #endif
98 ENDIF
99 ENDDO
100 ENDDO
101 ENDIF
102 #endif /* ALLOW_OBCS_WEST */
103
104 C ------------------------------------------------------------------------------
105
106 #ifdef ALLOW_OBCS_NORTH
107 C Northern OB
108 IF (useOrlanskiNorth) THEN
109 #ifdef ALLOW_ORLANSKI
110 CALL ORLANSKI_NORTH(
111 & bi, bj, futureTime,
112 & uVel, vVel, wVel, theta, salt,
113 & myThid )
114 #endif
115 ELSE
116 DO K=1,Nr
117 DO I=1-Olx,sNx+Olx
118 J_obc=OB_Jn(I,bi,bj)
119 IF (J_obc.ne.0) THEN
120 OBNv(I,K,bi,bj)=0.
121 OBNu(I,K,bi,bj)=0.
122 OBNt(I,K,bi,bj)=tRef(K)
123 OBNs(I,K,bi,bj)=sRef(K)
124 #ifdef ALLOW_NONHYDROSTATIC
125 OBNw(I,K,bi,bj)=0.
126 #endif
127 #ifdef NONLIN_FRSURF
128 OBNeta(J,bi,bj)=0.
129 #endif
130 ENDIF
131 ENDDO
132 ENDDO
133 ENDIF
134 #endif /* ALLOW_OBCS_NORTH */
135
136 C ------------------------------------------------------------------------------
137
138 #ifdef ALLOW_OBCS_SOUTH
139 C Southern OB
140 IF (useOrlanskiSouth) THEN
141 #ifdef ALLOW_ORLANSKI
142 CALL ORLANSKI_SOUTH(
143 & bi, bj, futureTime,
144 & uVel, vVel, wVel, theta, salt,
145 & myThid )
146 #endif
147 ELSE
148 DO K=1,Nr
149 DO I=1-Olx,sNx+Olx
150 J_obc=OB_Js(I,bi,bj)
151 IF (J_obc.ne.0) THEN
152 OBSu(I,K,bi,bj)=0.
153 OBSv(I,K,bi,bj)=0.
154 OBSt(I,K,bi,bj)=tRef(K)
155 OBSs(I,K,bi,bj)=sRef(K)
156 #ifdef ALLOW_NONHYDROSTATIC
157 OBSw(I,K,bi,bj)=0.
158 #endif
159 #ifdef NONLIN_FRSURF
160 OBSeta(J,bi,bj)=0.
161 #endif
162 ENDIF
163 ENDDO
164 ENDDO
165 ENDIF
166 #endif /* ALLOW_OBCS_SOUTH */
167
168
169 C ------------------------------------------------------------------------------
170
171 #ifdef ALLOW_OBCS_PRESCRIBE
172 IF (useOBCSprescribe) THEN
173 C-- Calculate future values on open boundaries
174 CALL OBCS_PRESCRIBE_READ(futureTime, futureIter, mythid)
175 ENDIF
176 #endif /* ALLOW_OBCS_PRESCRIBE */
177
178 C ------------------------------------------------------------------------------
179
180 #ifdef ALLOW_OBCS_BALANCE
181 IF ( useOBCSbalance) THEN
182
183 #ifdef ALLOW_OBCS_EAST
184 Tr_T = 0. _d 0
185 Ar_T = 0. _d 0
186 DO K=1,Nr
187 DO J=1-Oly,sNy+Oly
188 I_obc=OB_Ie(J,bi,bj)
189 IF (I_obc.ne.0) THEN
190 Ar = drF(k)*hFacC(I_obc,j,k,bi,bj)*dyG(I_obc,j,bi,bj)
191 Ar_T = Ar_T + Ar
192 Tr_T = Tr_T + Ar * OBEu(J,K,bi,bj)
193 ENDIF
194 ENDDO
195 ENDDO
196 _GLOBAL_SUM_R8( Ar_T , myThid )
197 _GLOBAL_SUM_R8( Tr_T , myThid )
198 Tr_T = (0. - Tr_T)/Ar_T
199 DO K=1,Nr
200 DO J=1-Oly,sNy+Oly
201 I_obc=OB_Ie(J,bi,bj)
202 IF (I_obc.ne.0) THEN
203 OBEu(J,K,bi,bj) = OBEu(J,K,bi,bj) + Tr_T
204 c OBEv(J,K,bi,bj) = 0.
205 ENDIF
206 ENDDO
207 ENDDO
208 #endif
209
210 #ifdef ALLOW_OBCS_WEST
211 Tr_T = 0. _d 0
212 Ar_T = 0. _d 0
213 DO K=1,Nr
214 DO J=1-Oly,sNy+Oly
215 I_obc=OB_Iw(J,bi,bj)
216 IF (I_obc.ne.0) THEN
217 Ar = drF(k)*hFacC(I_obc,j,k,bi,bj)*dyG(I_obc,j,bi,bj)
218 Ar_T = Ar_T + Ar
219 Tr_T = Tr_T + Ar * OBWu(J,K,bi,bj)
220 ENDIF
221 ENDDO
222 ENDDO
223 _GLOBAL_SUM_R8( Ar_T , myThid )
224 _GLOBAL_SUM_R8( Tr_T , myThid )
225 Tr_T = (0. - Tr_T)/Ar_T
226 DO K=1,Nr
227 DO J=1-Oly,sNy+Oly
228 I_obc=OB_Iw(J,bi,bj)
229 IF (I_obc.ne.0) THEN
230 OBWu(J,K,bi,bj) = OBWu(J,K,bi,bj) + Tr_T
231 c OBWv(J,K,bi,bj) = 0.
232 ENDIF
233 ENDDO
234 ENDDO
235 #endif
236
237 #ifdef ALLOW_OBCS_NORTH
238 Tr_T = 0. _d 0
239 Ar_T = 0. _d 0
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 Ar = drF(k)*hFacC(i,J_obc,k,bi,bj)*dxG(i,J_obc,bi,bj)
245 Ar_T = Ar_T + Ar
246 Tr_T = Tr_T + Ar * OBNv(I,K,bi,bj)
247 ENDIF
248 ENDDO
249 ENDDO
250 _GLOBAL_SUM_R8( Ar_T , myThid )
251 _GLOBAL_SUM_R8( Tr_T , myThid )
252 Tr_T = (0. - Tr_T)/Ar_T
253 DO K=1,Nr
254 DO I=1-Olx,sNx+Olx
255 J_obc=OB_Jn(I,bi,bj)
256 IF (J_obc.ne.0) THEN
257 c OBNu(I,K,bi,bj) = 0.
258 OBNv(I,K,bi,bj) = OBNv(I,K,bi,bj) + Tr_T
259 ENDIF
260 ENDDO
261 ENDDO
262 #endif
263
264 #ifdef ALLOW_OBCS_SOUTH
265 Tr_T = 0. _d 0
266 Ar_T = 0. _d 0
267 DO K=1,Nr
268 DO I=1-Olx,sNx+Olx
269 J_obc=OB_Js(I,bi,bj)
270 IF (J_obc.ne.0) THEN
271 Ar = drF(k)*hFacC(i,J_obc,k,bi,bj)*dxG(i,J_obc,bi,bj)
272 Ar_T = Ar_T + Ar
273 Tr_T = Tr_T + Ar * OBSv(I,K,bi,bj)
274 ENDIF
275 ENDDO
276 ENDDO
277 _GLOBAL_SUM_R8( Ar_T , myThid )
278 _GLOBAL_SUM_R8( Tr_T , myThid )
279 Tr_T = (0. - Tr_T)/Ar_T
280 DO K=1,Nr
281 DO I=1-Olx,sNx+Olx
282 J_obc=OB_Js(I,bi,bj)
283 IF (J_obc.ne.0) THEN
284 c OBSu(I,K,bi,bj) = 0.
285 OBSv(I,K,bi,bj) = OBSv(I,K,bi,bj) + Tr_T
286 ENDIF
287 ENDDO
288 ENDDO
289 #endif
290
291 ENDIF
292 #endif /* ALLOW_OBCS_BALANCE */
293
294 #endif /* ALLOW_OBCS */
295
296 RETURN
297 END

  ViewVC Help
Powered by ViewVC 1.1.22