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

Contents of /MITgcm/pkg/ecco/cost_drift.F

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


Revision 1.8 - (show annotations) (download)
Tue Oct 9 00:02:50 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.7: +36 -35 lines
add missing cvs $Header:$ or $Name:$

1 C $Header: $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_drift( myiter, mytime, mythid )
8
9 c ==================================================================
10 c SUBROUTINE cost_drift
11 c ==================================================================
12 c
13 c o Evaluate cost function contribution of the t and S difference
14 c between the first and the last year.
15 c
16 c started: from the "old" code
17 c
18 c Elisabeth Remy eremy@ucsd.edu july 31 2001
19 c
20 c ==================================================================
21 c SUBROUTINE cost_drift
22 c ==================================================================
23
24 implicit none
25
26 c == global variables ==
27
28 #include "EEPARAMS.h"
29 #include "SIZE.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "DYNVARS.h"
33
34 #include "cal.h"
35 #include "ecco_cost.h"
36 #include "ctrl.h"
37 #include "ctrl_dummy.h"
38 #include "optim.h"
39
40 c == routine arguments ==
41
42 integer myiter
43 _RL mytime
44 integer mythid
45
46 c == local variables ==
47
48 _RS one_rs
49 parameter( one_rs = 1. )
50
51 integer bi,bj
52 integer i,j,k
53 integer itlo,ithi
54 integer jtlo,jthi
55 integer jmin,jmax
56 integer imin,imax
57 integer irec
58 integer iltheta
59 integer ilsalt
60 integer nf, nl, nfmin
61 integer minrec
62
63 _RL fctilet
64 _RL fctiles
65 _RL fcthread_tdrift
66 _RL fcthread_tdrifs
67 _RL errtannurescal
68 _RL errsannurescal
69
70 character*(80) fnametheta
71 character*(80) fnamesalt
72
73 logical doglobalread
74 logical ladinit
75
76 character*(MAX_LEN_MBUF) msgbuf
77
78 _RL diagnosfld3d(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
79
80 c == external functions ==
81
82 integer ilnblnk
83 external ilnblnk
84
85 c == end of interface ==
86
87 jtlo = mybylo(mythid)
88 jthi = mybyhi(mythid)
89 itlo = mybxlo(mythid)
90 ithi = mybxhi(mythid)
91 jmin = 1
92 jmax = sny
93 imin = 1
94 imax = snx
95
96 c-- Read tiled data.
97 doglobalread = .false.
98 ladinit = .false.
99
100 #ifdef ALLOW_DRIFT_COST_CONTRIBUTION
101
102 c-- Rescale error read from data.err to convert to error/year
103 c-- (e.g. 0.08 degC year based on Levitus decadal drift 0.8 degC)
104 errtannurescal = 0.16
105 errsannurescal = 0.16
106
107 if (optimcycle .ge. 0) then
108 iltheta = ilnblnk( tbarfile )
109 write(fnametheta(1:80),'(2a,i10.10)')
110 & tbarfile(1:iltheta),'.',optimcycle
111 ilsalt = ilnblnk( sbarfile )
112 write(fnamesalt(1:80),'(2a,i10.10)')
113 & sbarfile(1:ilsalt),'.',optimcycle
114 endif
115
116 fcthread_tdrift = 0. _d 0
117 fcthread_tdrifs = 0. _d 0
118
119 do bj = jtlo,jthi
120 do bi = itlo,ithi
121 do k = 1,nr
122 do j = jmin,jmax
123 do i = imin,imax
124 Tfmean(i,j,k,bi,bj) = 0.0
125 Sfmean(i,j,k,bi,bj) = 0.0
126 Tlmean(i,j,k,bi,bj) = 0.0
127 Slmean(i,j,k,bi,bj) = 0.0
128 enddo
129 enddo
130 enddo
131 enddo
132 enddo
133
134 nf = 0
135 nl = 0
136 c-- Number of full years
137 nfmin = MAX(INT(FLOAT(nmonsrec)/12.),1)
138 c-- Prevent code from crashing if integrated for less than a year
139 minrec = MIN(nmonsrec,12)
140
141 c-- Loop over records.
142 do irec = 1,minrec
143
144 c-- Read time averages and the monthly mean data.
145 call active_read_xyz( fnametheta, tbar, irec,
146 & doglobalread, ladinit,
147 & optimcycle, mythid,
148 & xx_tbar_mean_dummy )
149
150 call active_read_xyz( fnamesalt, sbar, irec,
151 & doglobalread, ladinit,
152 & optimcycle, mythid,
153 & xx_sbar_mean_dummy )
154
155 nf = nf + 1
156 do bj = jtlo,jthi
157 do bi = itlo,ithi
158 do k = 1,nr
159 do j = jmin,jmax
160 do i = imin,imax
161 Tfmean(i,j,k,bi,bj) = Tfmean(i,j,k,bi,bj) +
162 & tbar(i,j,k,bi,bj)
163 Sfmean(i,j,k,bi,bj) = Sfmean(i,j,k,bi,bj) +
164 & sbar(i,j,k,bi,bj)
165 enddo
166 enddo
167 enddo
168 enddo
169 enddo
170
171 enddo
172
173 do irec = nmonsrec-minrec+1, nmonsrec
174
175 c-- Read time averages and the monthly mean data.
176 call active_read_xyz( fnametheta, tbar, irec,
177 & doglobalread, ladinit,
178 & optimcycle, mythid,
179 & xx_tbar_mean_dummy )
180
181 call active_read_xyz( fnamesalt, sbar, irec,
182 & doglobalread, ladinit,
183 & optimcycle, mythid,
184 & xx_sbar_mean_dummy )
185
186 nl = nl + 1
187
188 do bj = jtlo,jthi
189 do bi = itlo,ithi
190 do k = 1,nr
191 do j = jmin,jmax
192 do i = imin,imax
193 Tlmean(i,j,k,bi,bj) = Tlmean(i,j,k,bi,bj) +
194 & tbar(i,j,k,bi,bj)
195 Slmean(i,j,k,bi,bj) = Slmean(i,j,k,bi,bj) +
196 & sbar(i,j,k,bi,bj)
197 enddo
198 enddo
199 enddo
200 enddo
201 enddo
202
203 enddo
204
205
206 do bj = jtlo,jthi
207 do bi = itlo,ithi
208
209 c-- Loop over the model layers
210 fctiles = 0. _d 0
211 fctilet = 0. _d 0
212
213 do k = 1,nr
214 do j = jmin,jmax
215 do i = imin,imax
216 if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
217 fctiles = fctiles +
218 & (wsaltLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)/
219 & ((nfmin*errsannurescal)**2)*
220 & (Slmean(i,j,k,bi,bj)/nl - Sfmean(i,j,k,bi,bj)/nf)*
221 & (Slmean(i,j,k,bi,bj)/nl - Sfmean(i,j,k,bi,bj)/nf))
222 c
223 diagnosfld3d(i,j,k,bi,bj) =
224 & (wsaltLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)/
225 & ((nfmin*errsannurescal)**2)*
226 & (Slmean(i,j,k,bi,bj)/nl - Sfmean(i,j,k,bi,bj)/nf)*
227 & (Slmean(i,j,k,bi,bj)/nl - Sfmean(i,j,k,bi,bj)/nf))
228 c
229 if ( wsaltLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)
230 & .ne. 0. )
231 & num_sdrift(bi,bj) = num_sdrift(bi,bj) + 1. _d 0
232 else
233 diagnosfld3d(i,j,k,bi,bj) = 0.
234 endif
235 enddo
236 enddo
237 enddo
238
239 call mdswritefield( 'DiagnosCost_DriftSalt',
240 & writeBinaryPrec, globalfiles, 'RL', Nr,
241 & diagnosfld3d, 1, optimcycle, mythid )
242
243 do k = 1,nr
244 do j = jmin,jmax
245 do i = imin,imax
246 if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
247 fctilet = fctilet +
248 & (wthetaLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)/
249 & ((nfmin*errtannurescal)**2)*
250 & (Tlmean(i,j,k,bi,bj)/nl - Tfmean(i,j,k,bi,bj)/nf)*
251 & (Tlmean(i,j,k,bi,bj)/nl - Tfmean(i,j,k,bi,bj)/nf))
252 c
253 diagnosfld3d(i,j,k,bi,bj) =
254 & (wthetaLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)/
255 & ((nfmin*errtannurescal)**2)*
256 & (Tlmean(i,j,k,bi,bj)/nl - Tfmean(i,j,k,bi,bj)/nf)*
257 & (Tlmean(i,j,k,bi,bj)/nl - Tfmean(i,j,k,bi,bj)/nf))
258 c
259 if ( wthetaLev(i,j,k,bi,bj)*cosphi(i,j,bi,bj)
260 & .ne. 0. )
261 & num_tdrift(bi,bj) = num_tdrift(bi,bj) + 1. _d 0
262 else
263 diagnosfld3d(i,j,k,bi,bj) = 0.
264 endif
265 enddo
266 enddo
267 enddo
268
269 call mdswritefield( 'DiagnosCost_DriftTheta',
270 & writeBinaryPrec, globalfiles, 'RL', Nr,
271 & diagnosfld3d, 1, optimcycle, mythid )
272
273 fcthread_tdrift = fcthread_tdrift + fctilet
274 fcthread_tdrifs = fcthread_tdrifs + fctiles
275 objf_tdrift(bi,bj) = objf_tdrift(bi,bj) + fctilet
276 objf_sdrift(bi,bj) = objf_sdrift(bi,bj) + fctiles
277
278 enddo
279 enddo
280
281 #endif
282
283 return
284 end
285

  ViewVC Help
Powered by ViewVC 1.1.22