/[MITgcm]/MITgcm_contrib/SOSE/code_ad/cost_obcsn.F
ViewVC logotype

Annotation of /MITgcm_contrib/SOSE/code_ad/cost_obcsn.F

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


Revision 1.1 - (hide annotations) (download)
Fri Apr 23 19:55:11 2010 UTC (15 years, 3 months ago) by mmazloff
Branch: MAIN
CVS Tags: HEAD
original files

1 mmazloff 1.1
2     #include "COST_CPPOPTIONS.h"
3     #ifdef ALLOW_OBCS
4     # include "OBCS_OPTIONS.h"
5     #endif
6    
7     subroutine cost_obcsn(
8     I myiter,
9     I mytime,
10     I startrec,
11     I endrec,
12     I mythid
13     & )
14    
15     c ==================================================================
16     c SUBROUTINE cost_obcsn
17     c ==================================================================
18     c
19     c o cost function contribution obc
20     c
21     c o G. Gebbie, gebbie@mit.edu, 18-Mar-2003
22     c ==================================================================
23     c SUBROUTINE cost_obcsn
24     c ==================================================================
25    
26     implicit none
27    
28     c == global variables ==
29    
30     #include "EEPARAMS.h"
31     #include "SIZE.h"
32     #include "PARAMS.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35     #ifdef ALLOW_OBCS
36     # include "OBCS.h"
37     #endif
38    
39     #include "cal.h"
40     #include "ecco_cost.h"
41     #include "ctrl.h"
42     #include "ctrl_dummy.h"
43     #include "optim.h"
44    
45     c == routine arguments ==
46    
47     integer myiter
48     _RL mytime
49     integer mythid
50     cgg(
51     integer startrec
52     integer endrec
53     cgg)
54    
55     c == local variables ==
56    
57     integer bi,bj
58     integer i,j,k
59     integer itlo,ithi
60     integer jtlo,jthi
61     integer jmin,jmax
62     integer imin,imax
63     integer irec
64     integer il
65     integer iobcs
66     integer jp1
67     integer nrec
68     integer ilfld
69     integer igg
70     integer ihh
71    
72     _RL fctile
73     _RL fcthread
74     _RL dummy
75     _RL gg
76     _RL tmpx
77     _RL tmpfield (1-olx:snx+olx,nr,nsx,nsy)
78     _RL maskxz (1-olx:snx+olx,nr,nsx,nsy)
79     _RL area
80     _RL volflux
81    
82     character*(80) fnamefld
83    
84     logical doglobalread
85     logical ladinit
86    
87     #ifdef ECCO_VERBOSE
88     character*(MAX_LEN_MBUF) msgbuf
89     #endif
90    
91     c == external functions ==
92    
93     integer ilnblnk
94     external ilnblnk
95    
96     c == end of interface ==
97    
98     jtlo = mybylo(mythid)
99     jthi = mybyhi(mythid)
100     itlo = mybxlo(mythid)
101     ithi = mybxhi(mythid)
102     jmin = 1
103     jmax = sny
104     imin = 1
105     imax = snx
106    
107     c-- Read tiled data.
108     doglobalread = .false.
109     ladinit = .false.
110    
111     c Number of records to be used.
112     nrec = endrec-startrec+1
113    
114     #ifdef ALLOW_OBCSN_COST_CONTRIBUTION
115    
116     jp1 = 0
117     fcthread = 0. _d 0
118    
119     #ifdef ECCO_VERBOSE
120     _BEGIN_MASTER( mythid )
121     write(msgbuf,'(a)') ' '
122     call print_message( msgbuf, standardmessageunit,
123     & SQUEEZE_RIGHT , mythid)
124     write(msgbuf,'(a)') ' '
125     call print_message( msgbuf, standardmessageunit,
126     & SQUEEZE_RIGHT , mythid)
127     write(msgbuf,'(a,i9.8)')
128     & ' cost_obcsn: number of records to process: ',nrec
129     call print_message( msgbuf, standardmessageunit,
130     & SQUEEZE_RIGHT , mythid)
131     write(msgbuf,'(a)') ' '
132     call print_message( msgbuf, standardmessageunit,
133     & SQUEEZE_RIGHT , mythid)
134     _END_MASTER( mythid )
135     #endif
136    
137     if (optimcycle .ge. 0) then
138     ilfld=ilnblnk( xx_obcsn_file )
139     write(fnamefld(1:80),'(2a,i10.10)')
140     & xx_obcsn_file(1:ilfld), '.', optimcycle
141     endif
142    
143     c-- Loop over records.
144     do irec = 1,nrec
145    
146     area = 0. _d 0
147     volflux = 0. _d 0
148    
149     call active_read_xz( fnamefld, tmpfield, irec, doglobalread,
150     & ladinit, optimcycle, mythid
151     & , xx_obcsn_dummy )
152    
153     cgg Need to solve for iobcs would have been.
154     gg = (irec-1)/nobcs
155     igg = int(gg)
156     iobcs = irec - igg*nobcs
157    
158     call active_read_xz( 'maskobcsn', maskxz,
159     & iobcs,
160     & doglobalread, ladinit, 0,
161     & mythid, dummy )
162    
163     #ifdef BALANCE_CONTROL_VOLFLUX_GLOBAL
164     cih -- Balance net transport from the northern boundary.
165     c Compute total net transport.
166     if (iobcs .eq. 3) then
167     ihh = igg+1
168     call ctrl_volflux( ihh, area, volflux, mythid)
169     _GLOBAL_SUM_RL( volflux, mythid )
170     _GLOBAL_SUM_RL( area,mythid )
171     c print*,'volflux,area',volflux,area
172     endif
173     c Correct barofield if normal velocity at the northern boundary.
174     do bj = jtlo,jthi
175     do bi = itlo,ithi
176     do i = imin,imax
177     if (iobcs .eq. 3) then
178     tmpfield(i,1,bi,bj) = (tmpfield(i,1,bi,bj) +
179     & volflux/area)*maskxz(i,1,bi,bj)
180     c print*,'volflux2,area2',volflux,area
181     c print*,'barofield',tmpfield(i,1,bi,bj)
182     endif
183     enddo
184     enddo
185     enddo
186     #endif
187    
188     c-- Loop over this thread's tiles.
189     do bj = jtlo,jthi
190     do bi = itlo,ithi
191    
192     c-- Determine the weights to be used.
193     fctile = 0. _d 0
194    
195     do k = 1, Nr
196     do i = imin,imax
197     j = OB_Jn(I,bi,bj)
198     cgg if (maskS(i,j+jp1,k,bi,bj) .ne. 0.) then
199     tmpx = tmpfield(i,k,bi,bj)
200     CMM fctile = fctile + wobcsn2(i,k,bi,bj,iobcs)
201     fctile = fctile + wobcsn(k,iobcs)
202     & *tmpx*tmpx*maskxz(i,k,bi,bj)
203     cgg endif
204     CMM if (wobcsn2(i,k,bi,bj,iobcs)*maskxz(i,k,bi,bj).ne.0.)
205     if (wobcsn(k,iobcs)*maskxz(i,k,bi,bj).ne.0.)
206     & num_obcsn(bi,bj) = num_obcsn(bi,bj) + 1. _d 0
207     cgg print*,'S fctile',fctile
208     enddo
209     enddo
210    
211     objf_obcsn(bi,bj) = objf_obcsn(bi,bj) + fctile
212     fcthread = fcthread + fctile
213     enddo
214     enddo
215    
216     #ifdef ECCO_VERBOSE
217     c-- Print cost function for all tiles.
218     _GLOBAL_SUM_RL( fcthread , myThid )
219     write(msgbuf,'(a)') ' '
220     call print_message( msgbuf, standardmessageunit,
221     & SQUEEZE_RIGHT , mythid)
222     write(msgbuf,'(a,i8.8)')
223     & ' cost_obcsn: irec = ',irec
224     call print_message( msgbuf, standardmessageunit,
225     & SQUEEZE_RIGHT , mythid)
226     write(msgbuf,'(a,a,d22.15)')
227     & ' global cost function value',
228     & ' (obcsn) = ',fcthread
229     call print_message( msgbuf, standardmessageunit,
230     & SQUEEZE_RIGHT , mythid)
231     write(msgbuf,'(a)') ' '
232     call print_message( msgbuf, standardmessageunit,
233     & SQUEEZE_RIGHT , mythid)
234     #endif
235    
236     enddo
237     c-- End of loop over records.
238    
239     #endif
240    
241     return
242     end
243    
244    
245    
246    
247    
248    
249    

  ViewVC Help
Powered by ViewVC 1.1.22