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

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

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


Revision 1.1 - (hide annotations) (download)
Thu Nov 6 22:10:08 2003 UTC (20 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: branch-netcdf, checkpoint52d_pre, checkpoint52b_pre, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint52c_post, ecco_c52_e35, checkpoint52a_pre, checkpoint51u_post
Branch point for: netcdf-sm0
o merging from ecco-branch
o pkg/ecco now containes ecco-specific part of cost function
o top level routines the_main_loop, forward_step
  supersede those in model/src/
  previous input data.cost now in data.ecco
  (new namelist ecco_cost_nml)

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_salt.F,v 1.1.2.4 2003/06/19 15:21:16 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_Salt(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_Salt
14     c ==================================================================
15     c
16     c o Evaluate cost function contribution of salinity.
17     c
18     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
19     c
20     c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
21     c
22     c - Restructured the code in order to create a package
23     c for the MITgcmUV.
24     c
25     c changed: Patrick Heimbach heimbach@mit.edu 27-May-2000
26     c
27     c - set ladinit to .true. to initialise adsbar file
28     c
29     c ==================================================================
30     c SUBROUTINE cost_Salt
31     c ==================================================================
32    
33     implicit none
34    
35     c == global variables ==
36    
37     #include "EEPARAMS.h"
38     #include "SIZE.h"
39     #include "GRID.h"
40     #include "DYNVARS.h"
41    
42     #include "cal.h"
43     #include "ecco_cost.h"
44     #include "ctrl.h"
45     #include "ctrl_dummy.h"
46     #include "optim.h"
47    
48     c == routine arguments ==
49    
50     integer myiter
51     _RL mytime
52     integer mythid
53    
54     c == local variables ==
55    
56     _RS one_rs
57     parameter( one_rs = 1. )
58    
59     integer bi,bj
60     integer i,j,k
61     integer itlo,ithi
62     integer jtlo,jthi
63     integer jmin,jmax
64     integer imin,imax
65     integer irec
66     integer levmon
67     integer levoff
68     integer ilsalt
69    
70     _RL fctile
71     _RL fcthread
72    
73     _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
74     _RL spval
75    
76     character*(80) fnamesalt
77    
78     logical doglobalread
79     logical ladinit
80    
81     character*(MAX_LEN_MBUF) msgbuf
82    
83     #ifdef GENERIC_BAR_MONTH
84     integer mrec, nyears, iyear
85     #endif
86    
87     c == external functions ==
88    
89     integer ilnblnk
90     external ilnblnk
91    
92     c == end of interface ==
93    
94     jtlo = mybylo(mythid)
95     jthi = mybyhi(mythid)
96     itlo = mybxlo(mythid)
97     ithi = mybxhi(mythid)
98     jmin = 1
99     jmax = sny
100     imin = 1
101     imax = snx
102    
103     spval = -9990.
104    
105     c-- Read tiled data.
106     doglobalread = .false.
107     ladinit = .false.
108    
109     #ifdef ALLOW_SALT_COST_CONTRIBUTION
110    
111     #ifdef ECCO_VERBOSE
112     _BEGIN_MASTER( mythid )
113     write(msgbuf,'(a)') ' '
114     call print_message( msgbuf, standardmessageunit,
115     & SQUEEZE_RIGHT , mythid)
116     write(msgbuf,'(a,i8.8)')
117     & ' cost_Salt: number of records to process = ',nmonsrec
118     call print_message( msgbuf, standardmessageunit,
119     & SQUEEZE_RIGHT , mythid)
120     write(msgbuf,'(a)') ' '
121     call print_message( msgbuf, standardmessageunit,
122     & SQUEEZE_RIGHT , mythid)
123     _END_MASTER( mythid )
124     #endif
125    
126     if (optimcycle .ge. 0) then
127     ilsalt = ilnblnk( sbarfile )
128     write(fnamesalt(1:80),'(2a,i10.10)')
129     & sbarfile(1:ilsalt),'.',optimcycle
130     endif
131    
132     fcthread = 0. _d 0
133    
134     #ifdef GENERIC_BAR_MONTH
135    
136     c-- Loop over month
137     do irec = 1,12
138     nyears=int((nmonsrec-irec)/12)+1
139     if(nyears.gt.0) then
140     do iyear=1,nyears
141     mrec=irec+(iyear-1)*12
142     c-- Read time averages and the monthly mean data.
143     call active_read_xyz( fnamesalt, sbar, mrec,
144     & doglobalread, ladinit,
145     & optimcycle, mythid,
146     & xx_sbar_mean_dummy )
147     do bj = jtlo,jthi
148     do bi = itlo,ithi
149     do k = 1,nr
150     do j = jmin,jmax
151     do i = imin,imax
152     if(iyear.eq.1) then
153     sbar_gen(i,j,k,bi,bj) =sbar(i,j,k,bi,bj)
154     elseif(iyear.eq.nyears) then
155     sbar(i,j,k,bi,bj) =(sbar_gen(i,j,k,bi,bj)
156     $ +sbar(i,j,k,bi,bj))/float(nyears)
157     else
158     sbar_gen(i,j,k,bi,bj) =sbar_gen(i,j,k,bi,bj)
159     $ +sbar(i,j,k,bi,bj)
160     endif
161     enddo
162     enddo
163     enddo
164     enddo
165     enddo
166     enddo
167    
168     #else
169    
170     c-- Loop over records.
171     do irec = 1,nmonsrec
172    
173     c-- Read time averages and the monthly mean data.
174     call active_read_xyz( fnamesalt, sbar, irec,
175     & doglobalread, ladinit,
176     & optimcycle, mythid,
177     & xx_sbar_mean_dummy )
178    
179     #endif
180    
181     c-- Determine the month to be read.
182     levoff = mod(modelstartdate(1)/100,100)
183     levmon = (irec-1) + levoff
184     levmon = mod(levmon-1,12)+1
185    
186     call mdsreadfield( sdatfile, cost_iprec, cost_yftype,
187     & nr, sdat, levmon, mythid)
188    
189     do bj = jtlo,jthi
190     do bi = itlo,ithi
191    
192     c-- Loop over the model layers
193     fctile = 0. _d 0
194     do k = 1,nr
195    
196     c-- Determine the mask or weights
197     do j = jmin,jmax
198     do i = imin,imax
199     cmask(i,j) = 1. _d 0
200     if (sdat(i,j,k,bi,bj) .eq. 0.) then
201     cmask(i,j) = 0. _d 0
202     endif
203     if (sdat(i,j,k,bi,bj) .lt. spval) then
204     cmask(i,j) = 0. _d 0
205     endif
206    
207     cph(
208     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
209     cph below statement could be replaced by following
210     cph to make it independnet of Nr:
211     cph
212     cph if ( rC(K) .GT. -1000. ) then
213     cph)
214     c set cmask=0 in areas shallower than 1000m
215     if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
216     cmask(i,j) = 0. _d 0
217     endif
218    
219     enddo
220     enddo
221    
222     c-- Compute model data misfit and cost function term for
223     c the salinity field.
224     do j = jmin,jmax
225     do i = imin,imax
226     if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
227     fctile = fctile +
228     & (wsalt(k,bi,bj)*cosphi(i,j,bi,bj)*cmask(i,j)*
229     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj))*
230     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj)) )
231     endif
232     enddo
233     enddo
234    
235     enddo
236     c-- End of loop over layers.
237    
238     fcthread = fcthread + fctile
239     objf_salt(bi,bj) = objf_salt(bi,bj) + fctile
240    
241     #ifdef ECCO_VERBOSE
242     c-- Print cost function for each tile in each thread.
243     write(msgbuf,'(a)') ' '
244     call print_message( msgbuf, standardmessageunit,
245     & SQUEEZE_RIGHT , mythid)
246     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
247     & ' cost_Salt: irec,bi,bj = ',irec,bi,bj
248     call print_message( msgbuf, standardmessageunit,
249     & SQUEEZE_RIGHT , mythid)
250     write(msgbuf,'(a,d22.15)')
251     & ' cost function (salinity) = ',
252     & fctile
253     call print_message( msgbuf, standardmessageunit,
254     & SQUEEZE_RIGHT , mythid)
255     write(msgbuf,'(a)') ' '
256     call print_message( msgbuf, standardmessageunit,
257     & SQUEEZE_RIGHT , mythid)
258     #endif
259    
260     enddo
261     enddo
262    
263     #ifdef ECCO_VERBOSE
264     c-- Print cost function for all tiles.
265     _GLOBAL_SUM_R8( fcthread , myThid )
266     write(msgbuf,'(a)') ' '
267     call print_message( msgbuf, standardmessageunit,
268     & SQUEEZE_RIGHT , mythid)
269     write(msgbuf,'(a,i8.8)')
270     & ' cost_Salt: irec = ',irec
271     call print_message( msgbuf, standardmessageunit,
272     & SQUEEZE_RIGHT , mythid)
273     write(msgbuf,'(a,a,d22.15)')
274     & ' global cost function value',
275     & ' (salinity) = ',fcthread
276     call print_message( msgbuf, standardmessageunit,
277     & SQUEEZE_RIGHT , mythid)
278     write(msgbuf,'(a)') ' '
279     call print_message( msgbuf, standardmessageunit,
280     & SQUEEZE_RIGHT , mythid)
281     #endif
282    
283     #ifdef GENERIC_BAR_MONTH
284     endif
285     #endif
286    
287     enddo
288     c-- End of loop over records.
289    
290     #endif
291    
292     return
293     end
294    

  ViewVC Help
Powered by ViewVC 1.1.22