/[MITgcm]/MITgcm_contrib/SOSE/BoxAdj/code_ad/ctrl_getobcse.F
ViewVC logotype

Annotation of /MITgcm_contrib/SOSE/BoxAdj/code_ad/ctrl_getobcse.F

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


Revision 1.3 - (hide annotations) (download)
Wed Jan 19 12:45:02 2011 UTC (14 years, 11 months ago) by mmazloff
Branch: MAIN
Changes since 1.2: +1 -1 lines
CPP option

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

  ViewVC Help
Powered by ViewVC 1.1.22