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

Annotation of /MITgcm/pkg/ecco/cost_ctdsclim.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:07 2003 UTC (20 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: branch-netcdf, checkpoint52b_pre, checkpoint52, checkpoint52a_post, checkpoint52b_post, checkpoint52c_post, ecco_c52_e35, checkpoint52a_pre, checkpoint51u_post
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_ctdsclim.F,v 1.1.2.1 2003/06/19 15:21:16 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_ctdsclim(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_Ctdsclim
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_Ctdsclim
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 ilctdsclim
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     c == external functions ==
87    
88     integer ilnblnk
89     external ilnblnk
90    
91     c == end of interface ==
92    
93     jtlo = mybylo(mythid)
94     jthi = mybyhi(mythid)
95     itlo = mybxlo(mythid)
96     ithi = mybxhi(mythid)
97     jmin = 1
98     jmax = sny
99     imin = 1
100     imax = snx
101    
102     spval = -9990.
103    
104     c-- Read tiled data.
105     doglobalread = .false.
106     ladinit = .false.
107    
108     #ifdef ALLOW_CTDSCLIM_COST_CONTRIBUTION
109    
110     #ifdef ECCO_VERBOSE
111     _BEGIN_MASTER( mythid )
112     write(msgbuf,'(a)') ' '
113     call print_message( msgbuf, standardmessageunit,
114     & SQUEEZE_RIGHT , mythid)
115     write(msgbuf,'(a,i8.8)')
116     & ' cost_Ctdsclim: number of records to process = ',nmonsrec
117     call print_message( msgbuf, standardmessageunit,
118     & SQUEEZE_RIGHT , mythid)
119     write(msgbuf,'(a)') ' '
120     call print_message( msgbuf, standardmessageunit,
121     & SQUEEZE_RIGHT , mythid)
122     _END_MASTER( mythid )
123     #endif
124    
125     if (optimcycle .ge. 0) then
126     ilctdsclim = ilnblnk( sbarfile )
127     write(fnamesalt(1:80),'(2a,i10.10)')
128     & sbarfile(1:ilctdsclim),'.',optimcycle
129     else
130     print*
131     print*,' cost_Ctdsclim: optimcycle has a wrong value.'
132     print*,' optimcycle = ',optimcycle
133     print*
134     stop ' ... stopped in cost_Ctdsclim.'
135     endif
136    
137     fcthread = 0. _d 0
138    
139     #ifdef GENERIC_BAR_MONTH
140     c-- Loop over month
141     do irec = 1,12
142     nyears=int((nmonsrec-irec)/12)+1
143     if(nyears.gt.0) then
144     do iyear=1,nyears
145     mrec=irec+(iyear-1)*12
146     c-- Read time averages and the monthly mean data.
147     call active_read_xyz( fnamesalt, sbar, mrec,
148     & doglobalread, ladinit,
149     & optimcycle, mythid,
150     & xx_sbar_mean_dummy )
151     do bj = jtlo,jthi
152     do bi = itlo,ithi
153     do k = 1,nr
154     do j = jmin,jmax
155     do i = imin,imax
156     if(iyear.eq.1) then
157     sbar_gen(i,j,k,bi,bj) =sbar(i,j,k,bi,bj)
158     elseif(iyear.eq.nyears) then
159     sbar(i,j,k,bi,bj) =(sbar_gen(i,j,k,bi,bj)
160     $ +sbar(i,j,k,bi,bj))/float(nyears)
161     else
162     sbar_gen(i,j,k,bi,bj) =sbar_gen(i,j,k,bi,bj)
163     $ +sbar(i,j,k,bi,bj)
164     endif
165     enddo
166     enddo
167     enddo
168     enddo
169     enddo
170     enddo
171     #else
172     c-- Loop over records.
173     do irec = 1,nmonsrec
174    
175     c-- Read time averages and the monthly mean data.
176     call active_read_xyz( fnamesalt, sbar, irec,
177     & doglobalread, ladinit,
178     & optimcycle, mythid,
179     & xx_sbar_mean_dummy )
180     #endif
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( ctdsclimfile, 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     & (wsalt2(i,j,k,bi,bj)*cosphi(i,j,bi,bj)*
229     & cmask(i,j)*
230     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj))*
231     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj)) )
232     endif
233     enddo
234     enddo
235    
236     enddo
237     c-- End of loop over layers.
238    
239     fcthread = fcthread + fctile
240     objf_ctdsclim(bi,bj) = objf_ctdsclim(bi,bj) + fctile
241    
242     #ifdef ECCO_VERBOSE
243     c-- Print cost function for each tile in each thread.
244     write(msgbuf,'(a)') ' '
245     call print_message( msgbuf, standardmessageunit,
246     & SQUEEZE_RIGHT , mythid)
247     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
248     & ' cost_Ctdsclim: irec,bi,bj = ',irec,bi,bj
249     call print_message( msgbuf, standardmessageunit,
250     & SQUEEZE_RIGHT , mythid)
251     write(msgbuf,'(a,d22.15)')
252     & ' cost function (salinity) = ',
253     & fctile
254     call print_message( msgbuf, standardmessageunit,
255     & SQUEEZE_RIGHT , mythid)
256     write(msgbuf,'(a)') ' '
257     call print_message( msgbuf, standardmessageunit,
258     & SQUEEZE_RIGHT , mythid)
259     #endif
260    
261     enddo
262     enddo
263    
264     #ifdef ECCO_VERBOSE
265     c-- Print cost function for all tiles.
266     _GLOBAL_SUM_R8( fcthread , myThid )
267     write(msgbuf,'(a)') ' '
268     call print_message( msgbuf, standardmessageunit,
269     & SQUEEZE_RIGHT , mythid)
270     write(msgbuf,'(a,i8.8)')
271     & ' cost_Ctdsclim: irec = ',irec
272     call print_message( msgbuf, standardmessageunit,
273     & SQUEEZE_RIGHT , mythid)
274     write(msgbuf,'(a,a,d22.15)')
275     & ' global cost function value',
276     & ' (salinity) = ',fcthread
277     call print_message( msgbuf, standardmessageunit,
278     & SQUEEZE_RIGHT , mythid)
279     write(msgbuf,'(a)') ' '
280     call print_message( msgbuf, standardmessageunit,
281     & SQUEEZE_RIGHT , mythid)
282     #endif
283    
284     #ifdef GENERIC_BAR_MONTH
285     endif
286     #endif
287     enddo
288     c-- End of loop over records.
289    
290     #else
291     c-- Do not enter the calculation of the salinity contribution to
292     c-- the final cost function.
293    
294     _BEGIN_MASTER( mythid )
295     write(msgbuf,'(a)') ' '
296     call print_message( msgbuf, standardmessageunit,
297     & SQUEEZE_RIGHT , mythid)
298     write(msgbuf,'(a,a)')
299     & ' cost_Ctdsclim: no contribution of salinity field ',
300     & 'to cost function.'
301     call print_message( msgbuf, standardmessageunit,
302     & SQUEEZE_RIGHT , mythid)
303     write(msgbuf,'(a,a,i9.8)')
304     & ' cost_Ctdsclim: number of records that would have',
305     & ' been processed: ',nmonsrec
306     call print_message( msgbuf, standardmessageunit,
307     & SQUEEZE_RIGHT , mythid)
308     write(msgbuf,'(a)') ' '
309     call print_message( msgbuf, standardmessageunit,
310     & SQUEEZE_RIGHT , mythid)
311     _END_MASTER( mythid )
312     #endif
313    
314     return
315     end
316    

  ViewVC Help
Powered by ViewVC 1.1.22