/[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.5 - (show annotations) (download)
Wed Sep 7 02:44:37 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
Changes since 1.4: +5 -1 lines
o replace various cost routines by single generic routine cost_generic.F
o add weights for SST, SSS control
o bracket GAD.h for #undef ALLOW_GENERIC_ADVDIFF version

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_generic.F,v 1.4 2005/09/02 21:11:19 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_generic(
7 & nnzbar, localbarfile, localbar, xx_localbar_mean_dummy,
8 & nnzobs, localobsfile, localobs, mult_local,
9 & nrecloc, localstartdate, localperiod,
10 & localmask, localweight,
11 & spminloc, spmaxloc, spzeroloc,
12 & objf_local, num_local,
13 & myiter, mytime, mythid )
14
15 c ==================================================================
16 c SUBROUTINE cost_generic
17 c ==================================================================
18 c
19 c o Generic routine for evaluating time-dependent
20 c cost function contribution
21 c
22 c ==================================================================
23 c SUBROUTINE cost_generic
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 #ifdef ALLOW_CAL
34 # include "cal.h"
35 #endif
36 #ifdef ALLOW_COST
37 # include "ecco_cost.h"
38 # include "optim.h"
39 # ifdef ALLOW_SEAICE
40 # include "SEAICE_COST.h"
41 # endif
42 #endif
43
44 c == routine arguments ==
45
46 integer nnzbar
47 integer nnzobs
48 integer nrecloc
49 integer myiter
50 integer mythid
51 integer localstartdate(4)
52
53 _RL localbar (1-olx:snx+olx,1-oly:sny+oly,nnzbar,nsx,nsy)
54 _RL localobs (1-olx:snx+olx,1-oly:sny+oly,nnzobs,nsx,nsy)
55 _RL localweight(1-olx:snx+olx,1-oly:sny+oly,nnzobs,nsx,nsy)
56 _RL localmask (1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
57 _RL xx_localbar_mean_dummy
58 _RL mult_local
59 _RL mytime
60 _RL localperiod
61 _RL spminloc
62 _RL spmaxloc
63 _RL spzeroloc
64 _RL objf_local(nsx,nsy)
65 _RL num_local(nsx,nsy)
66
67 character*(MAX_LEN_FNAM) localbarfile
68 character*(MAX_LEN_FNAM) localobsfile
69
70 #ifdef ALLOW_COST
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 cmask (1-olx:snx+olx,1-oly:sny+oly,nnzobs)
94
95 character*(128) fname1, fname2
96 character*(MAX_LEN_MBUF) msgbuf
97
98 cnew(
99 _RL daytime
100 _RL diffsecs
101 integer dayiter
102 integer daydate(4)
103 integer difftime(4)
104 integer middate(4)
105 integer yday, ymod
106 integer md, dd, sd, ld, wd
107 integer mody, modm
108 integer beginmodel, beginlocal
109 logical exst
110 cnew)
111
112 c == external functions ==
113
114 integer ilnblnk
115 external ilnblnk
116
117 c == end of interface ==
118
119 jtlo = mybylo(mythid)
120 jthi = mybyhi(mythid)
121 itlo = mybxlo(mythid)
122 ithi = mybxhi(mythid)
123 jmin = 1
124 jmax = sny
125 imin = 1
126 imax = snx
127
128 c-- Initialise local variables.
129
130 localwww = 0. _d 0
131
132 do bj = jtlo,jthi
133 do bi = itlo,ithi
134 objf_local(bi,bj) = 0. _d 0
135 num_local(bi,bj) = 0. _d 0
136 enddo
137 enddo
138
139 c-- First, read tiled data.
140 doglobalread = .false.
141 ladinit = .false.
142
143 write(fname1(1:128),'(80a)') ' '
144 il=ilnblnk( localbarfile )
145 write(fname1(1:128),'(2a,i10.10)')
146 & localbarfile(1:il),'.',optimcycle
147
148 if ( .NOT. ( mult_local.EQ.0. .OR. localobsfile.EQ.' ' ) ) then
149
150 c-- Loop over records for the second time.
151 do irec = 1, nrecloc
152 cph(
153 if ( localobsfile .EQ. sstdatfile )
154 & print *, 'ph-sst A ', irec, nrecloc
155 cph)
156
157 if ( nnzbar .EQ. 1 ) then
158 call active_read_xy( fname1, localbar, irec, doglobalread,
159 & ladinit, optimcycle, mythid,
160 & xx_localbar_mean_dummy )
161 else
162 call active_read_xyz( fname1, localbar, irec, doglobalread,
163 & ladinit, optimcycle, mythid,
164 & xx_localbar_mean_dummy )
165 endif
166
167 cnew(
168 if ( localperiod .EQ. 86400. ) then
169 c-- assume daily fields
170 obsrec = irec
171 daytime = FLOAT(secondsperday*(irec-1))
172 dayiter = hoursperday*(irec-1)
173 call cal_getdate( dayiter, daytime, daydate, mythid )
174 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
175 ymod = localstartdate(1)/10000
176 if ( ymod .EQ. yday ) then
177 middate(1) = modelstartdate(1)
178 else
179 middate(1) = yday*10000+100+1
180 endif
181 middate(2) = 0
182 middate(3) = modelstartdate(3)
183 middate(4) = modelstartdate(4)
184 call cal_TimePassed( middate, daydate, difftime, mythid )
185 call cal_ToSeconds( difftime, diffsecs, mythid )
186 localrec = int(diffsecs/localperiod) + 1
187 else
188 c-- assume monthly fields
189 beginlocal = localstartdate(1)/10000
190 beginmodel = modelstartdate(1)/10000
191 obsrec =
192 & ( beginmodel - beginlocal )*nmonthyear
193 & + ( mod(modelstartdate(1)/100,100)
194 & -mod(localstartdate(1)/100,100) )
195 & + irec
196 mody = modelstartdate(1)/10000
197 modm = modelstartdate(1)/100 - mody*100
198 yday = mody + INT((modm-1+irec-1)/12)
199 localrec = 1 + MOD(modm-1+irec-1,12)
200 endif
201
202 il=ilnblnk(localobsfile)
203 write(fname2(1:128),'(2a,i4)')
204 & localobsfile(1:il), '_', yday
205 inquire( file=fname2, exist=exst )
206 if (.NOT. exst) then
207 write(fname2(1:128),'(a)') localobsfile(1:il)
208 localrec = obsrec
209 endif
210
211 if ( localrec .GT. 0 ) then
212 call mdsreadfield( fname2, cost_iprec, cost_yftype, nnzobs,
213 & localobs, localrec, mythid )
214 else
215 do bj = jtlo,jthi
216 do bi = itlo,ithi
217 do k = 1,nnzobs
218 do j = jmin,jmax
219 do i = imin,imax
220 localobs(i,j,k,bi,bj) = spval
221 enddo
222 enddo
223 enddo
224 enddo
225 enddo
226 endif
227 cnew)
228
229 do bj = jtlo,jthi
230 do bi = itlo,ithi
231
232 localcost = 0. _d 0
233
234 c-- Determine the mask on weights
235 do k = 1,nnzobs
236 do j = jmin,jmax
237 do i = imin,imax
238 cmask(i,j,k) = cosphi(i,j,bi,bj)*localmask(i,j,k,bi,bj)
239 if ( localobs(i,j,k,bi,bj) .lt. spminloc .or.
240 & localobs(i,j,k,bi,bj) .gt. spmaxloc .or.
241 & localobs(i,j,k,bi,bj) .eq. spzeroloc ) then
242 cmask(i,j,k) = 0. _d 0
243 endif
244 enddo
245 enddo
246 enddo
247 c--
248 do k = 1,nnzobs
249 do j = jmin,jmax
250 do i = imin,imax
251 localwww = localweight(i,j,k,bi,bj)*cmask(i,j,k)
252 junk = ( localbar(i,j,k,bi,bj) -
253 & localobs(i,j,k,bi,bj) )
254 localcost = localcost + junk*junk*localwww
255 if ( localwww .ne. 0. )
256 & num_local(bi,bj) = num_local(bi,bj) + 1. _d 0
257 enddo
258 enddo
259 enddo
260
261 objf_local(bi,bj) = objf_local(bi,bj) + localcost
262
263 enddo
264 enddo
265
266 enddo
267 c-- End of second loop over records.
268
269 c-- End of mult_local or localobsfile
270 endif
271
272 #endif /* ifdef ALLOW_COST */
273
274 end

  ViewVC Help
Powered by ViewVC 1.1.22