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

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

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


Revision 1.7 - (show annotations) (download)
Wed Jun 17 15:11:32 2009 UTC (14 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, 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, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.6: +1 -14 lines
Remove depth limitations for in-situ costs.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_ctdsclim.F,v 1.6 2009/04/28 18:13:27 jmc Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_ctdsclim(
8 I myiter,
9 I mytime,
10 I mythid
11 & )
12
13 c ==================================================================
14 c SUBROUTINE cost_Ctdsclim
15 c ==================================================================
16 c
17 c o Evaluate cost function contribution of salinity.
18 c
19 c started: Christian Eckert eckert@mit.edu 30-Jun-1999
20 c
21 c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
22 c
23 c - Restructured the code in order to create a package
24 c for the MITgcmUV.
25 c
26 c changed: Patrick Heimbach heimbach@mit.edu 27-May-2000
27 c
28 c - set ladinit to .true. to initialise adsbar file
29 c
30 c ==================================================================
31 c SUBROUTINE cost_Ctdsclim
32 c ==================================================================
33
34 implicit none
35
36 c == global variables ==
37
38 #include "EEPARAMS.h"
39 #include "SIZE.h"
40 #include "GRID.h"
41 #include "DYNVARS.h"
42
43 #include "cal.h"
44 #include "ecco_cost.h"
45 #include "ctrl.h"
46 #include "ctrl_dummy.h"
47 #include "optim.h"
48
49 c == routine arguments ==
50
51 integer myiter
52 _RL mytime
53 integer mythid
54
55 c == local variables ==
56
57 _RS one_rs
58 parameter( one_rs = 1. )
59
60 integer bi,bj
61 integer i,j,k
62 integer itlo,ithi
63 integer jtlo,jthi
64 integer jmin,jmax
65 integer imin,imax
66 integer irec
67 integer levmon
68 integer levoff
69 integer ilctdsclim
70
71 _RL fctile
72 _RL fcthread
73
74 _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
75 _RL spval
76
77 character*(80) fnamesalt
78
79 logical doglobalread
80 logical ladinit
81
82 character*(MAX_LEN_MBUF) msgbuf
83
84 #ifdef GENERIC_BAR_MONTH
85 integer mrec, nyears, iyear
86 #endif
87 c == external functions ==
88
89 integer ilnblnk
90 external ilnblnk
91
92 c == end of interface ==
93
94 jtlo = mybylo(mythid)
95 jthi = mybyhi(mythid)
96 itlo = mybxlo(mythid)
97 ithi = mybxhi(mythid)
98 jmin = 1
99 jmax = sny
100 imin = 1
101 imax = snx
102
103 spval = -9990.
104
105 c-- Read tiled data.
106 doglobalread = .false.
107 ladinit = .false.
108
109 #ifdef ALLOW_CTDSCLIM_COST_CONTRIBUTION
110
111 if (optimcycle .ge. 0) then
112 ilctdsclim = ilnblnk( sbarfile )
113 write(fnamesalt(1:80),'(2a,i10.10)')
114 & sbarfile(1:ilctdsclim),'.',optimcycle
115 endif
116
117 fcthread = 0. _d 0
118
119 #ifdef GENERIC_BAR_MONTH
120 c-- Loop over month
121 do irec = 1,12
122 nyears=int((nmonsrec-irec)/12)+1
123 if(nyears.gt.0) then
124 do iyear=1,nyears
125 mrec=irec+(iyear-1)*12
126 c-- Read time averages and the monthly mean data.
127 call active_read_xyz( fnamesalt, sbar, mrec,
128 & doglobalread, ladinit,
129 & optimcycle, mythid,
130 & xx_sbar_mean_dummy )
131 do bj = jtlo,jthi
132 do bi = itlo,ithi
133 do k = 1,nr
134 do j = jmin,jmax
135 do i = imin,imax
136 if(iyear.eq.1) then
137 sbar_gen(i,j,k,bi,bj) =sbar(i,j,k,bi,bj)
138 elseif(iyear.eq.nyears) then
139 sbar(i,j,k,bi,bj) =(sbar_gen(i,j,k,bi,bj)
140 $ +sbar(i,j,k,bi,bj))/float(nyears)
141 else
142 sbar_gen(i,j,k,bi,bj) =sbar_gen(i,j,k,bi,bj)
143 $ +sbar(i,j,k,bi,bj)
144 endif
145 enddo
146 enddo
147 enddo
148 enddo
149 enddo
150 enddo
151 #else
152 c-- Loop over records.
153 do irec = 1,nmonsrec
154
155 c-- Read time averages and the monthly mean data.
156 call active_read_xyz( fnamesalt, sbar, irec,
157 & doglobalread, ladinit,
158 & optimcycle, mythid,
159 & xx_sbar_mean_dummy )
160 #endif
161 c-- Determine the month to be read.
162 levoff = mod(modelstartdate(1)/100,100)
163 levmon = (irec-1) + levoff
164 levmon = mod(levmon-1,12)+1
165
166 call mdsreadfield( ctdsclimfile, cost_iprec, cost_yftype,
167 & nr, sdat, levmon, mythid)
168
169 do bj = jtlo,jthi
170 do bi = itlo,ithi
171
172 c-- Loop over the model layers
173 fctile = 0. _d 0
174 do k = 1,nr
175
176 c-- Determine the mask or weights
177 do j = jmin,jmax
178 do i = imin,imax
179 cmask(i,j) = 1. _d 0
180 if (sdat(i,j,k,bi,bj) .eq. 0.) then
181 cmask(i,j) = 0. _d 0
182 endif
183 if (sdat(i,j,k,bi,bj) .lt. spval) then
184 cmask(i,j) = 0. _d 0
185 endif
186 enddo
187 enddo
188
189 c-- Compute model data misfit and cost function term for
190 c the salinity field.
191 do j = jmin,jmax
192 do i = imin,imax
193 if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
194 fctile = fctile +
195 & (wsalt2(i,j,k,bi,bj)*cosphi(i,j,bi,bj)*
196 & cmask(i,j)*
197 & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj))*
198 & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj)) )
199 endif
200 enddo
201 enddo
202
203 enddo
204 c-- End of loop over layers.
205
206 fcthread = fcthread + fctile
207 objf_ctdsclim(bi,bj) = objf_ctdsclim(bi,bj) + fctile
208
209 #ifdef ECCO_VERBOSE
210 c-- Print cost function for each tile in each thread.
211 write(msgbuf,'(a)') ' '
212 call print_message( msgbuf, standardmessageunit,
213 & SQUEEZE_RIGHT , mythid)
214 write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
215 & ' cost_Ctdsclim: irec,bi,bj = ',irec,bi,bj
216 call print_message( msgbuf, standardmessageunit,
217 & SQUEEZE_RIGHT , mythid)
218 write(msgbuf,'(a,d22.15)')
219 & ' cost function (salinity) = ',
220 & fctile
221 call print_message( msgbuf, standardmessageunit,
222 & SQUEEZE_RIGHT , mythid)
223 write(msgbuf,'(a)') ' '
224 call print_message( msgbuf, standardmessageunit,
225 & SQUEEZE_RIGHT , mythid)
226 #endif
227
228 enddo
229 enddo
230
231 #ifdef ECCO_VERBOSE
232 c-- Print cost function for all tiles.
233 _GLOBAL_SUM_RL( fcthread , myThid )
234 write(msgbuf,'(a)') ' '
235 call print_message( msgbuf, standardmessageunit,
236 & SQUEEZE_RIGHT , mythid)
237 write(msgbuf,'(a,i8.8)')
238 & ' cost_Ctdsclim: irec = ',irec
239 call print_message( msgbuf, standardmessageunit,
240 & SQUEEZE_RIGHT , mythid)
241 write(msgbuf,'(a,a,d22.15)')
242 & ' global cost function value',
243 & ' (salinity) = ',fcthread
244 call print_message( msgbuf, standardmessageunit,
245 & SQUEEZE_RIGHT , mythid)
246 write(msgbuf,'(a)') ' '
247 call print_message( msgbuf, standardmessageunit,
248 & SQUEEZE_RIGHT , mythid)
249 #endif
250
251 #ifdef GENERIC_BAR_MONTH
252 endif
253 #endif
254 enddo
255 c-- End of loop over records.
256
257 #else
258 c-- Do not enter the calculation of the salinity contribution to
259 c-- the final cost function.
260
261 _BEGIN_MASTER( mythid )
262 write(msgbuf,'(a)') ' '
263 call print_message( msgbuf, standardmessageunit,
264 & SQUEEZE_RIGHT , mythid)
265 write(msgbuf,'(a,a)')
266 & ' cost_Ctdsclim: no contribution of salinity field ',
267 & 'to cost function.'
268 call print_message( msgbuf, standardmessageunit,
269 & SQUEEZE_RIGHT , mythid)
270 write(msgbuf,'(a,a,i9.8)')
271 & ' cost_Ctdsclim: number of records that would have',
272 & ' been processed: ',nmonsrec
273 call print_message( msgbuf, standardmessageunit,
274 & SQUEEZE_RIGHT , mythid)
275 write(msgbuf,'(a)') ' '
276 call print_message( msgbuf, standardmessageunit,
277 & SQUEEZE_RIGHT , mythid)
278 _END_MASTER( mythid )
279 #endif
280
281 return
282 end
283

  ViewVC Help
Powered by ViewVC 1.1.22