/[MITgcm]/MITgcm_contrib/SOSE/code_ad/ecco_cost_final.F
ViewVC logotype

Annotation of /MITgcm_contrib/SOSE/code_ad/ecco_cost_final.F

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


Revision 1.1 - (hide annotations) (download)
Fri Apr 23 19:55:12 2010 UTC (15 years, 3 months ago) by mmazloff
Branch: MAIN
CVS Tags: HEAD
original files

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

  ViewVC Help
Powered by ViewVC 1.1.22