/[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.11 - (show annotations) (download)
Tue Oct 19 17:40:17 2004 UTC (19 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57r_post, checkpoint57d_post, checkpoint57i_post, checkpoint57, checkpoint56, checkpoint57n_post, checkpoint55i_post, checkpoint57l_post, checkpoint57t_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint57h_post, checkpoint57c_post, checkpoint57c_pre, checkpoint55j_post, checkpoint55h_post, checkpoint57e_post, checkpoint57p_post, checkpoint57q_post, eckpoint57e_pre, checkpoint56a_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint57o_post, checkpoint57k_post
Changes since 1.10: +26 -1 lines
Added some debug_msg() lines to track a bug in obcs/exf

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

  ViewVC Help
Powered by ViewVC 1.1.22