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

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

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


Revision 1.41 - (hide annotations) (download)
Tue Apr 28 18:13:28 2009 UTC (15 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.40: +142 -142 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 jmc 1.41 C $Header: /u/gcmpack/MITgcm/pkg/ecco/ecco_cost_final.F,v 1.40 2009/04/08 11:03:03 dimitri Exp $
2 jmc 1.38 C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
6 heimbach 1.3
7 heimbach 1.1 subroutine ecco_cost_final( mythid )
8    
9     c ==================================================================
10 heimbach 1.3 c SUBROUTINE cost_final
11 heimbach 1.1 c ==================================================================
12     c
13     c o Sum of all cost function contributions.
14     c
15     c ==================================================================
16 heimbach 1.3 c SUBROUTINE cost_final
17 heimbach 1.1 c ==================================================================
18    
19     implicit none
20    
21     c == global variables ==
22    
23     #include "EEPARAMS.h"
24     #include "SIZE.h"
25 heimbach 1.2 #include "PARAMS.h"
26 heimbach 1.14 #ifdef ALLOW_MNC
27     #include "MNC_PARAMS.h"
28     #endif
29 heimbach 1.1
30 heimbach 1.3 #include "cost.h"
31 heimbach 1.1 #include "ecco_cost.h"
32     #include "ctrl.h"
33     #include "optim.h"
34 heimbach 1.21 #ifdef ALLOW_PROFILES
35     # include "profiles.h"
36     #else
37     integer NFILESPROFMAX
38     parameter (NFILESPROFMAX=1)
39 gforget 1.27 integer NVARMAX
40     parameter (NVARMAX=1)
41 heimbach 1.21 #endif
42 heimbach 1.1
43     c == routine arguments ==
44    
45     integer mythid
46    
47 dimitri 1.40 C === Functions ====
48     LOGICAL MASTER_CPU_THREAD
49     EXTERNAL MASTER_CPU_THREAD
50    
51 heimbach 1.1 c == local variables ==
52    
53     integer bi,bj
54     integer itlo,ithi
55     integer jtlo,jthi
56     integer ifc
57 heimbach 1.7 integer totnum
58 heimbach 1.20 integer num_file,num_var
59 heimbach 1.1
60 heimbach 1.16 _RL f_temp0, f_salt0, f_temp0smoo, f_salt0smoo
61 jmc 1.38 _RL f_temp, f_salt
62 heimbach 1.12 _RL f_uwind, f_vwind
63 heimbach 1.15 _RL f_atemp, f_aqh, f_precip
64     _RL f_swflux, f_swdown
65 heimbach 1.12 _RL f_uwindm, f_vwindm
66 heimbach 1.15 _RL f_atempm, f_aqhm, f_precipm
67     _RL f_swfluxm, f_swdownm
68     _RL f_uwindsmoo, f_vwindsmoo
69     _RL f_atempsmoo, f_aqhsmoo, f_precipsmoo
70     _RL f_swfluxsmoo, f_swdownsmoo
71 jmc 1.38 _RL f_tauu, f_tauv, f_hflux, f_sflux
72     _RL f_tauum, f_tauvm, f_hfluxm, f_sfluxm
73 heimbach 1.15 _RL f_tauusmoo, f_tauvsmoo, f_hfluxsmoo, f_sfluxsmoo
74 heimbach 1.19 _RL f_hfluxmm, f_sfluxmm, f_hfluxmm2, f_sfluxmm2
75 heimbach 1.36 _RL f_sst, f_tmi, f_sss, f_bp, f_atl, f_ctdt, f_ctds
76 heimbach 1.1 _RL f_drifter, f_xbt, f_tdrift, f_sdrift, f_wdrift
77 heimbach 1.23 _RL f_ssh , f_tp, f_ers, f_gfo
78     _RL f_argot, f_argos, f_ctdtclim, f_ctdsclim
79 heimbach 1.1 _RL f_scatx, f_scaty, f_scatxm, f_scatym
80     _RL f_obcsn, f_obcss, f_obcsw, f_obcse
81     _RL f_ageos, f_curmtr
82     _RL f_ini_fin
83 gforget 1.39 _RL f_kapgm, f_kapredi, f_diffkr
84 gforget 1.33 _RL f_eddytau, f_bottomdrag
85 gforget 1.27 _RL f_profiles(NFILESPROFMAX,NVARMAX)
86 gforget 1.34 _RL f_gencost(NGENCOST)
87 heimbach 1.35 _RL f_transp
88 heimbach 1.1
89 jmc 1.38 _RL no_temp0, no_salt0, no_temp, no_salt
90 heimbach 1.12 _RL no_uwind, no_vwind
91     _RL no_atemp, no_aqh, no_precip, no_swflux, no_swdown
92     _RL no_uwindm, no_vwindm
93     _RL no_atempm, no_aqhm, no_precipm, no_swfluxm, no_swdownm
94 jmc 1.38 _RL no_tauu, no_tauv, no_hflux, no_sflux
95     _RL no_tauum, no_tauvm, no_hfluxm, no_sfluxm
96     _RL no_hfluxmm, no_sfluxmm
97 heimbach 1.36 _RL no_sst, no_tmi, no_sss, no_bp, no_atl, no_ctdt, no_ctds
98 heimbach 1.7 _RL no_drifter, no_xbt, no_tdrift, no_sdrift, no_wdrift
99 heimbach 1.23 _RL no_ssh, no_tp, no_ers, no_gfo
100     _RL no_argot, no_argos, no_ctdtclim, no_ctdsclim
101 heimbach 1.7 _RL no_scatx, no_scaty, no_scatxm, no_scatym
102     _RL no_obcsn, no_obcss, no_obcsw, no_obcse
103     _RL no_ageos, no_curmtr
104     _RL no_ini_fin
105 gforget 1.39 _RL no_kapgm, no_kapredi, no_diffkr
106 gforget 1.33 _RL no_eddytau, no_bottomdrag
107 heimbach 1.7 _RL no_hmean
108 gforget 1.27 _RL no_profiles(NFILESPROFMAX,NVARMAX)
109 gforget 1.34 _RL no_gencost(NGENCOST)
110 heimbach 1.35 _RL no_transp
111 heimbach 1.7
112 heimbach 1.1 character*20 cfname
113     #ifdef ECCO_VERBOSE
114     character*(MAX_LEN_MBUF) msgbuf
115     #endif
116    
117 heimbach 1.20 INTEGER IL
118     C Functions
119     INTEGER ILNBLNK
120    
121 heimbach 1.1 c == end of interface ==
122    
123     jtlo = mybylo(mythid)
124     jthi = mybyhi(mythid)
125     itlo = mybxlo(mythid)
126     ithi = mybxhi(mythid)
127    
128     ifc = 30
129 jmc 1.38
130 heimbach 1.1 f_temp = 0. _d 0
131     f_salt = 0. _d 0
132     f_temp0 = 0. _d 0
133 jmc 1.38 f_salt0 = 0. _d 0
134 heimbach 1.16 f_temp0smoo = 0. _d 0
135 jmc 1.38 f_salt0smoo = 0. _d 0
136     f_tauu = 0. _d 0
137     f_tauum = 0. _d 0
138     f_tauusmoo = 0. _d 0
139     f_tauv = 0. _d 0
140     f_tauvm = 0. _d 0
141     f_tauvsmoo = 0. _d 0
142     f_hflux = 0. _d 0
143 heimbach 1.15 f_hfluxm = 0. _d 0
144 jmc 1.38 f_hfluxsmoo = 0. _d 0
145     f_hfluxmm = 0. _d 0
146     f_hfluxmm2 = 0. _d 0
147 heimbach 1.1 f_sflux = 0. _d 0
148 jmc 1.38 f_sfluxsmoo = 0. _d 0
149 heimbach 1.1 f_sfluxm = 0. _d 0
150     f_sfluxmm = 0. _d 0
151 heimbach 1.19 f_sfluxmm2 = 0. _d 0
152 heimbach 1.7 f_uwind = 0. _d 0
153     f_vwind = 0. _d 0
154     f_atemp = 0. _d 0
155     f_aqh = 0. _d 0
156 heimbach 1.9 f_precip = 0. _d 0
157 heimbach 1.10 f_swflux = 0. _d 0
158 heimbach 1.12 f_swdown = 0. _d 0
159 heimbach 1.11 f_uwindm = 0. _d 0
160     f_vwindm = 0. _d 0
161     f_atempm = 0. _d 0
162     f_aqhm = 0. _d 0
163     f_precipm = 0. _d 0
164     f_swfluxm = 0. _d 0
165 heimbach 1.12 f_swdownm = 0. _d 0
166 heimbach 1.15 f_uwindsmoo = 0. _d 0
167     f_vwindsmoo = 0. _d 0
168     f_atempsmoo = 0. _d 0
169     f_aqhsmoo = 0. _d 0
170     f_precipsmoo = 0. _d 0
171     f_swfluxsmoo = 0. _d 0
172     f_swdownsmoo = 0. _d 0
173 heimbach 1.1 f_ssh = 0. _d 0
174 heimbach 1.23 f_tp = 0. _d 0
175     f_ers = 0. _d 0
176     f_gfo = 0. _d 0
177 heimbach 1.3 f_sst = 0. _d 0
178 heimbach 1.1 f_tmi = 0. _d 0
179     f_sss = 0. _d 0
180 heimbach 1.36 f_bp = 0. _d 0
181 heimbach 1.1 f_atl = 0. _d 0
182 jmc 1.38 f_ctdt = 0. _d 0
183 heimbach 1.3 f_ctds = 0. _d 0
184 jmc 1.38 f_ctdtclim = 0. _d 0
185 heimbach 1.7 f_ctdsclim = 0. _d 0
186 heimbach 1.3 f_xbt = 0. _d 0
187     f_argot = 0. _d 0
188     f_argos = 0. _d 0
189 jmc 1.38 f_drifter = 0. _d 0
190 heimbach 1.3 f_sdrift = 0. _d 0
191     f_tdrift = 0. _d 0
192     f_wdrift = 0. _d 0
193     f_scatx = 0. _d 0
194     f_scaty = 0. _d 0
195     f_scatxm = 0. _d 0
196     f_scatym = 0. _d 0
197 heimbach 1.1 f_obcsn = 0. _d 0
198     f_obcss = 0. _d 0
199     f_obcsw = 0. _d 0
200     f_obcse = 0. _d 0
201     f_curmtr = 0. _d 0
202     f_ageos = 0. _d 0
203     f_ini_fin = 0. _d 0
204     f_kapgm = 0. _d 0
205 gforget 1.39 f_kapredi = 0. _d 0
206 heimbach 1.1 f_diffkr = 0. _d 0
207 heimbach 1.6 f_eddytau = 0. _d 0
208 gforget 1.33 f_bottomdrag = 0. _d 0
209 heimbach 1.35 f_transp = 0. _d 0
210 heimbach 1.21 #ifdef ALLOW_PROFILES
211 heimbach 1.20 do num_file=1,NFILESPROFMAX
212 gforget 1.27 do num_var=1,NVARMAX
213 heimbach 1.20 f_profiles(num_file,num_var)= 0. _d 0
214     enddo
215     enddo
216 heimbach 1.21 #endif
217 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
218     do num_var=1,NGENCOST
219     f_gencost(num_var)= 0. _d 0
220     enddo
221     #endif
222 heimbach 1.1
223 heimbach 1.7 no_temp = 0. _d 0
224     no_salt = 0. _d 0
225     no_temp0 = 0. _d 0
226 jmc 1.38 no_salt0 = 0. _d 0
227     no_tauu = 0. _d 0
228     no_tauum = 0. _d 0
229     no_tauv = 0. _d 0
230     no_tauvm = 0. _d 0
231     no_hflux = 0. _d 0
232     no_hfluxm = 0. _d 0
233     no_hfluxmm = 0. _d 0
234 heimbach 1.7 no_sflux = 0. _d 0
235     no_sfluxm = 0. _d 0
236     no_sfluxmm = 0. _d 0
237     no_uwind = 0. _d 0
238     no_vwind = 0. _d 0
239     no_atemp = 0. _d 0
240     no_aqh = 0. _d 0
241 heimbach 1.9 no_precip = 0. _d 0
242 heimbach 1.10 no_swflux = 0. _d 0
243 heimbach 1.12 no_swdown = 0. _d 0
244 heimbach 1.11 no_uwindm = 0. _d 0
245     no_vwindm = 0. _d 0
246     no_atempm = 0. _d 0
247     no_aqhm = 0. _d 0
248     no_precipm = 0. _d 0
249     no_swfluxm = 0. _d 0
250 heimbach 1.12 no_swdownm = 0. _d 0
251 heimbach 1.7 no_ssh = 0. _d 0
252 heimbach 1.23 no_tp = 0. _d 0
253     no_ers = 0. _d 0
254     no_gfo = 0. _d 0
255 heimbach 1.7 no_sst = 0. _d 0
256     no_tmi = 0. _d 0
257     no_sss = 0. _d 0
258 heimbach 1.36 no_bp = 0. _d 0
259 heimbach 1.7 no_atl = 0. _d 0
260 jmc 1.38 no_ctdt = 0. _d 0
261 heimbach 1.7 no_ctds = 0. _d 0
262 jmc 1.38 no_ctdtclim = 0. _d 0
263 heimbach 1.7 no_ctdsclim = 0. _d 0
264     no_xbt = 0. _d 0
265     no_argot = 0. _d 0
266     no_argos = 0. _d 0
267 jmc 1.38 no_drifter = 0. _d 0
268 heimbach 1.7 no_sdrift = 0. _d 0
269     no_tdrift = 0. _d 0
270     no_wdrift = 0. _d 0
271     no_scatx = 0. _d 0
272     no_scaty = 0. _d 0
273     no_scatxm = 0. _d 0
274     no_scatym = 0. _d 0
275     no_obcsn = 0. _d 0
276     no_obcss = 0. _d 0
277     no_obcsw = 0. _d 0
278     no_obcse = 0. _d 0
279     no_curmtr = 0. _d 0
280     no_ageos = 0. _d 0
281     no_ini_fin = 0. _d 0
282     no_kapgm = 0. _d 0
283 gforget 1.39 no_kapredi = 0. _d 0
284 heimbach 1.7 no_diffkr = 0. _d 0
285     no_eddytau = 0. _d 0
286 gforget 1.33 no_bottomdrag = 0. _d 0
287 heimbach 1.35 no_transp = 0. _d 0
288 heimbach 1.21 #ifdef ALLOW_PROFILES
289 heimbach 1.20 do num_file=1,NFILESPROFMAX
290 gforget 1.27 do num_var=1,NVARMAX
291 heimbach 1.20 no_profiles(num_file,num_var)= 0. _d 0
292     enddo
293     enddo
294 heimbach 1.21 #endif
295 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
296     do num_var=1,NGENCOST
297     no_gencost(num_var)= 0. _d 0
298     enddo
299     #endif
300 heimbach 1.7
301 heimbach 1.1 c-- Sum up all contributions.
302     do bj = jtlo,jthi
303     do bi = itlo,ithi
304 jmc 1.38
305 heimbach 1.1 fc = fc
306 heimbach 1.15 & + mult_temp * objf_temp(bi,bj)
307     & + mult_salt * objf_salt(bi,bj)
308 heimbach 1.16 & + mult_temp0 * ( objf_temp0(bi,bj)
309     & +mult_smooth_ic*objf_temp0smoo(bi,bj) )
310     & + mult_salt0 * ( objf_salt0(bi,bj)
311     & +mult_smooth_ic*objf_salt0smoo(bi,bj) )
312 jmc 1.38 & + mult_sst * objf_sst(bi,bj)
313     & + mult_tmi * objf_tmi(bi,bj)
314     & + mult_sss * objf_sss(bi,bj)
315     & + mult_bp * objf_bp(bi,bj)
316 heimbach 1.15 & + mult_tauu * ( objf_tauu(bi,bj)+objf_tauum(bi,bj)
317 heimbach 1.16 & +mult_smooth_bc*objf_tauusmoo(bi,bj) )
318 heimbach 1.15 & + mult_tauv * ( objf_tauv(bi,bj)+objf_tauvm(bi,bj)
319 heimbach 1.16 & +mult_smooth_bc*objf_tauvsmoo(bi,bj) )
320 heimbach 1.37 & + mult_hflux * ( objf_hflux(bi,bj)
321 heimbach 1.16 & +mult_smooth_bc*objf_hfluxsmoo(bi,bj) )
322 heimbach 1.37 & + mult_sflux * ( objf_sflux(bi,bj)
323 heimbach 1.16 & +mult_smooth_bc*objf_sfluxsmoo(bi,bj) )
324 jmc 1.38 & + mult_h * ( mult_tp * objf_tp(bi,bj)
325 heimbach 1.23 & + mult_ers * objf_ers(bi,bj)
326     & + mult_gfo * objf_gfo(bi,bj) )
327 heimbach 1.15 & + mult_atl * objf_atl(bi,bj)
328     & + mult_ctdt * objf_ctdt(bi,bj)
329     & + mult_ctds * objf_ctds(bi,bj)
330     & + mult_ctdtclim* objf_ctdtclim(bi,bj)
331     & + mult_ctdsclim* objf_ctdsclim(bi,bj)
332     & + mult_xbt * objf_xbt(bi,bj)
333     & + mult_argot * objf_argot(bi,bj)
334     & + mult_argos * objf_argos(bi,bj)
335     & + mult_drift * objf_drift(bi,bj)
336     & + mult_sdrift * objf_sdrift(bi,bj)
337     & + mult_tdrift * objf_tdrift(bi,bj)
338     & + mult_wdrift * objf_wdrift(bi,bj)
339     & + mult_scatx * objf_scatx(bi,bj)
340     & + mult_scaty * objf_scaty(bi,bj)
341     & + mult_scatx * objf_scatxm(bi,bj)
342     & + mult_scaty * objf_scatym(bi,bj)
343     & + mult_uwind * ( objf_uwind(bi,bj)+objf_uwindm(bi,bj)
344 heimbach 1.16 & +mult_smooth_bc*objf_uwindsmoo(bi,bj) )
345 heimbach 1.15 & + mult_vwind * ( objf_vwind(bi,bj)+objf_vwindm(bi,bj)
346 heimbach 1.16 & +mult_smooth_bc*objf_vwindsmoo(bi,bj) )
347 heimbach 1.15 & + mult_atemp * ( objf_atemp(bi,bj)+objf_atempm(bi,bj)
348 heimbach 1.16 & +mult_smooth_bc*objf_atempsmoo(bi,bj) )
349 heimbach 1.15 & + mult_aqh * ( objf_aqh(bi,bj)+objf_aqhm(bi,bj)
350 heimbach 1.16 & +mult_smooth_bc*objf_aqhsmoo(bi,bj) )
351 heimbach 1.15 & + mult_precip * ( objf_precip(bi,bj)+objf_precipm(bi,bj)
352 heimbach 1.16 & +mult_smooth_bc*objf_precipsmoo(bi,bj) )
353 heimbach 1.15 & + mult_swflux * ( objf_swflux(bi,bj)+objf_swfluxm(bi,bj)
354 heimbach 1.16 & +mult_smooth_bc*objf_swfluxsmoo(bi,bj) )
355 heimbach 1.15 & + mult_swdown * ( objf_swdown(bi,bj)+objf_swdownm(bi,bj)
356 heimbach 1.16 & +mult_smooth_bc*objf_swdownsmoo(bi,bj) )
357 jmc 1.38 & + mult_obcsn * objf_obcsn(bi,bj)
358     & + mult_obcss * objf_obcss(bi,bj)
359     & + mult_obcsw * objf_obcsw(bi,bj)
360     & + mult_obcse * objf_obcse(bi,bj)
361 heimbach 1.15 & + mult_curmtr * objf_curmtr(bi,bj)
362     & + mult_ageos * objf_ageos(bi,bj)
363     & + mult_kapgm * objf_kapgm(bi,bj)
364 gforget 1.39 & + mult_kapredi * objf_kapredi(bi,bj)
365 heimbach 1.15 & + mult_diffkr * objf_diffkr(bi,bj)
366     & + mult_ini_fin *(objf_theta_ini_fin(bi,bj) +
367     & objf_salt_ini_fin(bi,bj))
368 gforget 1.33 & + mult_edtau * objf_eddytau(bi,bj)
369     & + mult_bottomdrag * objf_bottomdrag(bi,bj)
370 heimbach 1.21 #ifdef ALLOW_PROFILES
371 heimbach 1.20 do num_file=1,NFILESPROFMAX
372 gforget 1.27 do num_var=1,NVARMAX
373 heimbach 1.20 fc = fc
374     & + mult_profiles(num_file,num_var)
375     & *objf_profiles(num_file,num_var,bi,bj)
376     enddo
377     enddo
378 heimbach 1.21 #endif
379 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
380     do num_var=1,NGENCOST
381     fc = fc
382     & + mult_gencost(num_var)
383     & *objf_gencost(num_var,bi,bj)
384     enddo
385     #endif
386 heimbach 1.1 f_temp = f_temp + objf_temp(bi,bj)
387     f_salt = f_salt + objf_salt(bi,bj)
388     f_temp0 = f_temp0 + objf_temp0(bi,bj)
389 jmc 1.38 f_salt0 = f_salt0 + objf_salt0(bi,bj)
390 heimbach 1.16 f_temp0smoo = f_temp0smoo + objf_temp0smoo(bi,bj)
391 jmc 1.38 f_salt0smoo = f_salt0smoo + objf_salt0smoo(bi,bj)
392 heimbach 1.1 f_tauu = f_tauu + objf_tauu(bi,bj)
393     f_tauum = f_tauum + objf_tauum(bi,bj)
394 heimbach 1.15 f_tauusmoo = f_tauusmoo + objf_tauusmoo(bi,bj)
395 heimbach 1.1 f_tauv = f_tauv + objf_tauv(bi,bj)
396     f_tauvm = f_tauvm + objf_tauvm(bi,bj)
397 heimbach 1.15 f_tauvsmoo = f_tauvsmoo + objf_tauvsmoo(bi,bj)
398 jmc 1.38 f_hflux = f_hflux + objf_hflux(bi,bj)
399     f_hfluxsmoo = f_hfluxsmoo + objf_hfluxsmoo(bi,bj)
400     f_sflux = f_sflux + objf_sflux(bi,bj)
401     f_sfluxsmoo = f_sfluxsmoo + objf_sfluxsmoo(bi,bj)
402 heimbach 1.15 f_uwind = f_uwind + objf_uwind(bi,bj)
403     f_vwind = f_vwind + objf_vwind(bi,bj)
404     f_atemp = f_atemp + objf_atemp(bi,bj)
405     f_aqh = f_aqh + objf_aqh(bi,bj)
406     f_precip = f_precip + objf_precip(bi,bj)
407     f_swflux = f_swflux + objf_swflux(bi,bj)
408     f_swdown = f_swdown + objf_swdown(bi,bj)
409     f_uwindm = f_uwindm + objf_uwindm(bi,bj)
410     f_vwindm = f_vwindm + objf_vwindm(bi,bj)
411     f_atempm = f_atempm + objf_atempm(bi,bj)
412     f_aqhm = f_aqhm + objf_aqhm(bi,bj)
413     f_precipm = f_precipm + objf_precipm(bi,bj)
414     f_swfluxm = f_swfluxm + objf_swfluxm(bi,bj)
415     f_swdownm = f_swdownm + objf_swdownm(bi,bj)
416     f_uwindsmoo = f_uwindsmoo + objf_uwindsmoo(bi,bj)
417     f_vwindsmoo = f_vwindsmoo + objf_vwindsmoo(bi,bj)
418     f_atempsmoo = f_atempsmoo + objf_atempsmoo(bi,bj)
419     f_aqhsmoo = f_aqhsmoo + objf_aqhsmoo(bi,bj)
420     f_precipsmoo = f_precipsmoo + objf_precipsmoo(bi,bj)
421     f_swfluxsmoo = f_swfluxsmoo + objf_swfluxsmoo(bi,bj)
422     f_swdownsmoo = f_swdownsmoo + objf_swdownsmoo(bi,bj)
423 jmc 1.38 f_ssh = f_ssh + objf_h(bi,bj)
424     f_tp = f_tp + objf_tp(bi,bj)
425     f_ers = f_ers + objf_ers(bi,bj)
426     f_gfo = f_gfo + objf_gfo(bi,bj)
427     f_sst = f_sst + objf_sst(bi,bj)
428     f_tmi = f_tmi + objf_tmi(bi,bj)
429 heimbach 1.1 f_sss = f_sss + objf_sss(bi,bj)
430 heimbach 1.36 f_bp = f_bp + objf_bp(bi,bj)
431 heimbach 1.3 f_atl = f_atl + objf_atl(bi,bj)
432 heimbach 1.1 f_ctdt = f_ctdt + objf_ctdt(bi,bj)
433 jmc 1.38 f_ctds = f_ctds + objf_ctds(bi,bj)
434 heimbach 1.1 f_ctdtclim = f_ctdtclim + objf_ctdtclim(bi,bj)
435 jmc 1.38 f_ctdsclim = f_ctdsclim + objf_ctdsclim(bi,bj)
436 heimbach 1.1 f_xbt = f_xbt + objf_xbt(bi,bj)
437     f_argot = f_argot + objf_argot(bi,bj)
438     f_argos = f_argos + objf_argos(bi,bj)
439     f_drifter = f_drifter + objf_drift(bi,bj)
440     f_sdrift = f_sdrift + objf_sdrift(bi,bj)
441     f_tdrift = f_tdrift + objf_tdrift(bi,bj)
442     f_wdrift = f_wdrift + objf_wdrift(bi,bj)
443     f_scatx = f_scatx + objf_scatx(bi,bj)
444     f_scaty = f_scaty + objf_scaty(bi,bj)
445     f_scatxm = f_scatxm + objf_scatxm(bi,bj)
446     f_scatym = f_scatym + objf_scatym(bi,bj)
447     f_curmtr = f_curmtr + objf_curmtr(bi,bj)
448     f_ageos = f_ageos + objf_ageos(bi,bj)
449     f_kapgm = f_kapgm + objf_kapgm(bi,bj)
450 gforget 1.39 f_kapredi = f_kapredi + objf_kapredi(bi,bj)
451 heimbach 1.1 f_diffkr = f_diffkr + objf_diffkr(bi,bj)
452 heimbach 1.3 f_ini_fin = f_ini_fin +
453 heimbach 1.1 & objf_theta_ini_fin(bi,bj) + objf_salt_ini_fin(bi,bj)
454 jmc 1.38 f_eddytau = f_eddytau + objf_eddytau(bi,bj)
455 gforget 1.33 f_bottomdrag = f_bottomdrag + objf_bottomdrag(bi,bj)
456 heimbach 1.21 #ifdef ALLOW_PROFILES
457 heimbach 1.20 do num_file=1,NFILESPROFMAX
458 gforget 1.27 do num_var=1,NVARMAX
459 heimbach 1.20 f_profiles(num_file,num_var)=f_profiles(num_file,num_var)
460     & +objf_profiles(num_file,num_var,bi,bj)
461     enddo
462     enddo
463 heimbach 1.21 #endif
464 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
465     do num_var=1,NGENCOST
466     f_gencost(num_var)=f_gencost(num_var)
467     & +objf_gencost(num_var,bi,bj)
468     enddo
469     #endif
470 heimbach 1.7 no_temp = no_temp + num_temp(bi,bj)
471     no_salt = no_salt + num_salt(bi,bj)
472     no_temp0 = no_temp0 + num_temp0(bi,bj)
473 jmc 1.38 no_salt0 = no_salt0 + num_salt0(bi,bj)
474 heimbach 1.7 no_tauu = no_tauu + num_tauu(bi,bj)
475     no_tauum = no_tauum + num_tauum(bi,bj)
476     no_tauv = no_tauv + num_tauv(bi,bj)
477     no_tauvm = no_tauvm + num_tauvm(bi,bj)
478 jmc 1.38 no_hflux= no_hflux + num_hflux(bi,bj)
479     no_hfluxmm = no_hfluxmm + num_hfluxmm(bi,bj)
480     no_sflux= no_sflux + num_sflux(bi,bj)
481     no_sfluxmm = no_sfluxmm + num_sfluxmm(bi,bj)
482 heimbach 1.9 no_atemp = no_atemp + num_atemp(bi,bj)
483     no_aqh = no_aqh + num_aqh(bi,bj)
484     no_precip = no_precip + num_precip(bi,bj)
485 heimbach 1.10 no_swflux = no_swflux + num_swflux(bi,bj)
486 heimbach 1.12 no_swdown = no_swdown + num_swdown(bi,bj)
487 heimbach 1.9 no_uwind = no_uwind + num_uwind(bi,bj)
488     no_vwind = no_vwind + num_vwind(bi,bj)
489 heimbach 1.11 no_atempm = no_atempm + num_atempm(bi,bj)
490     no_aqhm = no_aqhm + num_aqhm(bi,bj)
491     no_precipm = no_precipm + num_precipm(bi,bj)
492     no_swfluxm = no_swfluxm + num_swfluxm(bi,bj)
493 heimbach 1.12 no_swdownm = no_swdownm + num_swdownm(bi,bj)
494 heimbach 1.11 no_uwindm = no_uwindm + num_uwindm(bi,bj)
495     no_vwindm = no_vwindm + num_vwindm(bi,bj)
496 jmc 1.38 no_ssh = no_ssh + num_h(bi,bj)
497     no_tp = no_tp + num_tp(bi,bj)
498     no_ers = no_ers + num_ers(bi,bj)
499     no_gfo = no_gfo + num_gfo(bi,bj)
500     no_sst = no_sst + num_sst(bi,bj)
501     no_tmi = no_tmi + num_tmi(bi,bj)
502 heimbach 1.7 no_sss = no_sss + num_sss(bi,bj)
503 heimbach 1.36 no_bp = no_bp + num_bp(bi,bj)
504 heimbach 1.7 no_ctdt = no_ctdt + num_ctdt(bi,bj)
505 jmc 1.38 no_ctds = no_ctds + num_ctds(bi,bj)
506 heimbach 1.7 no_ctdtclim = no_ctdtclim + num_ctdtclim(bi,bj)
507 jmc 1.38 no_ctdsclim = no_ctdsclim + num_ctdsclim(bi,bj)
508 heimbach 1.7 no_xbt = no_xbt + num_xbt(bi,bj)
509     no_argot = no_argot + num_argot(bi,bj)
510     no_argos = no_argos + num_argos(bi,bj)
511     no_drifter = no_drifter + num_drift(bi,bj)
512     no_sdrift = no_sdrift + num_sdrift(bi,bj)
513     no_tdrift = no_tdrift + num_tdrift(bi,bj)
514     no_wdrift = no_wdrift + num_wdrift(bi,bj)
515     no_scatx = no_scatx + num_scatx(bi,bj)
516     no_scaty = no_scaty + num_scaty(bi,bj)
517     no_scatxm = no_scatxm + num_scatxm(bi,bj)
518     no_scatym = no_scatym + num_scatym(bi,bj)
519     no_curmtr = no_curmtr + num_curmtr(bi,bj)
520     no_ageos = no_ageos + num_ageos(bi,bj)
521     no_kapgm = no_kapgm + num_kapgm(bi,bj)
522 gforget 1.39 no_kapredi = no_kapredi + num_kapredi(bi,bj)
523 heimbach 1.7 no_diffkr = no_diffkr + num_diffkr(bi,bj)
524     no_ini_fin = no_ini_fin +
525     & num_theta_ini_fin(bi,bj) + num_salt_ini_fin(bi,bj)
526 jmc 1.38 no_eddytau = no_eddytau + num_eddytau(bi,bj)
527 gforget 1.33 no_bottomdrag = no_bottomdrag + num_bottomdrag(bi,bj)
528 heimbach 1.21 #ifdef ALLOW_PROFILES
529 heimbach 1.20 do num_file=1,NFILESPROFMAX
530 gforget 1.27 do num_var=1,NVARMAX
531 heimbach 1.20 no_profiles(num_file,num_var)=no_profiles(num_file,num_var)
532     & +num_profiles(num_file,num_var,bi,bj)
533     enddo
534     enddo
535 heimbach 1.21 #endif
536 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
537     do num_var=1,NGENCOST
538     no_gencost(num_var)=no_gencost(num_var)
539     & +num_gencost(num_var,bi,bj)
540     enddo
541 jmc 1.38 #endif
542 heimbach 1.7
543 heimbach 1.1 enddo
544     enddo
545    
546    
547     c-- Do global summation.
548 jmc 1.41 _GLOBAL_SUM_RL( fc , myThid )
549 heimbach 1.1
550     c-- Do global summation for each part of the cost function
551 jmc 1.38
552 jmc 1.41 _GLOBAL_SUM_RL( f_temp , myThid )
553     _GLOBAL_SUM_RL( f_salt , myThid )
554     _GLOBAL_SUM_RL( f_temp0, myThid )
555     _GLOBAL_SUM_RL( f_salt0, myThid )
556     _GLOBAL_SUM_RL( f_temp0smoo, myThid )
557     _GLOBAL_SUM_RL( f_salt0smoo, myThid )
558     _GLOBAL_SUM_RL( f_tauu , myThid )
559     _GLOBAL_SUM_RL( f_tauum , myThid )
560     _GLOBAL_SUM_RL( f_tauusmoo , myThid )
561     _GLOBAL_SUM_RL( f_tauv , myThid )
562     _GLOBAL_SUM_RL( f_tauvm , myThid )
563     _GLOBAL_SUM_RL( f_tauvsmoo , myThid )
564     _GLOBAL_SUM_RL( f_hflux , myThid )
565     _GLOBAL_SUM_RL( f_hfluxmm , myThid )
566     _GLOBAL_SUM_RL( f_hfluxsmoo , myThid )
567     _GLOBAL_SUM_RL( f_sflux , myThid )
568     _GLOBAL_SUM_RL( f_sfluxsmoo , myThid )
569     _GLOBAL_SUM_RL( f_uwind , myThid )
570     _GLOBAL_SUM_RL( f_vwind , myThid )
571     _GLOBAL_SUM_RL( f_atemp , myThid )
572     _GLOBAL_SUM_RL( f_aqh , myThid )
573     _GLOBAL_SUM_RL( f_precip , myThid )
574     _GLOBAL_SUM_RL( f_swflux , myThid )
575     _GLOBAL_SUM_RL( f_swdown , myThid )
576     _GLOBAL_SUM_RL( f_uwindm , myThid )
577     _GLOBAL_SUM_RL( f_vwindm , myThid )
578     _GLOBAL_SUM_RL( f_atempm , myThid )
579     _GLOBAL_SUM_RL( f_aqhm , myThid )
580     _GLOBAL_SUM_RL( f_precipm , myThid )
581     _GLOBAL_SUM_RL( f_swfluxm , myThid )
582     _GLOBAL_SUM_RL( f_swdownm , myThid )
583     _GLOBAL_SUM_RL( f_uwindsmoo , myThid )
584     _GLOBAL_SUM_RL( f_vwindsmoo , myThid )
585     _GLOBAL_SUM_RL( f_atempsmoo , myThid )
586     _GLOBAL_SUM_RL( f_aqhsmoo , myThid )
587     _GLOBAL_SUM_RL( f_precipsmoo , myThid )
588     _GLOBAL_SUM_RL( f_swfluxsmoo , myThid )
589     _GLOBAL_SUM_RL( f_swdownsmoo , myThid )
590     _GLOBAL_SUM_RL( f_ssh , myThid )
591     _GLOBAL_SUM_RL( f_tp , myThid )
592     _GLOBAL_SUM_RL( f_ers , myThid )
593     _GLOBAL_SUM_RL( f_gfo , myThid )
594     _GLOBAL_SUM_RL( f_sst , myThid )
595     _GLOBAL_SUM_RL( f_tmi , myThid )
596     _GLOBAL_SUM_RL( f_sss , myThid )
597     _GLOBAL_SUM_RL( f_bp , myThid )
598     _GLOBAL_SUM_RL( f_atl , myThid )
599     _GLOBAL_SUM_RL( f_ctdt , myThid )
600     _GLOBAL_SUM_RL( f_ctds , myThid )
601     _GLOBAL_SUM_RL( f_ctdtclim , myThid )
602     _GLOBAL_SUM_RL( f_ctdsclim , myThid )
603     _GLOBAL_SUM_RL( f_xbt , myThid )
604     _GLOBAL_SUM_RL( f_argot , myThid )
605     _GLOBAL_SUM_RL( f_argos , myThid )
606     _GLOBAL_SUM_RL( f_drifter , myThid )
607     _GLOBAL_SUM_RL( f_sdrift , myThid )
608     _GLOBAL_SUM_RL( f_tdrift , myThid )
609     _GLOBAL_SUM_RL( f_wdrift , myThid )
610     _GLOBAL_SUM_RL( f_scatx , myThid )
611     _GLOBAL_SUM_RL( f_scaty , myThid )
612     _GLOBAL_SUM_RL( f_scatxm , myThid )
613     _GLOBAL_SUM_RL( f_scatym , myThid )
614     _GLOBAL_SUM_RL( f_obcsn , myThid )
615     _GLOBAL_SUM_RL( f_obcss , myThid )
616     _GLOBAL_SUM_RL( f_obcsw , myThid )
617     _GLOBAL_SUM_RL( f_obcse , myThid )
618     _GLOBAL_SUM_RL( f_curmtr , myThid )
619     _GLOBAL_SUM_RL( f_ageos , myThid )
620     _GLOBAL_SUM_RL( f_kapgm , myThid )
621     _GLOBAL_SUM_RL( f_kapredi, myThid )
622     _GLOBAL_SUM_RL( f_diffkr , myThid )
623     _GLOBAL_SUM_RL( f_ini_fin , myThid )
624     _GLOBAL_SUM_RL( f_eddytau , myThid )
625     _GLOBAL_SUM_RL( f_bottomdrag , myThid )
626 heimbach 1.21 #ifdef ALLOW_PROFILES
627 heimbach 1.20 do num_file=1,NFILESPROFMAX
628 gforget 1.27 do num_var=1,NVARMAX
629 jmc 1.41 _GLOBAL_SUM_RL(f_profiles(num_file,num_var), myThid )
630 heimbach 1.20 enddo
631     enddo
632 heimbach 1.21 #endif
633 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
634     do num_var=1,NGENCOST
635 jmc 1.41 _GLOBAL_SUM_RL(f_gencost(num_var), myThid )
636 gforget 1.34 enddo
637 jmc 1.38 #endif
638 jmc 1.41 _GLOBAL_SUM_RL( no_temp , myThid )
639     _GLOBAL_SUM_RL( no_salt , myThid )
640     _GLOBAL_SUM_RL( no_temp0, myThid )
641     _GLOBAL_SUM_RL( no_salt0, myThid )
642     _GLOBAL_SUM_RL( no_tauu , myThid )
643     _GLOBAL_SUM_RL( no_tauum , myThid )
644     _GLOBAL_SUM_RL( no_tauv , myThid )
645     _GLOBAL_SUM_RL( no_tauvm , myThid )
646     _GLOBAL_SUM_RL( no_hflux , myThid )
647     _GLOBAL_SUM_RL( no_hfluxmm , myThid )
648     _GLOBAL_SUM_RL( no_sflux , myThid )
649     _GLOBAL_SUM_RL( no_sfluxmm , myThid )
650     _GLOBAL_SUM_RL( no_uwind , myThid )
651     _GLOBAL_SUM_RL( no_vwind , myThid )
652     _GLOBAL_SUM_RL( no_atemp , myThid )
653     _GLOBAL_SUM_RL( no_aqh , myThid )
654     _GLOBAL_SUM_RL( no_precip , myThid )
655     _GLOBAL_SUM_RL( no_swflux , myThid )
656     _GLOBAL_SUM_RL( no_swdown , myThid )
657     _GLOBAL_SUM_RL( no_uwindm , myThid )
658     _GLOBAL_SUM_RL( no_vwindm , myThid )
659     _GLOBAL_SUM_RL( no_atempm , myThid )
660     _GLOBAL_SUM_RL( no_aqhm , myThid )
661     _GLOBAL_SUM_RL( no_precipm , myThid )
662     _GLOBAL_SUM_RL( no_swfluxm , myThid )
663     _GLOBAL_SUM_RL( no_swdownm , myThid )
664     _GLOBAL_SUM_RL( no_ssh , myThid )
665     _GLOBAL_SUM_RL( no_tp , myThid )
666     _GLOBAL_SUM_RL( no_ers , myThid )
667     _GLOBAL_SUM_RL( no_gfo , myThid )
668     _GLOBAL_SUM_RL( no_sst , myThid )
669     _GLOBAL_SUM_RL( no_tmi , myThid )
670     _GLOBAL_SUM_RL( no_sss , myThid )
671     _GLOBAL_SUM_RL( no_bp , myThid )
672     _GLOBAL_SUM_RL( no_atl , myThid )
673     _GLOBAL_SUM_RL( no_ctdt , myThid )
674     _GLOBAL_SUM_RL( no_ctds , myThid )
675     _GLOBAL_SUM_RL( no_ctdtclim , myThid )
676     _GLOBAL_SUM_RL( no_ctdsclim , myThid )
677     _GLOBAL_SUM_RL( no_xbt , myThid )
678     _GLOBAL_SUM_RL( no_argot , myThid )
679     _GLOBAL_SUM_RL( no_argos , myThid )
680     _GLOBAL_SUM_RL( no_drifter , myThid )
681     _GLOBAL_SUM_RL( no_sdrift , myThid )
682     _GLOBAL_SUM_RL( no_tdrift , myThid )
683     _GLOBAL_SUM_RL( no_wdrift , myThid )
684     _GLOBAL_SUM_RL( no_scatx , myThid )
685     _GLOBAL_SUM_RL( no_scaty , myThid )
686     _GLOBAL_SUM_RL( no_scatxm , myThid )
687     _GLOBAL_SUM_RL( no_scatym , myThid )
688     _GLOBAL_SUM_RL( no_obcsn , myThid )
689     _GLOBAL_SUM_RL( no_obcss , myThid )
690     _GLOBAL_SUM_RL( no_obcsw , myThid )
691     _GLOBAL_SUM_RL( no_obcse , myThid )
692     _GLOBAL_SUM_RL( no_curmtr , myThid )
693     _GLOBAL_SUM_RL( no_ageos , myThid )
694     _GLOBAL_SUM_RL( no_kapgm , myThid )
695     _GLOBAL_SUM_RL( no_kapredi , myThid )
696     _GLOBAL_SUM_RL( no_diffkr , myThid )
697     _GLOBAL_SUM_RL( no_ini_fin , myThid )
698     _GLOBAL_SUM_RL( no_eddytau , myThid )
699     _GLOBAL_SUM_RL( no_bottomdrag , myThid )
700 heimbach 1.21 #ifdef ALLOW_PROFILES
701 heimbach 1.20 do num_file=1,NFILESPROFMAX
702 gforget 1.27 do num_var=1,NVARMAX
703 jmc 1.41 _GLOBAL_SUM_RL(no_profiles(num_file,num_var), myThid )
704 heimbach 1.20 enddo
705     enddo
706 heimbach 1.21 #endif
707 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
708     do num_var=1,NGENCOST
709 jmc 1.41 _GLOBAL_SUM_RL(no_gencost(num_var), myThid )
710 gforget 1.34 enddo
711 jmc 1.38 #endif
712 heimbach 1.7
713     write(standardmessageunit,'(A,D22.15)')
714     & ' --> f_temp =',f_temp
715     write(standardmessageunit,'(A,D22.15)')
716     & ' --> f_salt =',f_salt
717     write(standardmessageunit,'(A,D22.15)')
718     & ' --> f_temp0 =',f_temp0
719     write(standardmessageunit,'(A,D22.15)')
720     & ' --> f_salt0 =',f_salt0
721     write(standardmessageunit,'(A,D22.15)')
722 heimbach 1.16 & ' --> f_temp0smoo =',f_temp0smoo
723     write(standardmessageunit,'(A,D22.15)')
724     & ' --> f_salt0smoo =',f_salt0smoo
725     write(standardmessageunit,'(A,D22.15)')
726 heimbach 1.7 & ' --> f_sst =',f_sst
727     write(standardmessageunit,'(A,D22.15)')
728     & ' --> f_tmi =',f_tmi
729     write(standardmessageunit,'(A,D22.15)')
730     & ' --> f_sss =',f_sss
731     write(standardmessageunit,'(A,D22.15)')
732 heimbach 1.36 & ' --> f_bp =',f_bp
733     write(standardmessageunit,'(A,D22.15)')
734 heimbach 1.7 & ' --> f_ssh =',f_ssh
735     write(standardmessageunit,'(A,D22.15)')
736 heimbach 1.23 & ' --> f_tp =',f_tp
737     write(standardmessageunit,'(A,D22.15)')
738     & ' --> f_ers =',f_ers
739     write(standardmessageunit,'(A,D22.15)')
740     & ' --> f_gfo =',f_gfo
741     write(standardmessageunit,'(A,D22.15)')
742 heimbach 1.7 & ' --> f_tauu =',f_tauu
743     write(standardmessageunit,'(A,D22.15)')
744     & ' --> f_tauum =',f_tauum
745     write(standardmessageunit,'(A,D22.15)')
746 heimbach 1.15 & ' --> f_tauusmoo =',f_tauusmoo
747     write(standardmessageunit,'(A,D22.15)')
748 heimbach 1.7 & ' --> f_tauv =',f_tauv
749     write(standardmessageunit,'(A,D22.15)')
750     & ' --> f_tauvm =',f_tauvm
751     write(standardmessageunit,'(A,D22.15)')
752 heimbach 1.15 & ' --> f_tauvsmoo =',f_tauvsmoo
753     write(standardmessageunit,'(A,D22.15)')
754 heimbach 1.7 & ' --> f_hflux =',f_hflux
755     write(standardmessageunit,'(A,D22.15)')
756 heimbach 1.10 & ' --> f_hfluxmm =',f_hfluxmm
757 heimbach 1.7 write(standardmessageunit,'(A,D22.15)')
758 heimbach 1.15 & ' --> f_hfluxsmoo =',f_hfluxsmoo
759     write(standardmessageunit,'(A,D22.15)')
760 heimbach 1.7 & ' --> f_sflux =',f_sflux
761     write(standardmessageunit,'(A,D22.15)')
762 heimbach 1.10 & ' --> f_sfluxmm =',f_sfluxmm
763 heimbach 1.7 write(standardmessageunit,'(A,D22.15)')
764 heimbach 1.15 & ' --> f_sfluxsmoo =',f_sfluxsmoo
765     write(standardmessageunit,'(A,D22.15)')
766 heimbach 1.7 & ' --> f_uwind =',f_uwind
767     write(standardmessageunit,'(A,D22.15)')
768     & ' --> f_vwind =',f_vwind
769     write(standardmessageunit,'(A,D22.15)')
770     & ' --> f_atemp =',f_atemp
771     write(standardmessageunit,'(A,D22.15)')
772     & ' --> f_aqh =',f_aqh
773     write(standardmessageunit,'(A,D22.15)')
774 heimbach 1.9 & ' --> f_precip =',f_precip
775     write(standardmessageunit,'(A,D22.15)')
776 heimbach 1.10 & ' --> f_swflux =',f_swflux
777     write(standardmessageunit,'(A,D22.15)')
778 heimbach 1.12 & ' --> f_swdown =',f_swdown
779     write(standardmessageunit,'(A,D22.15)')
780 heimbach 1.11 & ' --> f_uwindm =',f_uwindm
781     write(standardmessageunit,'(A,D22.15)')
782     & ' --> f_vwindm =',f_vwindm
783     write(standardmessageunit,'(A,D22.15)')
784     & ' --> f_atempm =',f_atempm
785     write(standardmessageunit,'(A,D22.15)')
786     & ' --> f_aqhm =',f_aqhm
787     write(standardmessageunit,'(A,D22.15)')
788     & ' --> f_precipm =',f_precipm
789     write(standardmessageunit,'(A,D22.15)')
790     & ' --> f_swfluxm =',f_swfluxm
791     write(standardmessageunit,'(A,D22.15)')
792 heimbach 1.12 & ' --> f_swdownm =',f_swdownm
793     write(standardmessageunit,'(A,D22.15)')
794 heimbach 1.15 & ' --> f_uwindsmoo =',f_uwindsmoo
795     write(standardmessageunit,'(A,D22.15)')
796     & ' --> f_vwindsmoo =',f_vwindsmoo
797     write(standardmessageunit,'(A,D22.15)')
798     & ' --> f_atempsmoo =',f_atempsmoo
799     write(standardmessageunit,'(A,D22.15)')
800     & ' --> f_aqhsmoo =',f_aqhsmoo
801     write(standardmessageunit,'(A,D22.15)')
802     & ' --> f_precipsmoo =',f_precipsmoo
803     write(standardmessageunit,'(A,D22.15)')
804     & ' --> f_swfluxsmoo =',f_swfluxsmoo
805     write(standardmessageunit,'(A,D22.15)')
806     & ' --> f_swdownsmoo =',f_swdownsmoo
807     write(standardmessageunit,'(A,D22.15)')
808 heimbach 1.7 & ' --> f_atl =',f_atl
809     write(standardmessageunit,'(A,D22.15)')
810     & ' --> f_ctdt =',f_ctdt
811     write(standardmessageunit,'(A,D22.15)')
812     & ' --> f_ctds =',f_ctds
813     write(standardmessageunit,'(A,D22.15)')
814     & ' --> f_ctdtclim=',f_ctdtclim
815     write(standardmessageunit,'(A,D22.15)')
816     & ' --> f_ctdsclim=',f_ctdsclim
817     write(standardmessageunit,'(A,D22.15)')
818     & ' --> f_xbt =',f_xbt
819     write(standardmessageunit,'(A,D22.15)')
820     & ' --> f_argot =',f_argot
821     write(standardmessageunit,'(A,D22.15)')
822     & ' --> f_argos =',f_argos
823     write(standardmessageunit,'(A,D22.15)')
824     & ' --> f_drifter =',f_drifter
825     write(standardmessageunit,'(A,D22.15)')
826     & ' --> f_tdrift =',f_tdrift
827     write(standardmessageunit,'(A,D22.15)')
828     & ' --> f_sdrift =',f_sdrift
829     write(standardmessageunit,'(A,D22.15)')
830     & ' --> f_wdrift =',f_wdrift
831     write(standardmessageunit,'(A,D22.15)')
832     & ' --> f_scatx =',f_scatx
833     write(standardmessageunit,'(A,D22.15)')
834     & ' --> f_scaty =',f_scaty
835     write(standardmessageunit,'(A,D22.15)')
836     & ' --> f_scatxm =',f_scatxm
837     write(standardmessageunit,'(A,D22.15)')
838     & ' --> f_scatym =',f_scatym
839     write(standardmessageunit,'(A,D22.15)')
840     & ' --> f_obcsn =',f_obcsn
841     write(standardmessageunit,'(A,D22.15)')
842     & ' --> f_obcss =',f_obcss
843     write(standardmessageunit,'(A,D22.15)')
844     & ' --> f_obcsw =',f_obcsw
845     write(standardmessageunit,'(A,D22.15)')
846     & ' --> f_obcse =',f_obcse
847     write(standardmessageunit,'(A,D22.15)')
848     & ' --> f_ageos =',f_ageos
849     write(standardmessageunit,'(A,D22.15)')
850     & ' --> f_curmtr =',f_curmtr
851     write(standardmessageunit,'(A,D22.15)')
852     & ' --> f_kapgm =',f_kapgm
853     write(standardmessageunit,'(A,D22.15)')
854 gforget 1.39 & ' --> f_kapredi =',f_kapredi
855     write(standardmessageunit,'(A,D22.15)')
856 heimbach 1.7 & ' --> f_diffkr =',f_diffkr
857     write(standardmessageunit,'(A,D22.15)')
858     & ' --> f_eddytau =', f_eddytau
859 gforget 1.33 write(standardmessageunit,'(A,D22.15)')
860     & ' --> f_bottomdrag =', f_bottomdrag
861 heimbach 1.21 #ifdef ALLOW_PROFILES
862 heimbach 1.20 do num_file=1,NFILESPROFMAX
863 gforget 1.27 do num_var=1,NVARMAX
864 heimbach 1.20 if (no_profiles(num_file,num_var).GT.0) then
865     write(standardmessageunit,'(A,D22.15,i2.0,i2.0)')
866     & ' --> f_profiles =',f_profiles(num_file,num_var),
867     & num_file, num_var
868     endif
869     enddo
870     enddo
871 heimbach 1.21 #endif
872 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
873     do num_var=1,NGENCOST
874     if (no_gencost(num_var).GT.0) then
875     write(standardmessageunit,'(A,D22.15,i2.0,i2.0)')
876     & ' --> f_gencost =',f_gencost(num_var),
877     & num_var
878     endif
879     enddo
880 jmc 1.38 #endif
881 heimbach 1.7
882 heimbach 1.1 c-- Each process has calculated the global part for itself.
883 dimitri 1.40 IF ( MASTER_CPU_THREAD(myThid) ) THEN
884 heimbach 1.1
885 jmc 1.38 fc = fc
886 heimbach 1.35 & + mult_hmean*objf_hmean
887 heimbach 1.9 no_hmean = num_hmean
888    
889 heimbach 1.25 cph(
890 heimbach 1.32 cph this is from annual mean misfits;
891     cph simple sums and squares needed to be taken at annual intervals
892 heimbach 1.37 f_hfluxmm = f_hfluxmm + objf_hfluxmm
893     f_hfluxmm2 = mult_hfluxmm*f_hfluxmm
894     c
895 heimbach 1.32 f_sfluxmm = f_sfluxmm + objf_sfluxmm
896 heimbach 1.23 f_sfluxmm2 = mult_sfluxmm*f_sfluxmm
897 heimbach 1.37 c
898 heimbach 1.35 f_transp = mult_transp*objf_transp
899    
900     no_transp = num_transp
901 heimbach 1.25 cph)
902 jmc 1.38 fc = fc
903 heimbach 1.35 & + f_hfluxmm2 + f_sfluxmm2
904     & + f_transp
905 heimbach 1.19
906     write(standardmessageunit,'(A,D22.15)')
907     & ' --> f_hfluxmm2 =',f_hfluxmm2
908     write(standardmessageunit,'(A,D22.15)')
909     & ' --> f_sfluxmm2 =',f_sfluxmm2
910 heimbach 1.5 write(standardmessageunit,'(A,D22.15)')
911 heimbach 1.35 & ' --> f_transp =',f_transp
912     write(standardmessageunit,'(A,D22.15)')
913 heimbach 1.5 & ' --> objf_hmean =',objf_hmean
914     write(standardmessageunit,'(A,D22.15)')
915     & ' --> fc =', fc
916 jmc 1.38
917 heimbach 1.1 write(cfname,'(A,i4.4)') 'costfunction',optimcycle
918     open(unit=ifc,file=cfname)
919 jmc 1.38
920     write(ifc,'(A,2D22.15)')
921 heimbach 1.31 & 'fc =', fc, 0.
922 jmc 1.38 write(ifc,'(A,2D22.15)')
923 heimbach 1.31 & 'f_temp =', f_temp, no_temp
924 jmc 1.38 write(ifc,'(A,2D22.15)')
925 heimbach 1.31 & 'f_salt =', f_salt, no_salt
926 jmc 1.38 write(ifc,'(A,2D22.15)')
927 heimbach 1.31 & 'f_temp0 =', f_temp0, no_temp0
928 jmc 1.38 write(ifc,'(A,2D22.15)')
929 heimbach 1.31 & 'f_salt0 =', f_salt0, no_salt0
930 jmc 1.38 write(ifc,'(A,2D22.15)')
931 heimbach 1.31 & 'f_temp0smoo =', f_temp0smoo, no_temp0
932 jmc 1.38 write(ifc,'(A,2D22.15)')
933 heimbach 1.31 & 'f_salt0smoo =', f_salt0smoo, no_salt0
934 jmc 1.38 write(ifc,'(A,2D22.15)')
935 heimbach 1.31 & 'f_tauu =', f_tauu, no_tauu
936 jmc 1.38 write(ifc,'(A,2D22.15)')
937 heimbach 1.31 & 'f_tauum =', f_tauum, no_tauum
938 jmc 1.38 write(ifc,'(A,2D22.15)')
939 heimbach 1.31 & 'f_tauusmoo =', f_tauusmoo, no_tauu
940 jmc 1.38 write(ifc,'(A,2D22.15)')
941 heimbach 1.31 & 'f_tauv =', f_tauv, no_tauv
942 jmc 1.38 write(ifc,'(A,2D22.15)')
943 heimbach 1.31 & 'f_tauvm =', f_tauvm, no_tauvm
944 jmc 1.38 write(ifc,'(A,2D22.15)')
945 heimbach 1.31 & 'f_tauvsmoo =', f_tauvsmoo, no_tauv
946 jmc 1.38 write(ifc,'(A,2D22.15)')
947 heimbach 1.31 & 'f_hflux =', f_hflux, no_hflux
948 jmc 1.38 write(ifc,'(A,2D22.15)')
949 heimbach 1.31 & 'f_hfluxm =', f_hfluxm, no_hfluxm
950 jmc 1.38 write(ifc,'(A,2D22.15)')
951 heimbach 1.31 & 'f_hfluxmm =', f_hfluxmm, no_hfluxmm
952 jmc 1.38 write(ifc,'(A,2D22.15)')
953 heimbach 1.31 & 'f_hfluxmm2 =', f_hfluxmm2, mult_hfluxmm
954 jmc 1.38 write(ifc,'(A,2D22.15)')
955 heimbach 1.31 & 'f_hfluxsmoo =', f_hfluxsmoo, no_hflux
956 jmc 1.38 write(ifc,'(A,2D22.15)')
957 heimbach 1.31 & 'f_sflux =', f_sflux, no_sflux
958 jmc 1.38 write(ifc,'(A,2D22.15)')
959 heimbach 1.31 & 'f_sfluxm =', f_sfluxm, no_sfluxm
960 jmc 1.38 write(ifc,'(A,2D22.15)')
961 heimbach 1.31 & 'f_sfluxmm =', f_sfluxmm, no_sfluxmm
962 jmc 1.38 write(ifc,'(A,2D22.15)')
963 heimbach 1.31 & 'f_sfluxmm2 =', f_sfluxmm2, mult_sfluxmm
964 jmc 1.38 write(ifc,'(A,2D22.15)')
965 heimbach 1.31 & 'f_sfluxsmoo =', f_sfluxsmoo, no_sflux
966 jmc 1.38 write(ifc,'(A,2D22.15)')
967 heimbach 1.31 & 'f_uwind =', f_uwind, no_uwind
968 jmc 1.38 write(ifc,'(A,2D22.15)')
969 heimbach 1.31 & 'f_vwind =', f_vwind, no_vwind
970 jmc 1.38 write(ifc,'(A,2D22.15)')
971 heimbach 1.31 & 'f_atemp =', f_atemp, no_atemp
972 jmc 1.38 write(ifc,'(A,2D22.15)')
973 heimbach 1.31 & 'f_aqh =', f_aqh, no_aqh
974 jmc 1.38 write(ifc,'(A,2D22.15)')
975 heimbach 1.31 & 'f_precip =', f_precip, no_precip
976 jmc 1.38 write(ifc,'(A,2D22.15)')
977 heimbach 1.31 & 'f_swflux =', f_swflux, no_swflux
978 jmc 1.38 write(ifc,'(A,2D22.15)')
979 heimbach 1.31 & 'f_swdown =', f_swdown, no_swdown
980 jmc 1.38 write(ifc,'(A,2D22.15)')
981 heimbach 1.31 & 'f_uwindm =', f_uwindm, no_uwindm
982 jmc 1.38 write(ifc,'(A,2D22.15)')
983 heimbach 1.31 & 'f_vwindm =', f_vwindm, no_vwindm
984 jmc 1.38 write(ifc,'(A,2D22.15)')
985 heimbach 1.31 & 'f_atempm =', f_atempm, no_atempm
986 jmc 1.38 write(ifc,'(A,2D22.15)')
987 heimbach 1.31 & 'f_aqhm =', f_aqhm, no_aqhm
988 jmc 1.38 write(ifc,'(A,2D22.15)')
989 heimbach 1.31 & 'f_precipm =', f_precipm, no_precipm
990 jmc 1.38 write(ifc,'(A,2D22.15)')
991 heimbach 1.31 & 'f_swfluxm =', f_swfluxm, no_swfluxm
992 jmc 1.38 write(ifc,'(A,2D22.15)')
993 heimbach 1.31 & 'f_swdownm =', f_swdownm, no_swdownm
994 jmc 1.38 write(ifc,'(A,2D22.15)')
995 heimbach 1.31 & 'f_uwindsmoo =', f_uwindsmoo, no_uwind
996 jmc 1.38 write(ifc,'(A,2D22.15)')
997 heimbach 1.31 & 'f_vwindsmoo =', f_vwindsmoo, no_vwind
998 jmc 1.38 write(ifc,'(A,2D22.15)')
999 heimbach 1.31 & 'f_atempsmoo =', f_atempsmoo, no_atemp
1000 jmc 1.38 write(ifc,'(A,2D22.15)')
1001 heimbach 1.31 & 'f_aqhsmoo =', f_aqhsmoo, no_aqh
1002 jmc 1.38 write(ifc,'(A,2D22.15)')
1003 heimbach 1.31 & 'f_precipsmoo =', f_precipsmoo, no_precip
1004 jmc 1.38 write(ifc,'(A,2D22.15)')
1005 heimbach 1.31 & 'f_swfluxsmoo =', f_swfluxsmoo, no_swflux
1006 jmc 1.38 write(ifc,'(A,2D22.15)')
1007 heimbach 1.31 & 'f_swdownsmoo =', f_swdownsmoo, no_swdown
1008 jmc 1.38 write(ifc,'(A,2D22.15)')
1009 heimbach 1.31 & 'f_ssh =', f_ssh, no_ssh
1010 jmc 1.38 write(ifc,'(A,2D22.15)')
1011 heimbach 1.31 & 'f_tp =', f_tp, no_tp
1012 jmc 1.38 write(ifc,'(A,2D22.15)')
1013 heimbach 1.31 & 'f_ers =', f_ers, no_ers
1014 jmc 1.38 write(ifc,'(A,2D22.15)')
1015 heimbach 1.31 & 'f_gfo =', f_gfo, no_gfo
1016 jmc 1.38 write(ifc,'(A,2D22.15)')
1017 heimbach 1.31 & 'f_sst =', f_sst, no_sst
1018 jmc 1.38 write(ifc,'(A,2D22.15)')
1019 heimbach 1.31 & 'f_tmi =', f_tmi, no_tmi
1020 jmc 1.38 write(ifc,'(A,2D22.15)')
1021 heimbach 1.31 & 'f_sss =', f_sss, no_sss
1022 jmc 1.38 write(ifc,'(A,2D22.15)')
1023 heimbach 1.36 & 'f_bp =', f_bp, no_bp
1024 jmc 1.38 write(ifc,'(A,2D22.15)')
1025 heimbach 1.31 & 'f_atl =', f_atl, no_atl
1026 jmc 1.38 write(ifc,'(A,2D22.15)')
1027 heimbach 1.31 & 'f_ctdt =', f_ctdt, no_ctdt
1028 jmc 1.38 write(ifc,'(A,2D22.15)')
1029 heimbach 1.31 & 'f_ctds =', f_ctds, no_ctds
1030 jmc 1.38 write(ifc,'(A,2D22.15)')
1031 heimbach 1.31 & 'f_ctdtclim =', f_ctdtclim, no_ctdtclim
1032 jmc 1.38 write(ifc,'(A,2D22.15)')
1033 heimbach 1.31 & 'f_ctdsclim =', f_ctdsclim, no_ctdsclim
1034 jmc 1.38 write(ifc,'(A,2D22.15)')
1035 heimbach 1.31 & 'f_xbt =', f_xbt, no_xbt
1036 jmc 1.38 write(ifc,'(A,2D22.15)')
1037 heimbach 1.31 & 'f_argot =', f_argot, no_argot
1038 jmc 1.38 write(ifc,'(A,2D22.15)')
1039 heimbach 1.31 & 'f_argos =', f_argos, no_argos
1040 jmc 1.38 write(ifc,'(A,2D22.15)')
1041 heimbach 1.31 & 'objf_hmean =', objf_hmean, no_hmean
1042 jmc 1.38 write(ifc,'(A,2D22.15)')
1043 heimbach 1.31 & 'f_drifter =', f_drifter, no_drifter
1044 jmc 1.38 write(ifc,'(A,2D22.15)')
1045 heimbach 1.31 & 'f_sdrift =', f_sdrift, no_sdrift
1046 jmc 1.38 write(ifc,'(A,2D22.15)')
1047 heimbach 1.31 & 'f_tdrift =', f_tdrift, no_tdrift
1048 jmc 1.38 write(ifc,'(A,2D22.15)')
1049 heimbach 1.31 & 'f_wdrift =', f_wdrift, no_wdrift
1050 jmc 1.38 write(ifc,'(A,2D22.15)')
1051 heimbach 1.31 & 'f_scatx =', f_scatx, no_scatx
1052 jmc 1.38 write(ifc,'(A,2D22.15)')
1053 heimbach 1.31 & 'f_scaty =', f_scaty, no_scaty
1054 jmc 1.38 write(ifc,'(A,2D22.15)')
1055 heimbach 1.31 & 'f_scatxm =', f_scatxm, no_scatxm
1056 jmc 1.38 write(ifc,'(A,2D22.15)')
1057 heimbach 1.31 & 'f_scatym =', f_scatym, no_scatym
1058 jmc 1.38 write(ifc,'(A,2D22.15)')
1059 heimbach 1.31 & 'f_obcsn =', f_obcsn, no_obcsn
1060 jmc 1.38 write(ifc,'(A,2D22.15)')
1061 heimbach 1.31 & 'f_obcss =', f_obcss, no_obcss
1062 jmc 1.38 write(ifc,'(A,2D22.15)')
1063 heimbach 1.31 & 'f_obcsw =', f_obcsw, no_obcsw
1064 jmc 1.38 write(ifc,'(A,2D22.15)')
1065 heimbach 1.31 & 'f_obcse =', f_obcse, no_obcse
1066 jmc 1.38 write(ifc,'(A,2D22.15)')
1067 heimbach 1.31 & 'f_ageos =', f_ageos, no_ageos
1068 jmc 1.38 write(ifc,'(A,2D22.15)')
1069 heimbach 1.31 & 'f_kapgm =', f_kapgm, no_kapgm
1070 jmc 1.38 write(ifc,'(A,2D22.15)')
1071 gforget 1.39 & 'f_kapredi =', f_kapredi, no_kapredi
1072     write(ifc,'(A,2D22.15)')
1073 heimbach 1.31 & 'f_diffkr =', f_diffkr, no_diffkr
1074 jmc 1.38 write(ifc,'(A,2D22.15)')
1075 heimbach 1.31 & 'f_ini_fin =', f_ini_fin, no_ini_fin
1076 jmc 1.38 write(ifc,'(A,2D22.15)')
1077 heimbach 1.31 & 'f_eddytau =', f_eddytau, no_eddytau
1078 jmc 1.38 write(ifc,'(A,2D22.15)')
1079 gforget 1.33 & 'f_bottomdrag =', f_bottomdrag, no_bottomdrag
1080 jmc 1.38 write(ifc,'(A,2D22.15)')
1081 heimbach 1.35 & 'f_transp =', f_transp, no_transp
1082 heimbach 1.21 #ifdef ALLOW_PROFILES
1083 heimbach 1.20 do num_file=1,NFILESPROFMAX
1084 gforget 1.27 do num_var=1,NVARMAX
1085 heimbach 1.20 if (no_profiles(num_file,num_var).GT.0) then
1086     IL = ILNBLNK( profilesfiles(num_file) )
1087 jmc 1.38 write(ifc,'(3A,2D22.15)')
1088 heimbach 1.30 & profilesfiles(num_file)(1:IL), prof_names(num_var), ' = ',
1089 jmc 1.38 & f_profiles(num_file,num_var),
1090 heimbach 1.20 & no_profiles(num_file,num_var)
1091     endif
1092     enddo
1093     enddo
1094 heimbach 1.21 #endif
1095 gforget 1.34 #ifdef ALLOW_GENCOST_CONTRIBUTION
1096     do num_var=1,NGENCOST
1097     if (no_gencost(num_var).GT.0) then
1098     write(ifc,'(A,i2.0,A,2D22.15)')
1099     & 'gencost', num_var, ' = ',
1100     & f_gencost(num_var),
1101     & no_gencost(num_var)
1102     endif
1103     enddo
1104 jmc 1.38 #endif
1105 heimbach 1.3
1106 heimbach 1.1 close(ifc)
1107 jmc 1.38
1108 dimitri 1.40 ENDIF
1109 heimbach 1.2
1110 heimbach 1.8 call cost_trans_merid( mythid )
1111     call cost_trans_zonal( mythid )
1112    
1113 heimbach 1.31 taveFreq = 0.
1114     dumpFreq = 0.
1115     pChkptFreq = 0.
1116 heimbach 1.4 monitorFreq = 0.
1117 heimbach 1.8 useDiagnostics = .FALSE.
1118 heimbach 1.22 useSBO = .FALSE.
1119 heimbach 1.4
1120 heimbach 1.14 #ifdef ALLOW_MNC
1121     monitor_mnc=.FALSE.
1122     snapshot_mnc=.FALSE.
1123     timeave_mnc=.FALSE.
1124     #endif
1125    
1126 heimbach 1.1 #ifdef ECCO_VERBOSE
1127     write(msgbuf,'(a,D22.15)')
1128     & ' cost_Final: final cost function = ',fc
1129     call print_message( msgbuf, standardmessageunit,
1130     & SQUEEZE_RIGHT , mythid)
1131     write(msgbuf,'(a)') ' '
1132     call print_message( msgbuf, standardmessageunit,
1133     & SQUEEZE_RIGHT , mythid)
1134     write(msgbuf,'(a)')
1135     & ' cost function evaluation finished.'
1136     call print_message( msgbuf, standardmessageunit,
1137     & SQUEEZE_RIGHT , mythid)
1138     write(msgbuf,'(a)') ' '
1139     call print_message( msgbuf, standardmessageunit,
1140     & SQUEEZE_RIGHT , mythid)
1141     #endif
1142    
1143     end

  ViewVC Help
Powered by ViewVC 1.1.22