/[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.2 - (hide annotations) (download)
Sat Dec 20 20:11:14 2003 UTC (20 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52e_pre, checkpoint52e_post, hrcube_1, checkpoint52f_post, checkpoint52f_pre
Changes since 1.1: +11 -3 lines
oh mann, die lieben verwandten...

1 heimbach 1.2 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_theta.F,v 1.1 2003/11/06 22:10:08 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     _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 iltheta
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) fnametheta
77    
78     logical doglobalread
79     logical ladinit
80    
81     character*(MAX_LEN_MBUF) msgbuf
82    
83     #ifdef GENERIC_BAR_MONTH
84 heimbach 1.2 integer mrec, nyears, iyear, tmpmon
85 heimbach 1.1 #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_THETA_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_Theta: 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     iltheta = ilnblnk( tbarfile )
128     write(fnametheta(1:80),'(2a,i10.10)')
129     & tbarfile(1:iltheta),'.',optimcycle
130     endif
131    
132     fcthread = 0. _d 0
133    
134     #ifdef GENERIC_BAR_MONTH
135    
136     c-- Loop over month
137 heimbach 1.2 if (nmonsrec.GT.12) then
138     tmpmon = 12
139     else
140     tmpmon = nmonsrec
141     endif
142     do irec = 1,tmpmon
143 heimbach 1.1 nyears=int((nmonsrec-irec)/12)+1
144     if(nyears.gt.0) then
145     do iyear=1,nyears
146     mrec=irec+(iyear-1)*12
147 heimbach 1.2 print *, 'ph-rec irec, iyear, mrec ',
148     & irec, iyear, mrec
149 heimbach 1.1 c-- Read time averages and the monthly mean data.
150     call active_read_xyz( fnametheta, tbar, mrec,
151     & doglobalread, ladinit,
152     & optimcycle, mythid,
153     & xx_tbar_mean_dummy )
154     do bj = jtlo,jthi
155     do bi = itlo,ithi
156     do k = 1,nr
157     do j = jmin,jmax
158     do i = imin,imax
159     if(iyear.eq.1) then
160     tbar_gen(i,j,k,bi,bj) =tbar(i,j,k,bi,bj)
161     elseif(iyear.eq.nyears) then
162     tbar(i,j,k,bi,bj) =(tbar_gen(i,j,k,bi,bj)
163     $ +tbar(i,j,k,bi,bj))/float(nyears)
164     else
165     tbar_gen(i,j,k,bi,bj) =tbar_gen(i,j,k,bi,bj)
166     $ +tbar(i,j,k,bi,bj)
167     endif
168     enddo
169     enddo
170     enddo
171     enddo
172     enddo
173     enddo
174    
175     #else
176    
177     c-- Loop over records.
178     do irec = 1,nmonsrec
179    
180     c-- Read time averages and the monthly mean data.
181     call active_read_xyz( fnametheta, tbar, irec,
182     & doglobalread, ladinit,
183     & optimcycle, mythid,
184     & xx_tbar_mean_dummy )
185    
186     #endif
187    
188     c-- Determine the month to be read.
189     levoff = mod(modelstartdate(1)/100,100)
190     levmon = (irec-1) + levoff
191     levmon = mod(levmon-1,12)+1
192    
193 heimbach 1.2 print *, 'ph-rec irec, levmon ', irec, levmon
194 heimbach 1.1 call mdsreadfield( tdatfile, cost_iprec, cost_yftype,
195     & nr, tdat, levmon, mythid)
196    
197     do bj = jtlo,jthi
198     do bi = itlo,ithi
199    
200     c-- Loop over the model layers
201     fctile = 0. _d 0
202     do k = 1,nr
203    
204     c-- Determine the mask on weights
205     do j = jmin,jmax
206     do i = imin,imax
207     cmask(i,j) = 1. _d 0
208     if (tdat(i,j,k,bi,bj) .eq. 0.) then
209     cmask(i,j) = 0. _d 0
210     endif
211    
212     if (tdat(i,j,k,bi,bj) .lt. spval) then
213     cmask(i,j) = 0. _d 0
214     endif
215    
216     cph(
217     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
218     cph below statement could be replaced by following
219     cph to make it independnet of Nr:
220     cph
221     cph if ( rC(K) .GT. -1000. ) then
222     cph)
223     c set cmask=0 in areas shallower than 1000m
224     if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
225     cmask(i,j) = 0. _d 0
226     endif
227     enddo
228     enddo
229    
230     c-- Compute model data misfit and cost function term for
231     c the temperature field.
232     do j = jmin,jmax
233     do i = imin,imax
234     if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
235     fctile = fctile +
236     & (wtheta(k,bi,bj)*cosphi(i,j,bi,bj)*cmask(i,j)*
237     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
238     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
239     endif
240     enddo
241     enddo
242    
243     enddo
244     c-- End of loop over layers.
245    
246     fcthread = fcthread + fctile
247     objf_temp(bi,bj) = objf_temp(bi,bj) + fctile
248    
249     #ifdef ECCO_VERBOSE
250     c-- Print cost function for each tile in each thread.
251     write(msgbuf,'(a)') ' '
252     call print_message( msgbuf, standardmessageunit,
253     & SQUEEZE_RIGHT , mythid)
254     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
255     & ' cost_Theta: irec,bi,bj = ',irec,bi,bj
256     call print_message( msgbuf, standardmessageunit,
257     & SQUEEZE_RIGHT , mythid)
258     write(msgbuf,'(a,d22.15)')
259     & ' cost function (temperature) = ',
260     & fctile
261     call print_message( msgbuf, standardmessageunit,
262     & SQUEEZE_RIGHT , mythid)
263     write(msgbuf,'(a)') ' '
264     call print_message( msgbuf, standardmessageunit,
265     & SQUEEZE_RIGHT , mythid)
266     #endif
267    
268     enddo
269     enddo
270    
271     #ifdef ECCO_VERBOSE
272     c-- Print cost function for all tiles.
273     _GLOBAL_SUM_R8( fcthread , myThid )
274     write(msgbuf,'(a)') ' '
275     call print_message( msgbuf, standardmessageunit,
276     & SQUEEZE_RIGHT , mythid)
277     write(msgbuf,'(a,i8.8)')
278     & ' cost_Theta: irec = ',irec
279     call print_message( msgbuf, standardmessageunit,
280     & SQUEEZE_RIGHT , mythid)
281     write(msgbuf,'(a,a,d22.15)')
282     & ' global cost function value',
283     & ' (temperature) = ',fcthread
284     call print_message( msgbuf, standardmessageunit,
285     & SQUEEZE_RIGHT , mythid)
286     write(msgbuf,'(a)') ' '
287     call print_message( msgbuf, standardmessageunit,
288     & SQUEEZE_RIGHT , mythid)
289     #endif
290    
291     #ifdef GENERIC_BAR_MONTH
292     endif
293     #endif
294    
295     enddo
296     c-- End of loop over records.
297    
298     #endif
299    
300     return
301     end
302    

  ViewVC Help
Powered by ViewVC 1.1.22