/[MITgcm]/MITgcm/pkg/ecco/cost_obcsvol.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/cost_obcsvol.F

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


Revision 1.2 - (hide annotations) (download)
Tue Oct 9 00:02:50 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.1: +12 -10 lines
add missing cvs $Header:$ or $Name:$

1 jmc 1.2 C $Header: $
2     C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5     #ifdef ALLOW_OBCS
6     # include "OBCS_OPTIONS.h"
7     #endif
8    
9     subroutine cost_obcsvol(
10     I myiter,
11     I mytime,
12     I startrec,
13     I endrec,
14     I mythid
15     & )
16    
17     c ==================================================================
18     c SUBROUTINE cost_obcsvol
19     c ==================================================================
20     c
21     c o cost function contribution obc -- Volume flux imbalance.
22     c
23     c ==================================================================
24     c SUBROUTINE cost_obcsvol
25     c ==================================================================
26    
27     implicit none
28    
29     c == global variables ==
30    
31     #include "EEPARAMS.h"
32     #include "SIZE.h"
33     #include "PARAMS.h"
34     #include "GRID.h"
35     #include "DYNVARS.h"
36     #ifdef ALLOW_OBCS
37     # include "OBCS.h"
38     #endif
39    
40     #include "cal.h"
41     #include "ecco_cost.h"
42     #include "ctrl.h"
43     #include "ctrl_dummy.h"
44     #include "optim.h"
45    
46     c == routine arguments ==
47    
48     integer myiter
49     _RL mytime
50     integer mythid
51     integer startrec
52     integer endrec
53    
54     c == local variables ==
55    
56     integer bi,bj
57     integer i,j,k
58     integer itlo,ithi
59     integer jtlo,jthi
60     integer jmin,jmax
61     integer imin,imax
62     integer irec
63     integer il
64     integer iobcs
65     integer ip1
66     integer jp1
67     integer nrec
68     integer ilfld
69     integer igg
70    
71     _RL fctile
72     _RL sumvol
73     _RL dummy
74     _RL gg
75     _RL tmpx
76     _RL tmpy
77     _RL wobcsvol
78     character*(80) fnamefldn
79     character*(80) fnameflds
80     character*(80) fnamefldw
81     character*(80) fnameflde
82    
83     logical doglobalread
84     logical ladinit
85    
86     #ifdef ECCO_VERBOSE
87     character*(MAX_LEN_MBUF) msgbuf
88     #endif
89    
90     c == external functions ==
91    
92     integer ilnblnk
93     external ilnblnk
94    
95     c == end of interface ==
96    
97     jtlo = mybylo(mythid)
98     jthi = mybyhi(mythid)
99     itlo = mybxlo(mythid)
100     ithi = mybxhi(mythid)
101     jmin = 1
102     jmax = sny
103     imin = 1
104     imax = snx
105    
106     c-- Read tiled data.
107     doglobalread = .false.
108     ladinit = .false.
109    
110     cgg Assume the number of records is the same for
111     cgg all boundaries.
112     c Number of records to be used.
113     nrec = endrec-startrec+1
114    
115     #ifdef OBCS_VOLFLUX_COST_CONTRIBUTION
116     #ifdef BAROTROPIC_OBVEL_CONTROL
117    
118     sumvol = 0. _d 0
119     wobcsvol = .01
120     cgg Acceptable volume flux is 10^-3. Corresponds to 5 mm change over a year.
121 jmc 1.2 cgg Added a factor of 1000 because its very important to me.
122 heimbach 1.1 wobcsvol = 1./(wobcsvol * wobcsvol)
123    
124     #ifdef ECCO_VERBOSE
125     _BEGIN_MASTER( mythid )
126     write(msgbuf,'(a)') ' '
127     call print_message( msgbuf, standardmessageunit,
128     & SQUEEZE_RIGHT , mythid)
129     write(msgbuf,'(a)') ' '
130     call print_message( msgbuf, standardmessageunit,
131     & SQUEEZE_RIGHT , mythid)
132     write(msgbuf,'(a,i9.8)')
133     & ' cost_obcsvol: number of records to process: ',nrec
134     call print_message( msgbuf, standardmessageunit,
135     & SQUEEZE_RIGHT , mythid)
136     write(msgbuf,'(a)') ' '
137     call print_message( msgbuf, standardmessageunit,
138     & SQUEEZE_RIGHT , mythid)
139     _END_MASTER( mythid )
140     #endif
141    
142     if (optimcycle .ge. 0) then
143     #ifdef ALLOW_OBCSN_CONTROL
144     ilfld=ilnblnk( xx_obcsn_file )
145 jmc 1.2 write(fnamefldn(1:80),'(2a,i10.10)')
146 heimbach 1.1 & xx_obcsn_file(1:ilfld),'.', optimcycle
147     #endif
148     #ifdef ALLOW_OBCSS_CONTROL
149     ilfld=ilnblnk( xx_obcss_file )
150 jmc 1.2 write(fnameflds(1:80),'(2a,i10.10)')
151 heimbach 1.1 & xx_obcss_file(1:ilfld),'.',optimcycle
152     #endif
153     #ifdef ALLOW_OBCSW_CONTROL
154     ilfld=ilnblnk( xx_obcsw_file )
155 jmc 1.2 write(fnamefldw(1:80),'(2a,i10.10)')
156 heimbach 1.1 & xx_obcsw_file(1:ilfld),'.',optimcycle
157     #endif
158     #ifdef ALLOW_OBCSE_CONTROL
159     ilfld=ilnblnk( xx_obcse_file )
160 jmc 1.2 write(fnameflde(1:80),'(2a,i10.10)')
161 heimbach 1.1 & xx_obcse_file(1:ilfld),'.',optimcycle
162     #endif
163     else
164     print*
165     print*,' ctrl_obcsvol: optimcycle has a wrong value.'
166     print*,' optimcycle = ',optimcycle
167     print*
168     stop ' ... stopped in ctrl_obcsvol.'
169     endif
170    
171     do irec = 1,nrec
172     c-- Loop over records. For north boundary, we only need V velocity.
173    
174     cgg Need to solve for iobcs. Then only keep iobcs=3.or.4.
175     gg = (irec-1)/nobcs
176     igg = int(gg)
177     iobcs = irec - igg*nobcs
178    
179     #ifdef ALLOW_OBCSN_CONTROL
180     cgg Assume that nobcs=4, and V velocity is the 4th record. I can't
181     cgg think of a more general way to do this.
182     jp1 = 0
183    
184     if (iobcs.eq.4) then
185     call active_read_xz( fnamefldn, tmpfldxz, irec, doglobalread,
186     & ladinit, optimcycle, mythid
187     & , xx_obcsn_dummy )
188    
189     cgg At this point, do not be concerned with the overlap halos.
190 jmc 1.2 cgg From experience, there is no control contribution in the
191 heimbach 1.1 cgg velocity points outside the boundaries. This has something
192     cgg to do with the computational stencil, and the fact that we
193     cgg are diagonally offset. Could check later by employing both
194     cgg BALANCE_CONTROL_VOLFLUX and VOLFLUX_COST_CONTRIBUTION.
195     cgg
196     cgg 25-jan-03 --- no idea what i was talking about ^^^^
197     c-- Loop over this thread's tiles.
198     do bj = jtlo,jthi
199     do bi = itlo,ithi
200    
201     c-- Determine the weights to be used.
202     fctile = 0. _d 0
203    
204     do k = 1, Nr
205     do i = imin,imax
206     j = OB_Jn(I,bi,bj)
207     cgg Barotropic velocity is stored in level 1.
208     tmpx = tmpfldxz(i,1,bi,bj)
209     if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
210     cgg -- Positive is flux in.
211     fctile = fctile - tmpx* delZ(k) *dxg(i,j+jp1,bi,bj)
212     endif
213     enddo
214     enddo
215    
216     sumvol = sumvol + fctile
217     enddo
218     enddo
219     endif
220     #endif
221    
222     #ifdef ALLOW_OBCSS_CONTROL
223     cgg Assume that nobcs=4, and V velocity is the 4th record. I can't
224     cgg think of a more general way to do this.
225     jp1 = 1
226    
227     if (iobcs.eq.4) then
228     call active_read_xz( fnameflds, tmpfldxz, irec, doglobalread,
229     & ladinit, optimcycle, mythid
230     & , xx_obcss_dummy )
231    
232     cgg At this point, do not be concerned with the overlap halos.
233 jmc 1.2 cgg From experience, there is no control contribution in the
234 heimbach 1.1 cgg velocity points outside the boundaries. This has something
235     cgg to do with the computational stencil, and the fact that we
236     cgg are diagonally offset. Could check later by employing both
237     cgg BALANCE_CONTROL_VOLFLUX and VOLFLUX_COST_CONTRIBUTION.
238    
239     c-- Loop over this thread's tiles.
240     do bj = jtlo,jthi
241     do bi = itlo,ithi
242    
243     c-- Determine the weights to be used.
244     fctile = 0. _d 0
245    
246     do k = 1, Nr
247     do i = imin,imax
248     j = OB_Js(I,bi,bj)
249     cgg Barotropic velocity is stored in level 1.
250     tmpx = tmpfldxz(i,1,bi,bj)
251     if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
252     cgg -- Positive is flux in.
253     fctile = fctile + tmpx* delZ(k) *dxg(i,j+jp1,bi,bj)
254     endif
255     enddo
256     enddo
257    
258     sumvol = sumvol + fctile
259     enddo
260     enddo
261     endif
262    
263     #endif
264    
265     #ifdef ALLOW_OBCSW_CONTROL
266     cgg Assume that nobcs=4, and V velocity is the 4th record. I can't
267     cgg think of a more general way to do this.
268     ip1 = 1
269    
270     if (iobcs.eq.3) then
271     call active_read_yz( fnamefldw, tmpfldyz, irec, doglobalread,
272     & ladinit, optimcycle, mythid
273     & , xx_obcsw_dummy )
274    
275     cgg At this point, do not be concerned with the overlap halos.
276 jmc 1.2 cgg From experience, there is no control contribution in the
277 heimbach 1.1 cgg velocity points outside the boundaries. This has something
278     cgg to do with the computational stencil, and the fact that we
279     cgg are diagonally offset. Could check later by employing both
280     cgg BALANCE_CONTROL_VOLFLUX and VOLFLUX_COST_CONTRIBUTION.
281    
282     c-- Loop over this thread's tiles.
283     do bj = jtlo,jthi
284     do bi = itlo,ithi
285    
286     c-- Determine the weights to be used.
287     fctile = 0. _d 0
288    
289     do k = 1, Nr
290     do j = jmin,jmax
291     i = OB_Iw(j,bi,bj)
292     cgg Barotropic velocity is stored in the level 1.
293     tmpy = tmpfldyz(j,1,bi,bj)
294     if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
295     cgg -- Positive is flux in.
296     fctile = fctile + tmpy* delZ(k) *dyg(i+ip1,j,bi,bj)
297     endif
298     enddo
299     enddo
300    
301     sumvol = sumvol + fctile
302     enddo
303     enddo
304     endif
305    
306     #endif
307    
308     #ifdef ALLOW_OBCSE_CONTROL
309     cgg Assume that nobcs=4, and V velocity is the 4th record. I can't
310     cgg think of a more general way to do this.
311     ip1 = 0
312    
313     if (iobcs.eq.3) then
314     call active_read_yz( fnameflde, tmpfldyz, irec, doglobalread,
315     & ladinit, optimcycle, mythid
316     & , xx_obcse_dummy )
317    
318     cgg At this point, do not be concerned with the overlap halos.
319 jmc 1.2 cgg From experience, there is no control contribution in the
320 heimbach 1.1 cgg velocity points outside the boundaries. This has something
321     cgg to do with the computational stencil, and the fact that we
322     cgg are diagonally offset. Could check later by employing both
323     cgg BALANCE_CONTROL_VOLFLUX and VOLFLUX_COST_CONTRIBUTION.
324    
325     c-- Loop over this thread's tiles.
326     do bj = jtlo,jthi
327     do bi = itlo,ithi
328    
329     c-- Determine the weights to be used.
330     fctile = 0. _d 0
331    
332     do k = 1, Nr
333     do j = jmin,jmax
334     i = OB_Ie(j,bi,bj)
335     cgg Barotropic velocity stored in level 1.
336     tmpy = tmpfldyz(j,1,bi,bj)
337     if (maskW(i+ip1,j,k,bi,bj) .ne. 0.) then
338     cgg -- Positive is flux in.
339     fctile = fctile - tmpy* delZ(k) *dyg(i+ip1,j,bi,bj)
340     endif
341     enddo
342     enddo
343    
344     sumvol = sumvol + fctile
345     enddo
346     enddo
347     endif
348    
349     #endif
350    
351     enddo
352     c-- End of loop over records.
353    
354     c-- Do the global summation.
355     _GLOBAL_SUM_R8( sumvol, mythid )
356 jmc 1.2 objf_obcsvol = wobcsvol * sumvol* sumvol
357 heimbach 1.1
358     #endif
359     #endif
360    
361     return
362     end
363    
364    
365    
366    
367    
368    
369    
370    
371    

  ViewVC Help
Powered by ViewVC 1.1.22