/[MITgcm]/MITgcm_contrib/heimbach/SO4x2/code_ad_nodiva/cost_theta.F
ViewVC logotype

Annotation of /MITgcm_contrib/heimbach/SO4x2/code_ad_nodiva/cost_theta.F

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


Revision 1.1 - (hide annotations) (download)
Thu Jan 26 06:27:12 2006 UTC (19 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
Setup for Southern Ocean on coarse grid. Test-bed for high-res. adjoint.

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_theta.F,v 1.8 2005/10/15 18:27:32 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_theta( myiter, mytime, mythid )
7    
8     c ==================================================================
9     c SUBROUTINE cost_theta
10     c ==================================================================
11     c
12     c o Evaluate cost function contribution of temperature.
13     c
14     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
15     c
16     c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
17     c
18     c - Restructured the code in order to create a package
19     c for the MITgcmUV.
20     c
21     c changed: Patrick Heimbach heimbach@mit.edu 27-May-2000
22     c
23     c - set ladinit to .true. to initialise adtbar file
24     c
25     c ==================================================================
26     c SUBROUTINE cost_theta
27     c ==================================================================
28    
29     implicit none
30    
31     c == global variables ==
32    
33     #include "EEPARAMS.h"
34     #include "SIZE.h"
35     #include "PARAMS.h"
36     #include "GRID.h"
37     #include "DYNVARS.h"
38    
39     #include "cal.h"
40     #include "ecco_cost.h"
41     #include "ctrl.h"
42     #include "ctrl_dummy.h"
43     #include "optim.h"
44     #ifdef ALLOW_OBCS
45     #include "OBCS.h"
46     #endif
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, irectmp
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     _RL spmax
73    
74     character*(80) fnametheta
75    
76     logical doglobalread
77     logical ladinit
78    
79     character*(MAX_LEN_MBUF) msgbuf
80     #ifdef GENERIC_BAR_MONTH
81     integer mrec, nyears, iyear
82     #endif
83    
84     _RL diagnosfld3d(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
85    
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 = -1.8
103     spmax = 40.
104    
105     c-- Read tiled data.
106     doglobalread = .false.
107     ladinit = .false.
108    
109     #ifdef ALLOW_THETA_COST_CONTRIBUTION
110    
111     if (optimcycle .ge. 0) then
112     iltheta = ilnblnk( tbarfile )
113     write(fnametheta(1:80),'(2a,i10.10)')
114     & tbarfile(1:iltheta),'.',optimcycle
115     endif
116    
117     fcthread = 0. _d 0
118    
119     #ifdef GENERIC_BAR_MONTH
120     c-- Loop over month
121     do irec = 1,min(nmonsrec,12)
122     nyears=int((nmonsrec-irec)/12)+1
123     do iyear=1,nyears
124     mrec=irec+(iyear-1)*12
125     irectmp=mrec
126     c-- Read time averages and the monthly mean data.
127     call active_read_xyz( fnametheta, tbar, mrec,
128     & doglobalread, ladinit,
129     & optimcycle, mythid,
130     & xx_tbar_mean_dummy )
131     do bj = jtlo,jthi
132     do bi = itlo,ithi
133     do k = 1,nr
134     do j = jmin,jmax
135     do i = imin,imax
136     if(iyear.eq.1) then
137     tbar_gen(i,j,k,bi,bj) =tbar(i,j,k,bi,bj)
138     elseif(iyear.eq.nyears) then
139     tbar(i,j,k,bi,bj) =(tbar_gen(i,j,k,bi,bj)
140     $ +tbar(i,j,k,bi,bj))/float(nyears)
141     else
142     tbar_gen(i,j,k,bi,bj) =tbar_gen(i,j,k,bi,bj)
143     $ +tbar(i,j,k,bi,bj)
144     endif
145     enddo
146     enddo
147     enddo
148     enddo
149     enddo
150     enddo
151     #else
152     c-- Loop over records.
153     do irec = 1,nmonsrec
154    
155     irectmp = irec
156     c-- Read time averages and the monthly mean data.
157     call active_read_xyz( fnametheta, tbar, irec,
158     & doglobalread, ladinit,
159     & optimcycle, mythid,
160     & xx_tbar_mean_dummy )
161     #endif
162     c-- Determine the month to be read.
163     levoff = mod(modelstartdate(1)/100,100)
164     levmon = (irectmp-1) + levoff
165     levmon = mod(levmon-1,12)+1
166    
167     call mdsreadfield( tdatfile, cost_iprec, cost_yftype,
168     & nr, tdat, levmon, mythid)
169    
170     do bj = jtlo,jthi
171     do bi = itlo,ithi
172    
173     c-- Loop over the model layers
174     fctile = 0. _d 0
175     do k = 1,nr
176    
177     c-- Determine the mask on weights
178     do j = jmin,jmax
179     do i = imin,imax
180     cmask(i,j) = cosphi(i,j,bi,bj)
181     if (tdat(i,j,k,bi,bj) .eq. 0.) then
182     cmask(i,j) = 0. _d 0
183     else if (tdat(i,j,k,bi,bj) .lt. spval) then
184     cmask(i,j) = 0. _d 0
185     else if (tdat(i,j,k,bi,bj) .gt. spmax) then
186     cmask(i,j) = 0. _d 0
187     #ifdef ALLOW_OBCS_NORTH
188     else if (OB_Jn(i,bi,bj).EQ.j) THEN
189     cmask(i,j) = 0. _d 0
190     #endif
191     endif
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     if ( _hFacC(i,j,k,bi,bj) .ne. 0. ) then
200     fctile = fctile +
201     & (wthetaLev(i,j,k,bi,bj)*cmask(i,j)*
202     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
203     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
204     if ( wthetaLev(i,j,k,bi,bj)*cmask(i,j) .ne. 0. )
205     & num_temp(bi,bj) = num_temp(bi,bj) + 1. _d 0
206     diagnosfld3d(i,j,k,bi,bj) =
207     & (wthetaLev(i,j,k,bi,bj)*cmask(i,j)*
208     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
209     & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
210     else
211     diagnosfld3d(i,j,k,bi,bj) = 0.
212     endif
213     enddo
214     enddo
215    
216     enddo
217     c-- End of loop over layers.
218    
219     call mdswritefield( 'DiagnosCost_ClimTheta',
220     & writeBinaryPrec, globalfiles, 'RL', Nr,
221     & diagnosfld3d, irec, optimcycle, mythid )
222    
223     fcthread = fcthread + fctile
224     objf_temp(bi,bj) = objf_temp(bi,bj) + fctile
225    
226     enddo
227     enddo
228    
229     enddo
230     c-- End of loop over records.
231    
232     #endif
233    
234     return
235     end
236    

  ViewVC Help
Powered by ViewVC 1.1.22