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

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

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


Revision 1.5 - (hide annotations) (download)
Fri Mar 24 22:58:25 2006 UTC (18 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58e_post, checkpoint58h_post, checkpoint58j_post, checkpoint58f_post, checkpoint58d_post, checkpoint58i_post, checkpoint58g_post, checkpoint58k_post
Changes since 1.4: +1 -19 lines
o package cost profiles routines to better modularize them.

1 heimbach 1.5 C $Header: /u/gcmpack/MITgcm/pkg/ecco/ecco_cost_init_varia.F,v 1.4 2006/03/23 23:06:48 heimbach Exp $
2 heimbach 1.1
3     #include "AD_CONFIG.h"
4     #include "COST_CPPOPTIONS.h"
5    
6     subroutine ecco_cost_init_varia( mythid )
7    
8     c ==================================================================
9     c SUBROUTINE ecco_cost_init_varia
10     c ==================================================================
11     c
12     c o Initialise the variable cost function part.
13     c
14     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
15     c changed: Christian Eckert eckert@mit.edu 18-Apr-2000
16     c - Restructured the code in order to create a package
17     c for the MITgcmUV.
18     c heimbach@mit.edu 05-Nov-2003 Now ecco part of cost
19     c
20     c ==================================================================
21     c SUBROUTINE ecco_cost_init_varia
22     c ==================================================================
23    
24     implicit none
25    
26     c == global variables ==
27    
28     #include "EEPARAMS.h"
29     #include "SIZE.h"
30     #include "GRID.h"
31    
32     #include "ecco_cost.h"
33    
34     c == routine arguments ==
35    
36     integer mythid
37    
38     c == local variables ==
39    
40     integer bi,bj
41     integer itlo,ithi
42     integer jtlo,jthi
43     integer imin, imax
44     integer jmin, jmax
45     integer i,j,k
46 heimbach 1.4 integer num_file,num_var
47 heimbach 1.1
48     logical exst
49    
50     c == external functions ==
51    
52     c == end of interface ==
53     jtlo = mybylo(mythid)
54     jthi = mybyhi(mythid)
55     itlo = mybxlo(mythid)
56     ithi = mybxhi(mythid)
57     jmin = 1-OLy
58     jmax = sny+OLy
59     imin = 1-OLx
60     imax = snx+OLy
61    
62     c-- Initialise adjoint of monthly mean files calculated
63     c-- in cost_averagesfields (and their ad...).
64     call cost_averagesinit( mythid )
65     _BARRIER
66    
67     #ifndef ALLOW_TANGENTLINEAR_RUN
68     cph(
69     cph The following init. shoud not be applied if in the middle
70     cph of a divided adjoint run
71     cph)
72     c inquire( file='costfinal', exist=exst )
73     c if ( .NOT. exst) then
74     c call ecco_cost_init_barfiles( mythid )
75     c endif
76     #endif
77    
78     c-- Initialize the tiled cost function contributions.
79     do bj = jtlo,jthi
80     do bi = itlo,ithi
81     objf_hflux(bi,bj) = 0. _d 0
82     objf_hfluxm(bi,bj) = 0. _d 0
83     objf_hfluxmm(bi,bj) = 0. _d 0
84     objf_sflux(bi,bj) = 0. _d 0
85     objf_sfluxm(bi,bj) = 0. _d 0
86     objf_sfluxmm(bi,bj) = 0. _d 0
87     objf_tauu(bi,bj) = 0. _d 0
88     objf_tauum(bi,bj) = 0. _d 0
89     objf_tauv(bi,bj) = 0. _d 0
90     objf_tauvm(bi,bj) = 0. _d 0
91     objf_temp(bi,bj) = 0. _d 0
92     objf_salt(bi,bj) = 0. _d 0
93     objf_temp0(bi,bj) = 0. _d 0
94     objf_salt0(bi,bj) = 0. _d 0
95 heimbach 1.2 objf_temp0smoo(bi,bj) = 0. _d 0
96     objf_salt0smoo(bi,bj) = 0. _d 0
97 heimbach 1.1 objf_tmi(bi,bj) = 0. _d 0
98     objf_sst(bi,bj) = 0. _d 0
99     objf_sss(bi,bj) = 0. _d 0
100     objf_h(bi,bj) = 0. _d 0
101     objf_ctdt(bi,bj) = 0. _d 0
102     objf_ctds(bi,bj) = 0. _d 0
103     objf_ctdtclim(bi,bj) = 0. _d 0
104     objf_ctdsclim(bi,bj) = 0. _d 0
105     objf_xbt(bi,bj) = 0. _d 0
106     objf_argot(bi,bj) = 0. _d 0
107     objf_argos(bi,bj) = 0. _d 0
108     objf_drift(bi,bj) = 0. _d 0
109     objf_wdrift(bi,bj) = 0. _d 0
110     objf_sdrift(bi,bj) = 0. _d 0
111     objf_tdrift(bi,bj) = 0. _d 0
112     objf_scatx(bi,bj) = 0. _d 0
113     objf_scaty(bi,bj) = 0. _d 0
114     objf_scatxm(bi,bj) = 0. _d 0
115     objf_scatym(bi,bj) = 0. _d 0
116     objf_atemp(bi,bj) = 0. _d 0
117     objf_aqh(bi,bj) = 0. _d 0
118     objf_precip(bi,bj) = 0. _d 0
119     objf_swflux(bi,bj) = 0. _d 0
120     objf_swdown(bi,bj) = 0. _d 0
121     objf_uwind(bi,bj) = 0. _d 0
122     objf_vwind(bi,bj) = 0. _d 0
123     objf_obcsn(bi,bj) = 0. _d 0
124     objf_obcss(bi,bj) = 0. _d 0
125     objf_obcsw(bi,bj) = 0. _d 0
126     objf_obcse(bi,bj) = 0. _d 0
127     objf_curmtr(bi,bj) = 0. _d 0
128     objf_ageos(bi,bj) = 0. _d 0
129     objf_diffkr(bi,bj) = 0. _d 0
130     objf_kapgm(bi,bj) = 0. _d 0
131     objf_theta_ini_fin(bi,bj) = 0. _d 0
132     objf_salt_ini_fin(bi,bj) = 0. _d 0
133     c
134     num_hflux(bi,bj) = 0. _d 0
135     num_hfluxm(bi,bj) = 0. _d 0
136     num_hfluxmm(bi,bj) = 0. _d 0
137     num_sflux(bi,bj) = 0. _d 0
138     num_sfluxm(bi,bj) = 0. _d 0
139     num_sfluxmm(bi,bj) = 0. _d 0
140     num_tauu(bi,bj) = 0. _d 0
141     num_tauum(bi,bj) = 0. _d 0
142     num_tauv(bi,bj) = 0. _d 0
143     num_tauvm(bi,bj) = 0. _d 0
144     num_temp(bi,bj) = 0. _d 0
145     num_salt(bi,bj) = 0. _d 0
146     num_temp0(bi,bj) = 0. _d 0
147     num_salt0(bi,bj) = 0. _d 0
148     num_tmi(bi,bj) = 0. _d 0
149     num_sst(bi,bj) = 0. _d 0
150     num_sss(bi,bj) = 0. _d 0
151     num_h(bi,bj) = 0. _d 0
152     num_ctdt(bi,bj) = 0. _d 0
153     num_ctds(bi,bj) = 0. _d 0
154     num_ctdtclim(bi,bj) = 0. _d 0
155     num_ctdsclim(bi,bj) = 0. _d 0
156     num_xbt(bi,bj) = 0. _d 0
157     num_argot(bi,bj) = 0. _d 0
158     num_argos(bi,bj) = 0. _d 0
159     num_drift(bi,bj) = 0. _d 0
160     num_wdrift(bi,bj) = 0. _d 0
161     num_sdrift(bi,bj) = 0. _d 0
162     num_tdrift(bi,bj) = 0. _d 0
163     num_scatx(bi,bj) = 0. _d 0
164     num_scaty(bi,bj) = 0. _d 0
165     num_scatxm(bi,bj) = 0. _d 0
166     num_scatym(bi,bj) = 0. _d 0
167     num_atemp(bi,bj) = 0. _d 0
168     num_aqh(bi,bj) = 0. _d 0
169     num_precip(bi,bj) = 0. _d 0
170     num_swflux(bi,bj) = 0. _d 0
171     num_swdown(bi,bj) = 0. _d 0
172     num_uwind(bi,bj) = 0. _d 0
173     num_vwind(bi,bj) = 0. _d 0
174     num_obcsn(bi,bj) = 0. _d 0
175     num_obcss(bi,bj) = 0. _d 0
176     num_obcsw(bi,bj) = 0. _d 0
177     num_obcse(bi,bj) = 0. _d 0
178     num_curmtr(bi,bj) = 0. _d 0
179     num_ageos(bi,bj) = 0. _d 0
180     num_diffkr(bi,bj) = 0. _d 0
181     num_kapgm(bi,bj) = 0. _d 0
182     num_theta_ini_fin(bi,bj) = 0. _d 0
183     num_salt_ini_fin(bi,bj) = 0. _d 0
184     enddo
185     enddo
186    
187     k = 1
188     do bj = jtlo,jthi
189     do bi = itlo,ithi
190     do j = jmin,jmax
191     do i = imin,imax
192     #ifdef ALLOW_SSH_COST_CONTRIBUTION
193     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
194     tpmeanmask(i,j,bi,bj) = 0. _d 0
195     else
196     tpmeanmask(i,j,bi,bj) = 1. _d 0
197     endif
198     tpmean(i,j,bi,bj) = 0. _d 0
199     #endif
200     #ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
201     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
202     tpmask(i,j,bi,bj) = 0. _d 0
203     else
204     tpmask(i,j,bi,bj) = 1. _d 0
205     endif
206     tpobs(i,j,bi,bj) = 0. _d 0
207     #endif
208     #ifdef ALLOW_SSH_ERSANOM_COST_CONTRIBUTION
209     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
210     ersmask(i,j,bi,bj) = 0. _d 0
211     else
212     ersmask(i,j,bi,bj) = 1. _d 0
213     endif
214     ersobs(i,j,bi,bj) = 0. _d 0
215     #endif
216 heimbach 1.3 #ifdef ALLOW_SSH_GFOANOM_COST_CONTRIBUTION
217     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
218     gfomask(i,j,bi,bj) = 0. _d 0
219     else
220     gfomask(i,j,bi,bj) = 1. _d 0
221     endif
222     gfoobs(i,j,bi,bj) = 0. _d 0
223     #endif
224 heimbach 1.1 #ifdef ALLOW_TMI_SST_COST_CONTRIBUTION
225     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
226     tmimask(i,j,bi,bj) = 0. _d 0
227     else
228     tmimask(i,j,bi,bj) = 1. _d 0
229     endif
230     tmidat(i,j,bi,bj) = 0. _d 0
231     #endif
232     #ifdef ALLOW_SST_COST_CONTRIBUTION
233     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
234     sstmask(i,j,bi,bj) = 0. _d 0
235     else
236     sstmask(i,j,bi,bj) = 1. _d 0
237     endif
238     sstdat(i,j,bi,bj) = 0. _d 0
239     #endif
240     #ifdef ALLOW_SSS_COST_CONTRIBUTION
241     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
242     sssmask(i,j,bi,bj) = 0. _d 0
243     else
244     sssmask(i,j,bi,bj) = 1. _d 0
245     endif
246     sssdat(i,j,bi,bj) = 0. _d 0
247     #endif
248     enddo
249     enddo
250     enddo
251     enddo
252    
253     c-- Initialise the "global" parts of the cost function.
254     _BEGIN_MASTER( mythid )
255     objf_obcsvol = 0. _d 0
256     objf_hmean = 0. _d 0
257     num_obcsvol = 0. _d 0
258     num_hmean = 0. _d 0
259     _END_MASTER( mythid )
260    
261     _BARRIER
262    
263     return
264     end
265    

  ViewVC Help
Powered by ViewVC 1.1.22