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

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

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


Revision 1.5 - (hide annotations) (download)
Mon Mar 28 23:49:49 2005 UTC (19 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57f_post, checkpoint57g_post, checkpoint57g_pre, checkpoint57f_pre
Changes since 1.4: +13 -12 lines
Adding counters to cost terms.

1 heimbach 1.5 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_theta.F,v 1.4 2004/10/11 16:38:53 heimbach Exp $
2 heimbach 1.1
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_Theta(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_Theta
14     c ==================================================================
15     c
16     c o Evaluate cost function contribution of temperature.
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 adtbar file
28     c
29     c ==================================================================
30     c SUBROUTINE cost_Theta
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     integer bi,bj
57     integer i,j,k
58     integer itlo,ithi
59     integer jtlo,jthi
60     integer jmin,jmax
61     integer imin,imax
62     integer irec
63     integer levmon
64     integer levoff
65     integer iltheta
66    
67     _RL fctile
68     _RL fcthread
69    
70     _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
71     _RL spval
72 heimbach 1.5 _RL spmax
73 heimbach 1.1
74     character*(80) fnametheta
75    
76     logical doglobalread
77     logical ladinit
78    
79     character*(MAX_LEN_MBUF) msgbuf
80     #ifdef GENERIC_BAR_MONTH
81 heimbach 1.4 integer mrec, nyears, iyear
82     #endif
83 heimbach 1.1 c == external functions ==
84    
85     integer ilnblnk
86     external ilnblnk
87    
88     c == end of interface ==
89    
90     jtlo = mybylo(mythid)
91     jthi = mybyhi(mythid)
92     itlo = mybxlo(mythid)
93     ithi = mybxhi(mythid)
94     jmin = 1
95     jmax = sny
96     imin = 1
97     imax = snx
98    
99 heimbach 1.4 spval = -1.8
100 heimbach 1.5 spmax = 40.
101 heimbach 1.1
102     c-- Read tiled data.
103     doglobalread = .false.
104     ladinit = .false.
105    
106     #ifdef ALLOW_THETA_COST_CONTRIBUTION
107    
108     if (optimcycle .ge. 0) then
109     iltheta = ilnblnk( tbarfile )
110     write(fnametheta(1:80),'(2a,i10.10)')
111     & tbarfile(1:iltheta),'.',optimcycle
112     endif
113    
114     fcthread = 0. _d 0
115    
116     #ifdef GENERIC_BAR_MONTH
117     c-- Loop over month
118 heimbach 1.4 do irec = 1,12
119 heimbach 1.1 nyears=int((nmonsrec-irec)/12)+1
120     if(nyears.gt.0) then
121     do iyear=1,nyears
122     mrec=irec+(iyear-1)*12
123     c-- Read time averages and the monthly mean data.
124     call active_read_xyz( fnametheta, tbar, mrec,
125     & doglobalread, ladinit,
126     & optimcycle, mythid,
127     & xx_tbar_mean_dummy )
128     do bj = jtlo,jthi
129     do bi = itlo,ithi
130     do k = 1,nr
131     do j = jmin,jmax
132     do i = imin,imax
133     if(iyear.eq.1) then
134     tbar_gen(i,j,k,bi,bj) =tbar(i,j,k,bi,bj)
135     elseif(iyear.eq.nyears) then
136     tbar(i,j,k,bi,bj) =(tbar_gen(i,j,k,bi,bj)
137     $ +tbar(i,j,k,bi,bj))/float(nyears)
138     else
139     tbar_gen(i,j,k,bi,bj) =tbar_gen(i,j,k,bi,bj)
140     $ +tbar(i,j,k,bi,bj)
141     endif
142     enddo
143     enddo
144     enddo
145     enddo
146     enddo
147     enddo
148     #else
149     c-- Loop over records.
150     do irec = 1,nmonsrec
151    
152     c-- Read time averages and the monthly mean data.
153     call active_read_xyz( fnametheta, tbar, irec,
154     & doglobalread, ladinit,
155     & optimcycle, mythid,
156     & xx_tbar_mean_dummy )
157     #endif
158     c-- Determine the month to be read.
159     levoff = mod(modelstartdate(1)/100,100)
160     levmon = (irec-1) + levoff
161     levmon = mod(levmon-1,12)+1
162    
163     call mdsreadfield( tdatfile, cost_iprec, cost_yftype,
164     & nr, tdat, levmon, mythid)
165    
166     do bj = jtlo,jthi
167     do bi = itlo,ithi
168    
169     c-- Loop over the model layers
170     fctile = 0. _d 0
171     do k = 1,nr
172    
173     c-- Determine the mask on weights
174     do j = jmin,jmax
175     do i = imin,imax
176 heimbach 1.5 cmask(i,j) = cosphi(i,j,bi,bj)
177 heimbach 1.1 if (tdat(i,j,k,bi,bj) .eq. 0.) then
178     cmask(i,j) = 0. _d 0
179 heimbach 1.5 else if (tdat(i,j,k,bi,bj) .lt. spval) then
180     cmask(i,j) = 0. _d 0
181     else if (tdat(i,j,k,bi,bj) .gt. spmax) then
182 heimbach 1.1 cmask(i,j) = 0. _d 0
183     endif
184    
185     cph(
186     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
187     cph below statement could be replaced by following
188     cph to make it independnet of Nr:
189     cph
190     cph if ( rC(K) .GT. -1000. ) then
191     cph)
192     enddo
193     enddo
194    
195     c-- Compute model data misfit and cost function term for
196     c the temperature field.
197     do j = jmin,jmax
198     do i = imin,imax
199 heimbach 1.5 if ( _hFacC(i,j,k,bi,bj) .ne. 0. .AND.
200     & _hFacC(i,j,13,bi,bj) .ne. 0. ) then
201 heimbach 1.1 fctile = fctile +
202 heimbach 1.5 & (wtheta(k,bi,bj)*cmask(i,j)*
203 heimbach 1.1 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
204 heimbach 1.5 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
205     if ( wtheta(k,bi,bj)*cmask(i,j) .ne. 0. )
206     & num_temp(bi,bj) = num_temp(bi,bj) + 1. _d 0
207 heimbach 1.1 endif
208     enddo
209     enddo
210    
211     enddo
212     c-- End of loop over layers.
213    
214     fcthread = fcthread + fctile
215     objf_temp(bi,bj) = objf_temp(bi,bj) + fctile
216    
217     #ifdef ECCO_VERBOSE
218     c-- Print cost function for each tile in each thread.
219     write(msgbuf,'(a)') ' '
220     call print_message( msgbuf, standardmessageunit,
221     & SQUEEZE_RIGHT , mythid)
222     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
223     & ' cost_Theta: irec,bi,bj = ',irec,bi,bj
224     call print_message( msgbuf, standardmessageunit,
225     & SQUEEZE_RIGHT , mythid)
226     write(msgbuf,'(a,d22.15)')
227     & ' cost function (temperature) = ',
228     & fctile
229     call print_message( msgbuf, standardmessageunit,
230     & SQUEEZE_RIGHT , mythid)
231     write(msgbuf,'(a)') ' '
232     call print_message( msgbuf, standardmessageunit,
233     & SQUEEZE_RIGHT , mythid)
234     #endif
235    
236     enddo
237     enddo
238    
239     #ifdef ECCO_VERBOSE
240     c-- Print cost function for all tiles.
241     _GLOBAL_SUM_R8( fcthread , myThid )
242     write(msgbuf,'(a)') ' '
243     call print_message( msgbuf, standardmessageunit,
244     & SQUEEZE_RIGHT , mythid)
245     write(msgbuf,'(a,i8.8)')
246     & ' cost_Theta: irec = ',irec
247     call print_message( msgbuf, standardmessageunit,
248     & SQUEEZE_RIGHT , mythid)
249     write(msgbuf,'(a,a,d22.15)')
250     & ' global cost function value',
251     & ' (temperature) = ',fcthread
252     call print_message( msgbuf, standardmessageunit,
253     & SQUEEZE_RIGHT , mythid)
254     write(msgbuf,'(a)') ' '
255     call print_message( msgbuf, standardmessageunit,
256     & SQUEEZE_RIGHT , mythid)
257     #endif
258    
259     #ifdef GENERIC_BAR_MONTH
260     endif
261     #endif
262     enddo
263     c-- End of loop over records.
264    
265 heimbach 1.4 #else
266     c-- Do not enter the calculation of the temperature contribution to
267     c-- the final cost function.
268    
269     #ifdef ECCO_VERBOSE
270     _BEGIN_MASTER( mythid )
271     write(msgbuf,'(a)') ' '
272     call print_message( msgbuf, standardmessageunit,
273     & SQUEEZE_RIGHT , mythid)
274     write(msgbuf,'(a,a)')
275     & ' cost_Theta: no contribution of temperature field ',
276     & 'to cost function.'
277     call print_message( msgbuf, standardmessageunit,
278     & SQUEEZE_RIGHT , mythid)
279     write(msgbuf,'(a,a,i9.8)')
280     & ' cost_Theta: number of records that would have',
281     & ' been processed: ',nmonsrec
282     call print_message( msgbuf, standardmessageunit,
283     & SQUEEZE_RIGHT , mythid)
284     write(msgbuf,'(a)') ' '
285     call print_message( msgbuf, standardmessageunit,
286     & SQUEEZE_RIGHT , mythid)
287     _END_MASTER( mythid )
288     #endif
289    
290 heimbach 1.1 #endif
291    
292     return
293     end
294    

  ViewVC Help
Powered by ViewVC 1.1.22