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

Contents of /MITgcm/pkg/ecco/cost_generic.F

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


Revision 1.20 - (show annotations) (download)
Wed Oct 1 12:54:03 2014 UTC (9 years, 7 months ago) by gforget
Branch: MAIN
Changes since 1.19: +8 -11 lines
- ecco.h : remove un-needed CCP options, add gencost_preproc, add 3D gencost
- cost_generic.F : move active_read calls to cost_genread (new) and setup
  generic pre-processing framework (via new preproc argument).
- cost_genread.F (new) : interface between cost_generic and active_read

- added 3D gencost involves : cost_averagesfields.F,
  cost_averagesinit.F, cost_gencost_all.F, ecco.h,
  ecco_check.F, ecco_cost_init_fixed.F, ecco_readparms.F
  (ALLOW_GENCOST3D, gencost_is3d, gencost_pointer3d,
   gencost_bar3d, gencost_mod3d, gencost_wei3d)
- added gencost_preproc involves : cost_gencost_all.F,
  cost_genread.F, cost_generic.F, cost_hyd.F, ecco_readparms.
  and ... pkg/seaice/seaice_cost_driver.F

- ecco_cost_driver.F : move cost_profiles here
- cost_hyd.F : remove cost_profiles from here
- ecco_cost_weights.F : remove gencost weights from here
- ecco_cost_init_fixed.F : more gencost weights here
- ecco_cost_final.F : 0. _ d 0 fixes

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_generic.F,v 1.19 2014/09/29 16:47:50 gforget Exp $
2 C $Name: $
3
4 #include "ECCO_OPTIONS.h"
5
6
7 subroutine cost_generic(
8 & nnzbar, localbarfile, localbar, xx_localbar_mean_dummy,
9 & nnzobs, localobsfile, mult_local,
10 & nrecloc, localstartdate, localperiod,
11 & ylocmask, localweight,
12 & spminloc, spmaxloc, spzeroloc, preproc,
13 & objf_local, num_local,
14 & myiter, mytime, mythid )
15
16 c ==================================================================
17 c SUBROUTINE cost_generic
18 c ==================================================================
19 c
20 c o Generic routine for evaluating time-dependent
21 c cost function contribution
22 c
23 c ==================================================================
24 c SUBROUTINE cost_generic
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 #ifdef ALLOW_CAL
36 # include "cal.h"
37 #endif
38 #ifdef ALLOW_ECCO
39 # include "ecco.h"
40 #endif
41 #ifdef ALLOW_SEAICE
42 # include "SEAICE_COST.h"
43 #endif
44
45 c == routine arguments ==
46
47 integer nnzbar
48 integer nnzobs
49 integer nrecloc
50 integer myiter
51 integer mythid
52 integer localstartdate(4)
53
54 _RL localbar (1-olx:snx+olx,1-oly:sny+oly,nnzbar,nsx,nsy)
55 _RL localweight(1-olx:snx+olx,1-oly:sny+oly,nnzobs,nsx,nsy)
56 _RL xx_localbar_mean_dummy
57 _RL mult_local
58 _RL mytime
59 _RL localperiod
60 _RL spminloc
61 _RL spmaxloc
62 _RL spzeroloc
63 _RL objf_local(nsx,nsy)
64 _RL num_local(nsx,nsy)
65
66 character*(1) ylocmask
67 character*(MAX_LEN_FNAM) localbarfile
68 character*(MAX_LEN_FNAM) localobsfile
69 character*(8) preproc
70
71 c == local variables ==
72
73 integer bi,bj
74 integer i,j,k
75 integer itlo,ithi
76 integer jtlo,jthi
77 integer jmin,jmax
78 integer imin,imax
79 integer irec
80 integer il
81 integer localrec
82 integer obsrec
83
84 logical doglobalread
85 logical ladinit
86
87 _RL spval
88 parameter (spval = -9999. )
89 _RL localwww
90 _RL localcost
91 _RL junk
92
93 _RL localmask (1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
94 _RL localobs (1-olx:snx+olx,1-oly:sny+oly,nnzobs,nsx,nsy)
95 _RL cmask (1-olx:snx+olx,1-oly:sny+oly,nnzobs)
96
97 character*(128) fname1, fname2
98
99 cnew(
100 _RL daytime
101 _RL diffsecs
102 integer dayiter
103 integer daydate(4)
104 integer difftime(4)
105 integer tempDate_1
106 integer middate(4)
107 integer yday, ymod
108 integer md, dd, sd, ld, wd
109 integer mody, modm
110 integer beginmodel, beginlocal
111 logical exst
112 cnew)
113
114 c == external functions ==
115
116 integer ilnblnk
117 external ilnblnk
118
119 c == end of interface ==
120
121 jtlo = mybylo(mythid)
122 jthi = mybyhi(mythid)
123 itlo = mybxlo(mythid)
124 ithi = mybxhi(mythid)
125 jmin = 1
126 jmax = sny
127 imin = 1
128 imax = snx
129
130 c-- Initialise local variables.
131
132 localwww = 0. _d 0
133
134 do bj = jtlo,jthi
135 do bi = itlo,ithi
136 objf_local(bi,bj) = 0. _d 0
137 num_local(bi,bj) = 0. _d 0
138 do k = 1,nnzobs
139 do j = jmin,jmax
140 do i = imin,imax
141 localobs(i,j,k,bi,bj) = 0. _d 0
142 enddo
143 enddo
144 enddo
145 enddo
146 enddo
147
148 c-- Assign mask
149 do bj = jtlo,jthi
150 do bi = itlo,ithi
151 do k = 1,Nr
152 do j = 1-oly,sny+oly
153 do i = 1-olx,snx+olx
154 if ( ylocmask .EQ. 'C' .OR. ylocmask .EQ. 'c' ) then
155 localmask(i,j,k,bi,bj) = maskC(i,j,k,bi,bj)
156 elseif ( ylocmask .EQ. 'S' .OR. ylocmask .EQ. 's' ) then
157 localmask(i,j,k,bi,bj) = maskS(i,j,k,bi,bj)
158 elseif ( ylocmask .EQ. 'W' .OR. ylocmask .EQ. 'w' ) then
159 localmask(i,j,k,bi,bj) = maskW(i,j,k,bi,bj)
160 else
161 STOP 'cost_generic: wrong ylocmask'
162 endif
163 enddo
164 enddo
165 enddo
166 enddo
167 enddo
168
169 c-- First, read tiled data.
170 doglobalread = .false.
171 ladinit = .false.
172
173 write(fname1(1:128),'(80a)') ' '
174 il=ilnblnk( localbarfile )
175 write(fname1(1:128),'(2a,i10.10)')
176 & localbarfile(1:il),'.',eccoiter
177
178 cgf here nrecloc will be updated based upon preproc
179
180 if ( .NOT. ( localobsfile.EQ.' ' ) ) then
181
182 c-- Loop over records for the second time.
183 do irec = 1, nrecloc
184
185 call cost_genread( fname1, localbar, irec, doglobalread,
186 & ladinit, eccoiter, nnzbar, preproc,
187 & mythid, xx_localbar_mean_dummy )
188
189 cnew(
190 if ( localperiod .EQ. 86400. ) then
191 c-- assume daily fields
192 obsrec = irec
193 daytime = FLOAT(secondsperday*(irec-1)) + modelstart
194 dayiter = hoursperday*(irec-1) + modeliter0
195 call cal_getdate( dayiter, daytime, daydate, mythid )
196 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
197 ymod = localstartdate(1)/10000
198 do k=1,4
199 middate(k)=0
200 enddo
201 tempDate_1 = yday*10000+100+1
202 if ( ymod .GE. yday ) then
203 call cal_FullDate( localstartdate(1), 0, middate, mythid)
204 else
205 call cal_FullDate( tempDate_1, 0, middate, mythid)
206 endif
207 call cal_TimePassed( middate, daydate, difftime, mythid )
208 call cal_ToSeconds( difftime, diffsecs, mythid )
209 c localrec = floor(diffsecs/localperiod) + 1
210 localrec = int(diffsecs/localperiod) + 1
211 else
212 c-- assume monthly fields
213 beginlocal = localstartdate(1)/10000
214 beginmodel = modelstartdate(1)/10000
215 obsrec =
216 & ( beginmodel - beginlocal )*nmonthyear
217 & + ( mod(modelstartdate(1)/100,100)
218 & -mod(localstartdate(1)/100,100) )
219 & + irec
220 mody = modelstartdate(1)/10000
221 modm = modelstartdate(1)/100 - mody*100
222 yday = mody + INT((modm-1+irec-1)/12)
223 localrec = 1 + MOD(modm-1+irec-1,12)
224 endif
225
226 il=ilnblnk(localobsfile)
227 write(fname2(1:128),'(2a,i4)')
228 & localobsfile(1:il), '_', yday
229 inquire( file=fname2, exist=exst )
230 if ( (.NOT. exst).AND.( localperiod .NE. 86400. ) ) then
231 write(fname2(1:128),'(a)') localobsfile(1:il)
232 inquire( file=fname2, exist=exst )
233 #ifndef COST_GENERIC_ASSUME_CYCLIC
234 c assume we have one big file, one year after the other
235 localrec = obsrec
236 c otherwise assume climatology, used for each year
237 #endif
238 endif
239
240 if ( (localrec .GT. 0).AND.(obsrec .GT. 0).AND.(exst) ) then
241 call mdsreadfield( fname2, cost_iprec, cost_yftype, nnzobs,
242 & localobs, localrec, mythid )
243 else
244 do bj = jtlo,jthi
245 do bi = itlo,ithi
246 do k = 1,nnzobs
247 do j = jmin,jmax
248 do i = imin,imax
249 localobs(i,j,k,bi,bj) = spval
250 enddo
251 enddo
252 enddo
253 enddo
254 enddo
255 endif
256 cnew)
257
258 do bj = jtlo,jthi
259 do bi = itlo,ithi
260
261 localcost = 0. _d 0
262
263 c-- Determine the mask on weights
264 do k = 1,nnzobs
265 do j = jmin,jmax
266 do i = imin,imax
267 #ifdef ALLOW_OLD_ESTIM_CODES
268 cmask(i,j,k) = cosphi(i,j,bi,bj)*localmask(i,j,k,bi,bj)
269 #else
270 cmask(i,j,k) = localmask(i,j,k,bi,bj)
271 #endif
272 if ( localobs(i,j,k,bi,bj) .lt. spminloc .or.
273 & localobs(i,j,k,bi,bj) .gt. spmaxloc .or.
274 & localobs(i,j,k,bi,bj) .eq. spzeroloc ) then
275 cmask(i,j,k) = 0. _d 0
276 endif
277 enddo
278 enddo
279 enddo
280 c--
281 do k = 1,nnzobs
282 do j = jmin,jmax
283 do i = imin,imax
284 localwww = localweight(i,j,k,bi,bj)*cmask(i,j,k)
285 junk = ( localbar(i,j,k,bi,bj) -
286 & localobs(i,j,k,bi,bj) )
287 localcost = localcost + junk*junk*localwww
288 if ( localwww .ne. 0. )
289 & num_local(bi,bj) = num_local(bi,bj) + 1. _d 0
290 enddo
291 enddo
292 enddo
293
294 objf_local(bi,bj) = objf_local(bi,bj) + localcost
295
296 enddo
297 enddo
298
299 enddo
300 c-- End of second loop over records.
301
302 c-- End of localobsfile
303 endif
304
305 end

  ViewVC Help
Powered by ViewVC 1.1.22