/[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.6 - (show annotations) (download)
Wed Sep 7 03:02:11 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint58e_post, checkpoint57v_post, checkpoint57s_post, checkpoint57y_post, checkpoint58n_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.5: +1 -5 lines
Introduce nnztbar, nnzsbar to distinguish btw 2d/3d bar files
at initialisation time.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_generic.F,v 1.5 2005/09/07 02:44:37 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
153 if ( nnzbar .EQ. 1 ) then
154 call active_read_xy( fname1, localbar, irec, doglobalread,
155 & ladinit, optimcycle, mythid,
156 & xx_localbar_mean_dummy )
157 else
158 call active_read_xyz( fname1, localbar, irec, doglobalread,
159 & ladinit, optimcycle, mythid,
160 & xx_localbar_mean_dummy )
161 endif
162
163 cnew(
164 if ( localperiod .EQ. 86400. ) then
165 c-- assume daily fields
166 obsrec = irec
167 daytime = FLOAT(secondsperday*(irec-1))
168 dayiter = hoursperday*(irec-1)
169 call cal_getdate( dayiter, daytime, daydate, mythid )
170 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
171 ymod = localstartdate(1)/10000
172 if ( ymod .EQ. yday ) then
173 middate(1) = modelstartdate(1)
174 else
175 middate(1) = yday*10000+100+1
176 endif
177 middate(2) = 0
178 middate(3) = modelstartdate(3)
179 middate(4) = modelstartdate(4)
180 call cal_TimePassed( middate, daydate, difftime, mythid )
181 call cal_ToSeconds( difftime, diffsecs, mythid )
182 localrec = int(diffsecs/localperiod) + 1
183 else
184 c-- assume monthly fields
185 beginlocal = localstartdate(1)/10000
186 beginmodel = modelstartdate(1)/10000
187 obsrec =
188 & ( beginmodel - beginlocal )*nmonthyear
189 & + ( mod(modelstartdate(1)/100,100)
190 & -mod(localstartdate(1)/100,100) )
191 & + irec
192 mody = modelstartdate(1)/10000
193 modm = modelstartdate(1)/100 - mody*100
194 yday = mody + INT((modm-1+irec-1)/12)
195 localrec = 1 + MOD(modm-1+irec-1,12)
196 endif
197
198 il=ilnblnk(localobsfile)
199 write(fname2(1:128),'(2a,i4)')
200 & localobsfile(1:il), '_', yday
201 inquire( file=fname2, exist=exst )
202 if (.NOT. exst) then
203 write(fname2(1:128),'(a)') localobsfile(1:il)
204 localrec = obsrec
205 endif
206
207 if ( localrec .GT. 0 ) then
208 call mdsreadfield( fname2, cost_iprec, cost_yftype, nnzobs,
209 & localobs, localrec, mythid )
210 else
211 do bj = jtlo,jthi
212 do bi = itlo,ithi
213 do k = 1,nnzobs
214 do j = jmin,jmax
215 do i = imin,imax
216 localobs(i,j,k,bi,bj) = spval
217 enddo
218 enddo
219 enddo
220 enddo
221 enddo
222 endif
223 cnew)
224
225 do bj = jtlo,jthi
226 do bi = itlo,ithi
227
228 localcost = 0. _d 0
229
230 c-- Determine the mask on weights
231 do k = 1,nnzobs
232 do j = jmin,jmax
233 do i = imin,imax
234 cmask(i,j,k) = cosphi(i,j,bi,bj)*localmask(i,j,k,bi,bj)
235 if ( localobs(i,j,k,bi,bj) .lt. spminloc .or.
236 & localobs(i,j,k,bi,bj) .gt. spmaxloc .or.
237 & localobs(i,j,k,bi,bj) .eq. spzeroloc ) then
238 cmask(i,j,k) = 0. _d 0
239 endif
240 enddo
241 enddo
242 enddo
243 c--
244 do k = 1,nnzobs
245 do j = jmin,jmax
246 do i = imin,imax
247 localwww = localweight(i,j,k,bi,bj)*cmask(i,j,k)
248 junk = ( localbar(i,j,k,bi,bj) -
249 & localobs(i,j,k,bi,bj) )
250 localcost = localcost + junk*junk*localwww
251 if ( localwww .ne. 0. )
252 & num_local(bi,bj) = num_local(bi,bj) + 1. _d 0
253 enddo
254 enddo
255 enddo
256
257 objf_local(bi,bj) = objf_local(bi,bj) + localcost
258
259 enddo
260 enddo
261
262 enddo
263 c-- End of second loop over records.
264
265 c-- End of mult_local or localobsfile
266 endif
267
268 #endif /* ifdef ALLOW_COST */
269
270 end

  ViewVC Help
Powered by ViewVC 1.1.22