/[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.1 - (hide annotations) (download)
Thu Aug 25 16:10:42 2005 UTC (18 years, 9 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57v_post, checkpoint57s_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57r_post, checkpoint57x_post, checkpoint57w_post, checkpint57u_post
Moving seaice-related cost to pkg/seaice/

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/ecco_cost_initvaria.F,v 1.7 2005/08/06 11:02:01 heimbach Exp $
2    
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    
47     logical exst
48    
49     c == external functions ==
50    
51     c == end of interface ==
52     jtlo = mybylo(mythid)
53     jthi = mybyhi(mythid)
54     itlo = mybxlo(mythid)
55     ithi = mybxhi(mythid)
56     jmin = 1-OLy
57     jmax = sny+OLy
58     imin = 1-OLx
59     imax = snx+OLy
60    
61     c-- Initialise adjoint of monthly mean files calculated
62     c-- in cost_averagesfields (and their ad...).
63     call cost_averagesinit( mythid )
64     _BARRIER
65    
66     #ifndef ALLOW_TANGENTLINEAR_RUN
67     cph(
68     cph The following init. shoud not be applied if in the middle
69     cph of a divided adjoint run
70     cph)
71     c inquire( file='costfinal', exist=exst )
72     c if ( .NOT. exst) then
73     c call ecco_cost_init_barfiles( mythid )
74     c endif
75     #endif
76    
77     c-- Initialize the tiled cost function contributions.
78     do bj = jtlo,jthi
79     do bi = itlo,ithi
80     objf_hflux(bi,bj) = 0. _d 0
81     objf_hfluxm(bi,bj) = 0. _d 0
82     objf_hfluxmm(bi,bj) = 0. _d 0
83     objf_sflux(bi,bj) = 0. _d 0
84     objf_sfluxm(bi,bj) = 0. _d 0
85     objf_sfluxmm(bi,bj) = 0. _d 0
86     objf_tauu(bi,bj) = 0. _d 0
87     objf_tauum(bi,bj) = 0. _d 0
88     objf_tauv(bi,bj) = 0. _d 0
89     objf_tauvm(bi,bj) = 0. _d 0
90     objf_temp(bi,bj) = 0. _d 0
91     objf_salt(bi,bj) = 0. _d 0
92     objf_temp0(bi,bj) = 0. _d 0
93     objf_salt0(bi,bj) = 0. _d 0
94     objf_tmi(bi,bj) = 0. _d 0
95     objf_sst(bi,bj) = 0. _d 0
96     objf_sss(bi,bj) = 0. _d 0
97     objf_h(bi,bj) = 0. _d 0
98     objf_ctdt(bi,bj) = 0. _d 0
99     objf_ctds(bi,bj) = 0. _d 0
100     objf_ctdtclim(bi,bj) = 0. _d 0
101     objf_ctdsclim(bi,bj) = 0. _d 0
102     objf_xbt(bi,bj) = 0. _d 0
103     objf_argot(bi,bj) = 0. _d 0
104     objf_argos(bi,bj) = 0. _d 0
105     objf_drift(bi,bj) = 0. _d 0
106     objf_wdrift(bi,bj) = 0. _d 0
107     objf_sdrift(bi,bj) = 0. _d 0
108     objf_tdrift(bi,bj) = 0. _d 0
109     objf_scatx(bi,bj) = 0. _d 0
110     objf_scaty(bi,bj) = 0. _d 0
111     objf_scatxm(bi,bj) = 0. _d 0
112     objf_scatym(bi,bj) = 0. _d 0
113     objf_atemp(bi,bj) = 0. _d 0
114     objf_aqh(bi,bj) = 0. _d 0
115     objf_precip(bi,bj) = 0. _d 0
116     objf_swflux(bi,bj) = 0. _d 0
117     objf_swdown(bi,bj) = 0. _d 0
118     objf_uwind(bi,bj) = 0. _d 0
119     objf_vwind(bi,bj) = 0. _d 0
120     objf_obcsn(bi,bj) = 0. _d 0
121     objf_obcss(bi,bj) = 0. _d 0
122     objf_obcsw(bi,bj) = 0. _d 0
123     objf_obcse(bi,bj) = 0. _d 0
124     objf_curmtr(bi,bj) = 0. _d 0
125     objf_ageos(bi,bj) = 0. _d 0
126     objf_diffkr(bi,bj) = 0. _d 0
127     objf_kapgm(bi,bj) = 0. _d 0
128     objf_theta_ini_fin(bi,bj) = 0. _d 0
129     objf_salt_ini_fin(bi,bj) = 0. _d 0
130     c
131     num_hflux(bi,bj) = 0. _d 0
132     num_hfluxm(bi,bj) = 0. _d 0
133     num_hfluxmm(bi,bj) = 0. _d 0
134     num_sflux(bi,bj) = 0. _d 0
135     num_sfluxm(bi,bj) = 0. _d 0
136     num_sfluxmm(bi,bj) = 0. _d 0
137     num_tauu(bi,bj) = 0. _d 0
138     num_tauum(bi,bj) = 0. _d 0
139     num_tauv(bi,bj) = 0. _d 0
140     num_tauvm(bi,bj) = 0. _d 0
141     num_temp(bi,bj) = 0. _d 0
142     num_salt(bi,bj) = 0. _d 0
143     num_temp0(bi,bj) = 0. _d 0
144     num_salt0(bi,bj) = 0. _d 0
145     num_tmi(bi,bj) = 0. _d 0
146     num_sst(bi,bj) = 0. _d 0
147     num_sss(bi,bj) = 0. _d 0
148     num_h(bi,bj) = 0. _d 0
149     num_ctdt(bi,bj) = 0. _d 0
150     num_ctds(bi,bj) = 0. _d 0
151     num_ctdtclim(bi,bj) = 0. _d 0
152     num_ctdsclim(bi,bj) = 0. _d 0
153     num_xbt(bi,bj) = 0. _d 0
154     num_argot(bi,bj) = 0. _d 0
155     num_argos(bi,bj) = 0. _d 0
156     num_drift(bi,bj) = 0. _d 0
157     num_wdrift(bi,bj) = 0. _d 0
158     num_sdrift(bi,bj) = 0. _d 0
159     num_tdrift(bi,bj) = 0. _d 0
160     num_scatx(bi,bj) = 0. _d 0
161     num_scaty(bi,bj) = 0. _d 0
162     num_scatxm(bi,bj) = 0. _d 0
163     num_scatym(bi,bj) = 0. _d 0
164     num_atemp(bi,bj) = 0. _d 0
165     num_aqh(bi,bj) = 0. _d 0
166     num_precip(bi,bj) = 0. _d 0
167     num_swflux(bi,bj) = 0. _d 0
168     num_swdown(bi,bj) = 0. _d 0
169     num_uwind(bi,bj) = 0. _d 0
170     num_vwind(bi,bj) = 0. _d 0
171     num_obcsn(bi,bj) = 0. _d 0
172     num_obcss(bi,bj) = 0. _d 0
173     num_obcsw(bi,bj) = 0. _d 0
174     num_obcse(bi,bj) = 0. _d 0
175     num_curmtr(bi,bj) = 0. _d 0
176     num_ageos(bi,bj) = 0. _d 0
177     num_diffkr(bi,bj) = 0. _d 0
178     num_kapgm(bi,bj) = 0. _d 0
179     num_theta_ini_fin(bi,bj) = 0. _d 0
180     num_salt_ini_fin(bi,bj) = 0. _d 0
181     enddo
182     enddo
183    
184     k = 1
185     do bj = jtlo,jthi
186     do bi = itlo,ithi
187     do j = jmin,jmax
188     do i = imin,imax
189     #ifdef ALLOW_SSH_COST_CONTRIBUTION
190     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
191     tpmeanmask(i,j,bi,bj) = 0. _d 0
192     else
193     tpmeanmask(i,j,bi,bj) = 1. _d 0
194     endif
195     tpmean(i,j,bi,bj) = 0. _d 0
196     #endif
197     #ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
198     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
199     tpmask(i,j,bi,bj) = 0. _d 0
200     else
201     tpmask(i,j,bi,bj) = 1. _d 0
202     endif
203     tpobs(i,j,bi,bj) = 0. _d 0
204     #endif
205     #ifdef ALLOW_SSH_ERSANOM_COST_CONTRIBUTION
206     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
207     ersmask(i,j,bi,bj) = 0. _d 0
208     else
209     ersmask(i,j,bi,bj) = 1. _d 0
210     endif
211     ersobs(i,j,bi,bj) = 0. _d 0
212     #endif
213     #ifdef ALLOW_TMI_SST_COST_CONTRIBUTION
214     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
215     tmimask(i,j,bi,bj) = 0. _d 0
216     else
217     tmimask(i,j,bi,bj) = 1. _d 0
218     endif
219     tmidat(i,j,bi,bj) = 0. _d 0
220     #endif
221     #ifdef ALLOW_SST_COST_CONTRIBUTION
222     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
223     sstmask(i,j,bi,bj) = 0. _d 0
224     else
225     sstmask(i,j,bi,bj) = 1. _d 0
226     endif
227     sstdat(i,j,bi,bj) = 0. _d 0
228     #endif
229     #ifdef ALLOW_SSS_COST_CONTRIBUTION
230     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
231     sssmask(i,j,bi,bj) = 0. _d 0
232     else
233     sssmask(i,j,bi,bj) = 1. _d 0
234     endif
235     sssdat(i,j,bi,bj) = 0. _d 0
236     #endif
237     enddo
238     enddo
239     enddo
240     enddo
241    
242     c-- Initialise the "global" parts of the cost function.
243     _BEGIN_MASTER( mythid )
244     objf_obcsvol = 0. _d 0
245     objf_hmean = 0. _d 0
246     num_obcsvol = 0. _d 0
247     num_hmean = 0. _d 0
248     _END_MASTER( mythid )
249    
250     _BARRIER
251    
252     return
253     end
254    

  ViewVC Help
Powered by ViewVC 1.1.22