/[MITgcm]/MITgcm_contrib/ifenty/ECCO_v4/code_ad/ecco_cost_final.F.trash
ViewVC logotype

Annotation of /MITgcm_contrib/ifenty/ECCO_v4/code_ad/ecco_cost_final.F.trash

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


Revision 1.1 - (hide annotations) (download)
Tue Apr 29 21:56:11 2014 UTC (11 years, 3 months ago) by ifenty
Branch: MAIN
CVS Tags: HEAD
ECCO v4 code and input directories

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

  ViewVC Help
Powered by ViewVC 1.1.22