/[MITgcm]/MITgcm/pkg/seaice/seaice_cost_sss.F
ViewVC logotype

Annotation of /MITgcm/pkg/seaice/seaice_cost_sss.F

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


Revision 1.10 - (hide annotations) (download)
Mon Mar 23 21:04:59 2015 UTC (10 years, 3 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65k, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, HEAD
Changes since 1.9: +5 -1 lines
- add CPP brackets.

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

  ViewVC Help
Powered by ViewVC 1.1.22