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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 31 19:00:51 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
New routine cost_generic.F should facilitate intro.
of new cost terms and replace individual routines.

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_ssh.F,v 1.6 2005/05/27 22:10:26 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,
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     #endif
40    
41     c == routine arguments ==
42    
43     integer nnzbar
44     integer nnzobs
45     integer nrecloc
46     integer myiter
47     integer mythid
48     integer localstartdate(4)
49    
50     _RL localbar (1-olx:snx+olx,1-oly:sny+oly,nnzbar,nsx,nsy)
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,nnzobs,nsx,nsy)
53     _RL localmask (1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
54     _RL xx_localbar_mean_dummy
55     _RL mytime
56     _RL localperiod
57     _RL spminloc
58     _RL spmaxloc
59     _RL spzeroloc
60     _RL objf_local(nsx,nsy)
61     _RL num_local(nsx,nsy)
62    
63     character*(MAX_LEN_FNAM) localbarfile
64     character*(MAX_LEN_FNAM) localobsfile
65    
66     #ifdef ALLOW_COST
67     c == local variables ==
68    
69     integer bi,bj
70     integer i,j,k
71     integer itlo,ithi
72     integer jtlo,jthi
73     integer jmin,jmax
74     integer imin,imax
75     integer irec
76     integer il
77     integer localrec
78    
79     logical doglobalread
80     logical ladinit
81    
82     _RL localwww
83     _RL localcost
84     _RL junk
85    
86     _RL cmask (1-olx:snx+olx,1-oly:sny+oly,nnzobs)
87    
88     character*(128) fname1, fname2
89     character*(MAX_LEN_MBUF) msgbuf
90    
91     cnew(
92     _RL daytime
93     _RL diffsecs
94     integer dayiter
95     integer daydate(4)
96     integer difftime(4)
97     integer middate(4)
98     integer yday, ymod
99     integer md, dd, sd, ld, wd
100     integer mody, modm
101     logical exst
102     cnew)
103    
104     c == external functions ==
105    
106     integer ilnblnk
107     external ilnblnk
108    
109     c == end of interface ==
110    
111     jtlo = mybylo(mythid)
112     jthi = mybyhi(mythid)
113     itlo = mybxlo(mythid)
114     ithi = mybxhi(mythid)
115     jmin = 1
116     jmax = sny
117     imin = 1
118     imax = snx
119    
120     c-- Initialise local variables.
121    
122     localwww = 0. _d 0
123    
124     c-- First, read tiled data.
125     doglobalread = .false.
126     ladinit = .false.
127    
128     write(fname1(1:128),'(80a)') ' '
129     il=ilnblnk( localbarfile )
130     write(fname1(1:128),'(2a,i10.10)')
131     & localbarfile(1:il),'.',optimcycle
132    
133     c-- Loop over records for the second time.
134     do irec = 1, nrecloc
135    
136     if ( nnzbar .EQ. 1 ) then
137     call active_read_xy( fname1, localbar, irec, doglobalread,
138     & ladinit, optimcycle, mythid,
139     & xx_localbar_mean_dummy )
140     else
141     call active_read_xyz( fname1, localbar, irec, doglobalread,
142     & ladinit, optimcycle, mythid,
143     & xx_localbar_mean_dummy )
144     endif
145    
146     cnew(
147     if ( localperiod .EQ. 86400. ) then
148     c-- assume daily fields
149     daytime = FLOAT(secondsperday*(irec-1))
150     dayiter = hoursperday*(irec-1)
151     call cal_getdate( dayiter, daytime, daydate, mythid )
152     call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
153     ymod = localstartdate(1)/10000
154     if ( ymod .EQ. yday ) then
155     middate(1) = modelstartdate(1)
156     else
157     middate(1) = yday*10000+100+1
158     endif
159     middate(2) = 0
160     middate(3) = modelstartdate(3)
161     middate(4) = modelstartdate(4)
162     call cal_TimePassed( middate, daydate, difftime, mythid )
163     call cal_ToSeconds( difftime, diffsecs, mythid )
164     localrec = int(diffsecs/localperiod) + 1
165     else
166     c-- assume monthly fields
167     mody = modelstartdate(1)/10000
168     modm = modelstartdate(1)/100 - mody*100
169     yday = mody + INT((modm-1+irec-1)/12)
170     localrec = 1 + MOD(modm-1+irec-1,12)
171     endif
172    
173     il=ilnblnk(localobsfile)
174     write(fname2(1:128),'(2a,i4)')
175     & localobsfile(1:il), '_', yday
176     inquire( file=fname2, exist=exst )
177     if (.NOT. exst) then
178     write(fname2(1:128),'(a)') localobsfile(1:il)
179     localrec = irec
180     endif
181    
182     call mdsreadfield( fname2, cost_iprec, cost_yftype, nnzobs,
183     & localobs, localrec, mythid )
184     cnew)
185    
186     do bj = jtlo,jthi
187     do bi = itlo,ithi
188    
189     localcost = 0. _d 0
190    
191     c-- Determine the mask on weights
192     do k = 1,nnzobs
193     do j = jmin,jmax
194     do i = imin,imax
195     cmask(i,j,k) = cosphi(i,j,bi,bj)*localmask(i,j,k,bi,bj)
196     if ( localobs(i,j,k,bi,bj) .lt. spminloc .or.
197     & localobs(i,j,k,bi,bj) .gt. spmaxloc .or.
198     & localobs(i,j,k,bi,bj) .eq. spzeroloc ) then
199     cmask(i,j,k) = 0. _d 0
200     endif
201     enddo
202     enddo
203     enddo
204     c--
205     do k = 1,nnzobs
206     do j = jmin,jmax
207     do i = imin,imax
208     localwww = localweight(i,j,k,bi,bj)*cmask(i,j,k)
209     junk = ( localbar(i,j,k,bi,bj) -
210     & localobs(i,j,k,bi,bj) )
211     localcost = localcost + junk*junk*localwww
212     if ( localwww .ne. 0. )
213     & num_local(bi,bj) = num_local(bi,bj) + 1. _d 0
214     enddo
215     enddo
216     enddo
217    
218     objf_local(bi,bj) = objf_local(bi,bj) + localcost
219    
220     enddo
221     enddo
222    
223     enddo
224     c-- End of second loop over records.
225    
226     #endif /* ifdef ALLOW_COST */
227    
228     end

  ViewVC Help
Powered by ViewVC 1.1.22