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

Annotation of /MITgcm_contrib/SOSE/code_ad/cost_forcing_gen.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 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_forcing_gen.F,v 1.10 2009/04/28 18:13:28 jmc Exp $
2     C $Name: $
3    
4     #include "COST_CPPOPTIONS.h"
5    
6    
7     subroutine cost_forcing_gen(
8     I myiter,
9     I mytime,
10     I startrec,
11     I endrec,
12     I xx_gen_file,
13     I xx_gen_dummy,
14     I xx_gen_period,
15     I wmean_gen,
16     I wgen,
17     O num_gen_anom,
18     O num_gen_mean,
19     O objf_gen_anom,
20     O objf_gen_mean,
21     O objf_gen_smoo,
22     I xx_gen_remo_intercept,
23     I xx_gen_remo_slope,
24     I genmask,
25     I mythid
26     & )
27    
28     c ==================================================================
29     c SUBROUTINE cost_forcing_gen
30     c ==================================================================
31     c
32     c o Generic routine for all forcing penalty terms (flux and bulk)
33     c
34     c ==================================================================
35     c SUBROUTINE cost_forcing_gen
36     c ==================================================================
37    
38     implicit none
39    
40     c == global variables ==
41    
42     #include "EEPARAMS.h"
43     #include "SIZE.h"
44     #include "PARAMS.h"
45     #include "GRID.h"
46    
47     #include "ecco_cost.h"
48     #include "ctrl.h"
49     #include "ctrl_dummy.h"
50     #include "optim.h"
51    
52     c == routine arguments ==
53    
54     integer myiter
55     _RL mytime
56     integer startrec
57     integer endrec
58     character*(MAX_LEN_FNAM) xx_gen_file
59     _RL xx_gen_dummy
60     _RL xx_gen_period
61     _RL wmean_gen
62     _RL wgen(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
63     _RL num_gen_anom(nsx,nsy)
64     _RL num_gen_mean(nsx,nsy)
65     _RL num_gen_smoo(nsx,nsy)
66     _RL objf_gen_anom(nsx,nsy)
67     _RL objf_gen_mean(nsx,nsy)
68     _RL objf_gen_smoo(nsx,nsy)
69     _RL xx_gen_remo_intercept
70     _RL xx_gen_remo_slope
71     _RS genmask(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
72     integer mythid
73    
74     c == local variables ==
75    
76     integer bi,bj
77     integer i,j,kk
78     integer itlo,ithi
79     integer jtlo,jthi
80     integer jmin,jmax
81     integer imin,imax
82     integer nrec
83     integer irec
84     integer ilfld
85    
86     _RL fctile
87     _RL fctilem
88     _RL fctilemm
89     _RL tmpx
90     _RL sumcos
91     _RL lengthscale
92    
93     _RL xx_mean(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
94    
95     logical doglobalread
96     logical ladinit
97    
98     character*(80) fnamefld
99    
100     character*(MAX_LEN_MBUF) msgbuf
101    
102     c == external functions ==
103    
104     integer ilnblnk
105     external ilnblnk
106    
107     c == end of interface ==
108    
109     jtlo = mybylo(mythid)
110     jthi = mybyhi(mythid)
111     itlo = mybxlo(mythid)
112     ithi = mybxhi(mythid)
113     jmin = 1
114     jmax = sny
115     imin = 1
116     imax = snx
117    
118     lengthscale = 1. _d 0
119    
120     c-- Read state record from global file.
121     doglobalread = .false.
122     ladinit = .false.
123    
124     c Number of records to be used.
125     nrec = endrec-startrec+1
126    
127     if (optimcycle .ge. 0) then
128     ilfld=ilnblnk( xx_gen_file )
129     write(fnamefld(1:80),'(2a,i10.10)')
130     & xx_gen_file(1:ilfld),'.',optimcycle
131     endif
132    
133     c-- >>> Loop 1 to compute mean forcing:
134     do bj = jtlo,jthi
135     do bi = itlo,ithi
136     do j = jmin,jmax
137     do i = imin,imax
138     xx_mean(i,j,bi,bj) = 0. _d 0
139     enddo
140     enddo
141     num_gen_anom(bi,bj) = 0. _d 0
142     num_gen_mean(bi,bj) = 0. _d 0
143     num_gen_smoo(bi,bj) = 0. _d 0
144     objf_gen_anom(bi,bj) = 0. _d 0
145     objf_gen_mean(bi,bj) = 0. _d 0
146     objf_gen_smoo(bi,bj) = 0. _d 0
147     enddo
148     enddo
149    
150     CMM HERE EDITED TO SEPERATE MEAN AND ANOMALY COST
151     CMM EVEN IF DOING SMOOTHING...
152     #ifndef ALLOW_SMOOTH_CORREL2D_CMM
153     do irec = 1,nrec
154    
155     call active_read_xy(
156     & fnamefld, tmpfld2d, irec, doglobalread,
157     & ladinit, optimcycle, mythid, xx_gen_dummy )
158    
159     c-- Loop over this thread tiles.
160     do bj = jtlo,jthi
161     do bi = itlo,ithi
162     do j = jmin,jmax
163     do i = imin,imax
164     xx_mean(i,j,bi,bj) = xx_mean(i,j,bi,bj)
165     & + tmpfld2d(i,j,bi,bj)
166     & - ( xx_gen_remo_intercept +
167     & xx_gen_remo_slope*(irec-1)*xx_gen_period )
168     enddo
169     enddo
170     enddo
171     enddo
172    
173     enddo
174    
175     if ( wmean_gen .NE. 0. ) then
176     do bj = jtlo,jthi
177     do bi = itlo,ithi
178     c-- Determine the weights to be used.
179     kk = 1
180     fctilem = 0. _d 0
181     do j = jmin,jmax
182     do i = imin,imax
183     xx_mean(i,j,bi,bj)
184     & = xx_mean(i,j,bi,bj)/float(nrec)
185     tmpx = xx_mean(i,j,bi,bj)/wmean_gen
186     if (genmask(i,j,kk,bi,bj) .ne. 0.) then
187     CMM if ( ABS(R_low(i,j,bi,bj)) .LT. 100. )
188     CMM & tmpx = tmpx*ABS(R_low(i,j,bi,bj))/100.
189     fctilem = fctilem + cosphi(i,j,bi,bj)*tmpx*tmpx
190     if ( cosphi(i,j,bi,bj) .ne. 0. )
191     & num_gen_mean(bi,bj) = num_gen_mean(bi,bj) + 1. _d 0
192     endif
193     enddo
194     enddo
195     objf_gen_mean(bi,bj) = objf_gen_mean(bi,bj) + fctilem
196     enddo
197     enddo
198     endif
199     #endif
200    
201     c-- >>> Loop 2 over records.
202     do irec = 1,nrec
203    
204     call active_read_xy(
205     & fnamefld, tmpfld2d, irec, doglobalread,
206     & ladinit, optimcycle, mythid, xx_gen_dummy )
207    
208     c-- Loop over this thread tiles.
209     do bj = jtlo,jthi
210     do bi = itlo,ithi
211    
212     c-- Determine the weights to be used.
213     kk = 1
214     fctile = 0. _d 0
215     do j = jmin,jmax
216     do i = imin,imax
217     if (genmask(i,j,kk,bi,bj) .ne. 0.) then
218     #ifndef ALLOW_SMOOTH_CORREL2D_CMM
219     tmpx = tmpfld2d(i,j,bi,bj)-xx_mean(i,j,bi,bj)
220     & - ( xx_gen_remo_intercept +
221     & xx_gen_remo_slope*(irec-1)*xx_gen_period )
222     CMM if ( ABS(R_low(i,j,bi,bj)) .LT. 100. )
223     CMM & tmpx = tmpx*ABS(R_low(i,j,bi,bj))/100.
224     fctile = fctile
225     & + wgen(i,j,bi,bj)*cosphi(i,j,bi,bj)
226     & *tmpx*tmpx
227     #else
228     tmpx = tmpfld2d(i,j,bi,bj)
229     fctile = fctile + tmpx*tmpx
230     #endif
231     if ( wgen(i,j,bi,bj)*cosphi(i,j,bi,bj) .ne. 0. )
232     & num_gen_anom(bi,bj) = num_gen_anom(bi,bj)
233     & + 1. _d 0
234     endif
235     enddo
236     enddo
237    
238     objf_gen_anom(bi,bj) = objf_gen_anom(bi,bj) + fctile
239    
240     enddo
241     enddo
242    
243     c-- End of loop over records.
244     enddo
245    
246     #ifndef ALLOW_SMOOTH_CORREL2D
247     #ifdef ALLOW_SMOOTH_BC_COST_CONTRIBUTION
248    
249     c-- >>> Loop 2 over records.
250     do irec = 1,nrec
251    
252     call active_read_xy(
253     & fnamefld, tmpfld2d, irec, doglobalread,
254     & ladinit, optimcycle, mythid, xx_gen_dummy )
255    
256     _EXCH_XY_RL(tmpfld2d, mythid)
257    
258     c-- Loop over this thread tiles.
259     do bj = jtlo,jthi
260     do bi = itlo,ithi
261    
262     c-- Determine the weights to be used.
263     kk = 1
264     fctile = 0. _d 0
265     do j = jmin,jmax
266     do i = imin,imax
267     if (genmask(i,j,kk,bi,bj) .ne. 0.) then
268     tmpx =
269     & ( tmpfld2d(i+2,j,bi,bj)-tmpfld2d(i+1,j,bi,bj) )
270     & *maskW(i+1,j,kk,bi,bj)*maskW(i+2,j,kk,bi,bj)
271     & + ( tmpfld2d(i+1,j,bi,bj)-tmpfld2d(i,j,bi,bj) )
272     & *maskW(i+1,j,kk,bi,bj)
273     & + ( tmpfld2d(i,j+2,bi,bj)-tmpfld2d(i,j+1,bi,bj) )
274     & *maskS(i,j+1,kk,bi,bj)*maskS(i,j+2,kk,bi,bj)
275     & + ( tmpfld2d(i,j+1,bi,bj)-tmpfld2d(i,j,bi,bj) )
276     & *maskS(i,j+1,kk,bi,bj)
277     if ( ABS(R_low(i,j,bi,bj)) .LT. 100. )
278     & tmpx = tmpx*ABS(R_low(i,j,bi,bj))/100.
279     fctile = fctile
280     & + wgen(i,j,bi,bj)*cosphi(i,j,bi,bj)
281     * *0.0161*lengthscale/4.0
282     & *tmpx*tmpx
283     if ( wgen(i,j,bi,bj)*cosphi(i,j,bi,bj) .ne. 0. )
284     & num_gen_smoo(bi,bj) = num_gen_smoo(bi,bj)
285     & + 1. _d 0
286     endif
287     enddo
288     enddo
289    
290     objf_gen_smoo(bi,bj) = objf_gen_smoo(bi,bj) + fctile
291    
292     enddo
293     enddo
294    
295     c-- End of loop over records.
296     enddo
297    
298     #endif
299     #endif
300    
301     return
302     end
303    

  ViewVC Help
Powered by ViewVC 1.1.22