/[MITgcm]/MITgcm/pkg/ctrl/ctrl_getobcse.F
ViewVC logotype

Contents of /MITgcm/pkg/ctrl/ctrl_getobcse.F

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


Revision 1.8 - (show annotations) (download)
Wed Jan 19 08:42:06 2011 UTC (13 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62t, checkpoint62s, checkpoint62r
Changes since 1.7: +8 -19 lines
simplify code so that it does not need to use S/R exf_swapfields

1 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_getobcse.F,v 1.7 2007/10/09 00:00:00 jmc Exp $
2 C $Name: $
3
4 #include "CTRL_CPPOPTIONS.h"
5 #ifdef ALLOW_OBCS
6 # include "OBCS_OPTIONS.h"
7 #endif
8
9
10 subroutine ctrl_getobcse(
11 I mytime,
12 I myiter,
13 I mythid
14 & )
15
16 c ==================================================================
17 c SUBROUTINE ctrl_getobcse
18 c ==================================================================
19 c
20 c o Get eastern obc of the control vector and add it
21 c to dyn. fields
22 c
23 c started: heimbach@mit.edu, 29-Aug-2001
24 c
25 c ==================================================================
26 c SUBROUTINE ctrl_getobcse
27 c ==================================================================
28
29 implicit none
30
31 #ifdef ALLOW_OBCSE_CONTROL
32
33 c == global variables ==
34
35 #include "EEPARAMS.h"
36 #include "SIZE.h"
37 #include "PARAMS.h"
38 #include "GRID.h"
39 #include "OBCS.h"
40
41 #include "ctrl.h"
42 #include "ctrl_dummy.h"
43 #include "optim.h"
44
45 c == routine arguments ==
46
47 _RL mytime
48 integer myiter
49 integer mythid
50
51 c == local variables ==
52
53 integer bi,bj
54 integer i,j,k
55 integer itlo,ithi
56 integer jtlo,jthi
57 integer jmin,jmax
58 integer imin,imax
59 integer ilobcse
60 integer iobcs
61
62 _RL dummy
63 _RL obcsefac
64 logical obcsefirst
65 logical obcsechanged
66 integer obcsecount0
67 integer obcsecount1
68 integer ip1
69
70 cgg _RL maskyz (1-oly:sny+oly,nr,nsx,nsy)
71
72 logical doglobalread
73 logical ladinit
74
75 character*(80) fnameobcse
76
77 cgg( Variables for splitting barotropic/baroclinic vels.
78 _RL ubaro
79 _RL utop
80 cgg)
81
82 c == external functions ==
83
84 integer ilnblnk
85 external ilnblnk
86
87
88 c == end of interface ==
89
90 jtlo = mybylo(mythid)
91 jthi = mybyhi(mythid)
92 itlo = mybxlo(mythid)
93 ithi = mybxhi(mythid)
94 jmin = 1-oly
95 jmax = sny+oly
96 imin = 1-olx
97 imax = snx+olx
98 ip1 = 0
99
100 cgg( Initialize variables for balancing volume flux.
101 ubaro = 0.d0
102 utop = 0.d0
103 cgg)
104
105 c-- Now, read the control vector.
106 doglobalread = .false.
107 ladinit = .false.
108
109 if (optimcycle .ge. 0) then
110 ilobcse=ilnblnk( xx_obcse_file )
111 write(fnameobcse(1:80),'(2a,i10.10)')
112 & xx_obcse_file(1:ilobcse), '.', optimcycle
113 endif
114
115 c-- Get the counters, flags, and the interpolation factor.
116 call ctrl_get_gen_rec(
117 I xx_obcsestartdate, xx_obcseperiod,
118 O obcsefac, obcsefirst, obcsechanged,
119 O obcsecount0,obcsecount1,
120 I mytime, myiter, mythid )
121
122 do iobcs = 1,nobcs
123
124 if ( obcsefirst ) then
125 call active_read_yz( fnameobcse, tmpfldyz,
126 & (obcsecount0-1)*nobcs+iobcs,
127 & doglobalread, ladinit, optimcycle,
128 & mythid, xx_obcse_dummy )
129
130 #ifdef ALLOW_CTRL_OBCS_BALANCE
131
132 if ( optimcycle .gt. 0) then
133 if (iobcs .eq. 3) then
134 cgg Special attention is needed for the normal velocity.
135 cgg For the north, this is the v velocity, iobcs = 4.
136 cgg This is done on a columnwise basis here.
137 do bj = jtlo,jthi
138 do bi = itlo, ithi
139 do j = jmin,jmax
140 i = OB_Ie(J,bi,bj)
141
142 cgg The barotropic velocity is stored in the level 1.
143 ubaro = tmpfldyz(j,1,bi,bj)
144 tmpfldyz(j,1,bi,bj) = 0.d0
145 utop = 0.d0
146
147 do k = 1,Nr
148 cgg If cells are not full, this should be modified with hFac.
149 cgg
150 cgg The xx field (tmpfldxz) does not contain the velocity at the
151 cgg surface level. This velocity is not independent; it must
152 cgg exactly balance the volume flux, since we are dealing with
153 cgg the baroclinic velocity structure..
154 utop = tmpfldyz(j,k,bi,bj)*
155 & maskW(i+ip1,j,k,bi,bj) * delR(k) + utop
156 cgg Add the barotropic velocity component.
157 if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
158 tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
159 endif
160 enddo
161 cgg Compute the baroclinic velocity at level 1. Should balance flux.
162 tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
163 & - utop / delR(1)
164 enddo
165 enddo
166 enddo
167 endif
168 if (iobcs .eq. 4) then
169 cgg Special attention is needed for the normal velocity.
170 cgg For the north, this is the v velocity, iobcs = 4.
171 cgg This is done on a columnwise basis here.
172 do bj = jtlo,jthi
173 do bi = itlo, ithi
174 do j = jmin,jmax
175 i = OB_Ie(J,bi,bj)
176
177 cgg The barotropic velocity is stored in the level 1.
178 ubaro = tmpfldyz(j,1,bi,bj)
179 tmpfldyz(j,1,bi,bj) = 0.d0
180 utop = 0.d0
181
182 do k = 1,Nr
183 cgg If cells are not full, this should be modified with hFac.
184 cgg
185 cgg The xx field (tmpfldxz) does not contain the velocity at the
186 cgg surface level. This velocity is not independent; it must
187 cgg exactly balance the volume flux, since we are dealing with
188 cgg the baroclinic velocity structure..
189 utop = tmpfldyz(j,k,bi,bj)*
190 & maskS(i,j,k,bi,bj) * delR(k) + utop
191 cgg Add the barotropic velocity component.
192 if (maskS(i,j,k,bi,bj) .ne. 0.) then
193 tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
194 endif
195 enddo
196 cgg Compute the baroclinic velocity at level 1. Should balance flux.
197 tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
198 & - utop / delR(1)
199 enddo
200 enddo
201 enddo
202 endif
203 endif
204
205 #endif /* ALLOW_CTRL_OBCS_BALANCE */
206
207 do bj = jtlo,jthi
208 do bi = itlo,ithi
209 do k = 1,nr
210 do j = jmin,jmax
211 xx_obcse1(j,k,bi,bj,iobcs) = tmpfldyz (j,k,bi,bj)
212 cgg & * maskyz (j,k,bi,bj)
213 enddo
214 enddo
215 enddo
216 enddo
217 endif
218
219 if ( (obcsefirst) .or. (obcsechanged)) then
220
221 do bj = jtlo,jthi
222 do bi = itlo,ithi
223 do j = jmin,jmax
224 do k = 1,nr
225 xx_obcse0(j,k,bi,bj,iobcs) = xx_obcse1(j,k,bi,bj,iobcs)
226 tmpfldyz (j,k,bi,bj) = 0. _d 0
227 enddo
228 enddo
229 enddo
230 enddo
231
232 call active_read_yz( fnameobcse, tmpfldyz,
233 & (obcsecount1-1)*nobcs+iobcs,
234 & doglobalread, ladinit, optimcycle,
235 & mythid, xx_obcse_dummy )
236
237 #ifdef ALLOW_CTRL_OBCS_BALANCE
238
239 if ( optimcycle .gt. 0) then
240 if (iobcs .eq. 3) then
241 cgg Special attention is needed for the normal velocity.
242 cgg For the north, this is the v velocity, iobcs = 4.
243 cgg This is done on a columnwise basis here.
244 do bj = jtlo,jthi
245 do bi = itlo, ithi
246 do j = jmin,jmax
247 i = OB_Ie(J,bi,bj)
248
249 cgg The barotropic velocity is stored in the level 1.
250 ubaro = tmpfldyz(j,1,bi,bj)
251 tmpfldyz(j,1,bi,bj) = 0.d0
252 utop = 0.d0
253
254 do k = 1,Nr
255 cgg If cells are not full, this should be modified with hFac.
256 cgg
257 cgg The xx field (tmpfldxz) does not contain the velocity at the
258 cgg surface level. This velocity is not independent; it must
259 cgg exactly balance the volume flux, since we are dealing with
260 cgg the baroclinic velocity structure..
261 utop = tmpfldyz(j,k,bi,bj)*
262 & maskW(i+ip1,j,k,bi,bj) * delR(k) + utop
263 cgg Add the barotropic velocity component.
264 if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
265 tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
266 endif
267 enddo
268 cgg Compute the baroclinic velocity at level 1. Should balance flux.
269 tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
270 & - utop / delR(1)
271 enddo
272 enddo
273 enddo
274 endif
275 if (iobcs .eq. 4) then
276 cgg Special attention is needed for the normal velocity.
277 cgg For the north, this is the v velocity, iobcs = 4.
278 cgg This is done on a columnwise basis here.
279 do bj = jtlo,jthi
280 do bi = itlo, ithi
281 do j = jmin,jmax
282 i = OB_Ie(J,bi,bj)
283
284 cgg The barotropic velocity is stored in the level 1.
285 ubaro = tmpfldyz(j,1,bi,bj)
286 tmpfldyz(j,1,bi,bj) = 0.d0
287 utop = 0.d0
288
289 do k = 1,Nr
290 cgg If cells are not full, this should be modified with hFac.
291 cgg
292 cgg The xx field (tmpfldxz) does not contain the velocity at the
293 cgg surface level. This velocity is not independent; it must
294 cgg exactly balance the volume flux, since we are dealing with
295 cgg the baroclinic velocity structure..
296 utop = tmpfldyz(j,k,bi,bj)*
297 & maskS(i,j,k,bi,bj) * delR(k) + utop
298 cgg Add the barotropic velocity component.
299 if (maskS(i,j,k,bi,bj) .ne. 0.) then
300 tmpfldyz(j,k,bi,bj) = tmpfldyz(j,k,bi,bj)+ ubaro
301 endif
302 enddo
303 cgg Compute the baroclinic velocity at level 1. Should balance flux.
304 tmpfldyz(j,1,bi,bj) = tmpfldyz(j,1,bi,bj)
305 & - utop / delR(1)
306 enddo
307 enddo
308 enddo
309 endif
310 endif
311
312 #endif /* ALLOW_CTRL_OBCS_BALANCE */
313
314 do bj = jtlo,jthi
315 do bi = itlo,ithi
316 do k = 1,nr
317 do j = jmin,jmax
318 xx_obcse1 (j,k,bi,bj,iobcs) = tmpfldyz (j,k,bi,bj)
319 cgg & * maskyz (j,k,bi,bj)
320 enddo
321 enddo
322 enddo
323 enddo
324 endif
325
326 c-- Add control to model variable.
327 do bj = jtlo,jthi
328 do bi = itlo,ithi
329 c-- Calculate mask for tracer cells (0 => land, 1 => water).
330 do k = 1,nr
331 do j = 1,sny
332 i = OB_Ie(j,bi,bj)
333 if (iobcs .EQ. 1) then
334 OBEt(j,k,bi,bj) = OBEt (j,k,bi,bj)
335 & + obcsefac *xx_obcse0(j,k,bi,bj,iobcs)
336 & + (1. _d 0 - obcsefac)*xx_obcse1(j,k,bi,bj,iobcs)
337 OBEt(j,k,bi,bj) = OBEt(j,k,bi,bj)
338 & *maskW(i+ip1,j,k,bi,bj)
339 else if (iobcs .EQ. 2) then
340 OBEs(j,k,bi,bj) = OBEs (j,k,bi,bj)
341 & + obcsefac *xx_obcse0(j,k,bi,bj,iobcs)
342 & + (1. _d 0 - obcsefac)*xx_obcse1(j,k,bi,bj,iobcs)
343 OBEs(j,k,bi,bj) = OBEs(j,k,bi,bj)
344 & *maskW(i+ip1,j,k,bi,bj)
345 else if (iobcs .EQ. 3) then
346 OBEu(j,k,bi,bj) = OBEu (j,k,bi,bj)
347 & + obcsefac *xx_obcse0(j,k,bi,bj,iobcs)
348 & + (1. _d 0 - obcsefac)*xx_obcse1(j,k,bi,bj,iobcs)
349 OBEu(j,k,bi,bj) = OBEu(j,k,bi,bj)
350 & *maskW(i+ip1,j,k,bi,bj)
351 else if (iobcs .EQ. 4) then
352 OBEv(j,k,bi,bj) = OBEv (j,k,bi,bj)
353 & + obcsefac *xx_obcse0(j,k,bi,bj,iobcs)
354 & + (1. _d 0 - obcsefac)*xx_obcse1(j,k,bi,bj,iobcs)
355 OBEv(j,k,bi,bj) = OBEv(j,k,bi,bj)
356 & *maskS(i,j,k,bi,bj)
357 endif
358 enddo
359 enddo
360 enddo
361 enddo
362
363 C-- End over iobcs loop
364 enddo
365
366 #else /* ALLOW_OBCSE_CONTROL undefined */
367
368 c == routine arguments ==
369
370 _RL mytime
371 integer myiter
372 integer mythid
373
374 c-- CPP flag ALLOW_OBCSE_CONTROL undefined.
375
376 #endif /* ALLOW_OBCSE_CONTROL */
377
378 end
379

  ViewVC Help
Powered by ViewVC 1.1.22