/[MITgcm]/MITgcm_contrib/torge/itd/code/seaice_cost_sst.F
ViewVC logotype

Annotation of /MITgcm_contrib/torge/itd/code/seaice_cost_sst.F

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


Revision 1.2 - (hide annotations) (download)
Wed Mar 27 18:59:52 2013 UTC (12 years, 4 months ago) by torge
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +1 -1 lines
updating my MITgcm_contrib directory to include latest changes on main branch;
settings are to run a 1D test szenario with ITD code and 7 categories

1 torge 1.2 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_cost_sst.F,v 1.8 2012/11/09 22:15:18 heimbach Exp $
2 torge 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     subroutine seaice_cost_sst(
7     & nnzbar, localbarfile, localbar, xx_localbar_mean_dummy,
8     & areabarfile, areabar, xx_areabar_mean_dummy,
9     & nnzobs, localobsfile, localobs, mult_local,
10     & nrecloc, localstartdate, localperiod,
11     & localmask, localweight,
12     & spminloc, spmaxloc, spzeroloc,
13     & objf_local, num_local,
14     & myiter, mytime, mythid )
15    
16     implicit none
17    
18     c ian fenty
19     c == global variables ==
20    
21     #include "EEPARAMS.h"
22     #include "SIZE.h"
23     #include "PARAMS.h"
24     #ifdef ALLOW_CAL
25     # include "cal.h"
26     #endif
27     #ifdef ALLOW_COST
28     # include "optim.h"
29     # ifdef ALLOW_ECCO
30     # include "ecco_cost.h"
31     # endif
32     # ifdef ALLOW_SEAICE
33     # include "SEAICE_COST.h"
34     # include "SEAICE_SIZE.h"
35     # include "SEAICE_PARAMS.h"
36     # endif
37     #endif
38    
39     c == routine arguments ==
40    
41     integer nnzbar
42     integer nnzobs
43     integer nrecloc
44     integer myiter
45     integer mythid
46     integer localstartdate(4)
47    
48     _RL localbar (1-olx:snx+olx,1-oly:sny+oly,nnzbar,nsx,nsy)
49     _RL areabar (1-olx:snx+olx,1-oly:sny+oly,nnzbar,nsx,nsy)
50    
51     _RL localobs (1-olx:snx+olx,1-oly:sny+oly,nnzobs,nsx,nsy)
52     _RL localweight(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
53     _RS localmask (1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
54     _RL xx_localbar_mean_dummy
55     _RL xx_areabar_mean_dummy
56     _RL mult_local
57     _RL mytime
58     _RL localperiod
59     _RL spminloc
60     _RL spmaxloc
61     _RL spzeroloc
62     _RL objf_local(nsx,nsy)
63     _RL num_local(nsx,nsy)
64    
65     character*(MAX_LEN_FNAM) areabarfile
66     character*(MAX_LEN_FNAM) localbarfile
67     character*(MAX_LEN_FNAM) localobsfile
68    
69     #if (defined (ALLOW_ECCO) && defined (ALLOW_COST))
70     c == local variables ==
71    
72     integer bi,bj
73     integer i,j,k
74     integer itlo,ithi
75     integer jtlo,jthi
76     integer jmin,jmax
77     integer imin,imax
78     integer irec
79     integer il
80     integer localrec
81     integer obsrec
82    
83     logical doglobalread
84     logical ladinit
85    
86     _RL spval
87     parameter (spval = -9999. )
88     _RL localwww
89     _RL localcost
90     _RL junk
91    
92     _RL cmask (1-olx:snx+olx,1-oly:sny+oly,nnzobs)
93    
94     character*(128) fname1, fname2,fname3
95     character*(MAX_LEN_MBUF) msgbuf
96    
97     cnew(
98     _RL daytime
99     _RL diffsecs
100     integer dayiter
101     integer daydate(4)
102     integer difftime(4)
103     integer middate(4)
104     integer yday, ymod
105     integer md, dd, sd, ld, wd
106     integer mody, modm
107     integer beginmodel, beginlocal
108     logical exst
109     cnew)
110    
111     c == external functions ==
112    
113     integer ilnblnk
114     external ilnblnk
115    
116     c == end of interface ==
117    
118     C- jmc: params SEAICE_freeze has been retired; set it locally until someone
119     C who knows what this cost-cointribution means fix it.
120     _RL SEAICE_freeze
121     SEAICE_freeze = -1.96 _d 0
122    
123     jtlo = mybylo(mythid)
124     jthi = mybyhi(mythid)
125     itlo = mybxlo(mythid)
126     ithi = mybxhi(mythid)
127     jmin = 1
128     jmax = sny
129     imin = 1
130     imax = snx
131    
132     c-- Initialise local variables.
133    
134     localwww = 0. _d 0
135    
136     do bj = jtlo,jthi
137     do bi = itlo,ithi
138     objf_local(bi,bj) = 0. _d 0
139     num_local(bi,bj) = 0. _d 0
140     enddo
141     enddo
142    
143     c-- First, read tiled data.
144     doglobalread = .false.
145     ladinit = .false.
146    
147    
148     write(fname1(1:128),'(80a)') ' '
149     write(fname3(1:128),'(80a)') ' '
150    
151     il=ilnblnk( localbarfile )
152     write(fname1(1:128),'(2a,i10.10)')
153     & localbarfile(1:il),'.',optimcycle
154    
155     il=ilnblnk( areabarfile )
156     write(fname3(1:128),'(2a,i10.10)')
157     & areabarfile(1:il),'.',optimcycle
158    
159     if ( .NOT. ( localobsfile.EQ.' ' ) ) then
160    
161     c-- Loop over records for the second time.
162     do irec = 1, nrecloc
163    
164     if ( nnzbar .EQ. 1 ) then
165     call active_read_xy( fname1, localbar, irec, doglobalread,
166     & ladinit, optimcycle, mythid,
167     & xx_localbar_mean_dummy )
168     else
169     call active_read_xyz( fname1, localbar, irec, doglobalread,
170     & ladinit, optimcycle, mythid,
171     & xx_localbar_mean_dummy )
172     endif
173    
174     if ( nnzbar .EQ. 1 ) then
175     call active_read_xy( fname3, areabar, irec, doglobalread,
176     & ladinit, optimcycle, mythid,
177     & xx_areabar_mean_dummy )
178     else
179     call active_read_xyz( fname3, areabar, irec, doglobalread,
180     & ladinit, optimcycle, mythid,
181     & xx_areabar_mean_dummy )
182     endif
183    
184     cnew(
185     obsrec = irec
186    
187     daytime = FLOAT(secondsperday*(irec-1)) + modelstart
188     dayiter = hoursperday*(irec-1)+modeliter0
189    
190     call cal_getdate( dayiter, daytime, daydate, mythid )
191     call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
192     ymod = smrareastartdate(1)/10000
193    
194     #ifdef SEAICE_DEBUG
195     print *,'cost_seaice_sst_r2'
196     print *,'daydate ', daydate
197     print *,'areaobsfile: ', localobsfile
198     print *,'nrecloc ', nrecloc
199     print *,'obsrec,daytime ', obsrec,daytime
200     print *,'dayiter ', dayiter
201     print *,'yday : ', yday
202     print *,'md,dd,sd ', md,dd,sd
203     print *,'ld,wd ', ld,wd
204     print *,'loclstrtdte(1) ', localstartdate(1)
205     print *,'ymod, yday ', ymod,yday
206     print *,'smrarstrtdt(1) ', smrareastartdate(1)
207     print *,'smrarstartdate ', smrareastartdate
208     #endif /* SEAICE_DEBUG */
209    
210     if ( ymod .EQ. yday ) then
211     middate(1) = smrareastartdate(1)
212     else
213     middate(1) = yday*10000+100+1
214     endif
215     middate(2) = 0
216     middate(3) = modelstartdate(3)
217     middate(4) = modelstartdate(4)
218    
219    
220     call cal_TimePassed( middate, daydate, difftime, mythid )
221     call cal_ToSeconds( difftime, diffsecs, mythid )
222    
223     localrec = int(diffsecs/localperiod) + 1
224    
225     #ifdef SEAICE_DEBUG
226     print *,'middate(1,2) ',middate(1),middate(2)
227     print *,'middate(3,4) ', middate(3),middate(4)
228     print *,'difftime,diffsecs',difftime,diffsecs
229     print *,'localrec ',localrec
230     #endif
231    
232     il=ilnblnk(localobsfile)
233     write(fname2(1:128),'(2a,i4)')
234     & localobsfile(1:il), '_', yday
235     inquire( file=fname2, exist=exst )
236    
237     #ifdef SEAICE_DEBUG
238     print *,'fname2',fname2
239     #endif
240     if (.NOT. exst) then
241     write(fname2(1:128),'(a)') localobsfile(1:il)
242     localrec = obsrec
243     #ifdef SEAICE_DEBUG
244     print *,'localrec ', localrec
245     print *,'not exist'
246     #endif
247     endif
248    
249     if ( localrec .GT. 0 ) then
250    
251     #ifdef SEAICE_DEBUG
252     print *,'calling mdsreadfile',fname2,localrec
253     #endif
254    
255     call mdsreadfield( fname2, cost_iprec, cost_yftype, nnzobs,
256     & localobs, localrec, mythid )
257     else
258     do bj = jtlo,jthi
259     do bi = itlo,ithi
260     do k = 1,nnzobs
261     do j = jmin,jmax
262     do i = imin,imax
263     localobs(i,j,k,bi,bj) = spval
264     enddo
265     enddo
266     enddo
267     enddo
268     enddo
269     endif
270     cnew)
271    
272     #ifdef SEAICE_DEBUG
273     do bj = jtlo,jthi
274     do bi = itlo,ithi
275     do k = 1,nnzobs
276     do i = imin,imax
277     do j = jmin,jmax
278     if (localobs(i,j,k,bi,bj) .LT. -1) THEN
279     print *,'obs rec date: ', -localobs(i,j,1,bi,bj)
280     endif
281     enddo
282     enddo
283     enddo
284     enddo
285     enddo
286     #endif
287    
288     do bj = jtlo,jthi
289     do bi = itlo,ithi
290    
291     localcost = 0. _d 0
292    
293     c-- Determine the mask on weights
294     do k = 1,nnzobs
295     do j = jmin,jmax
296     do i = imin,imax
297     cmask(i,j,k) = cosphi(i,j,bi,bj)*localmask(i,j,k,bi,bj)
298     if ( localobs(i,j,k,bi,bj) .lt. spminloc .or.
299     & localobs(i,j,k,bi,bj) .gt. spmaxloc .or.
300     & localobs(i,j,k,bi,bj) .eq. spzeroloc ) then
301     cmask(i,j,k) = 0. _d 0
302     endif
303     enddo
304     enddo
305     enddo
306     c--
307     do k = 1,nnzobs
308     do j = jmin,jmax
309     do i = imin,imax
310     localwww = localweight(i,j,bi,bj)*cmask(i,j,k)
311    
312     c only accumulate cost if there is ice observed but not simulated..
313     if ( localobs(i,j,k,bi,bj) .GT. 0.0 .AND.
314     & areabar(i,j,1,bi,bj) .LE. 0.0) then
315    
316     junk = ( localbar(i,j,k,bi,bj) -
317     & SEAICE_freeze + SEAICE_clamp_theta )
318    
319     else
320     junk = 0.0
321     endif
322    
323     localcost = localcost + junk*junk*localwww
324    
325     #ifdef SEAICE_DEBUG
326     if ((i == SEAICE_debugPointX) .and.
327     & (j == SEAICE_debugPointY)) then
328    
329     print '(A,2i4,3(1x,1P2E15.3))',
330     & 'costg i j tbar, abar,obs ',i,j,
331     & localbar(i,j,k,bi,bj),
332     & areabar(i,j,k,bi,bj),
333     & localobs(i,j,k,bi,bj)
334    
335     print '(A,2i4,2(1x,1P2E15.3))',
336     & 'costg i j bar-obs,wgt,loCost ',i,j,
337     & junk,
338     & localwww,
339     & localcost
340     endif
341     #endif
342    
343     if ( localwww .ne. 0. )
344     & num_local(bi,bj) = num_local(bi,bj) + 1. _d 0
345     enddo
346     enddo
347     enddo
348    
349     objf_local(bi,bj) = objf_local(bi,bj) + localcost
350    
351     enddo !/bj
352     enddo !/ bi
353    
354     enddo
355     c-- End of second loop over records.
356    
357     c-- End of mult_local or localobsfile
358     endif
359     #endif /* ifdef ALLOW_COST */
360    
361     end

  ViewVC Help
Powered by ViewVC 1.1.22