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

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

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


Revision 1.8 - (show annotations) (download)
Sat Oct 15 18:27:32 2005 UTC (18 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58u_post, checkpoint58r_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58w_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint58a_post, checkpoint58i_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.7: +17 -3 lines
Changing to spatially varying weights.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_theta.F,v 1.7 2005/09/02 16:02:11 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
45 c == routine arguments ==
46
47 integer myiter
48 _RL mytime
49 integer mythid
50
51 c == local variables ==
52
53 integer bi,bj
54 integer i,j,k
55 integer itlo,ithi
56 integer jtlo,jthi
57 integer jmin,jmax
58 integer imin,imax
59 integer irec, irectmp
60 integer levmon
61 integer levoff
62 integer iltheta
63
64 _RL fctile
65 _RL fcthread
66
67 _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
68 _RL spval
69 _RL spmax
70
71 character*(80) fnametheta
72
73 logical doglobalread
74 logical ladinit
75
76 character*(MAX_LEN_MBUF) msgbuf
77 #ifdef GENERIC_BAR_MONTH
78 integer mrec, nyears, iyear
79 #endif
80
81 _RL diagnosfld3d(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
82
83 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 spval = -1.8
100 spmax = 40.
101
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 do irec = 1,min(nmonsrec,12)
119 nyears=int((nmonsrec-irec)/12)+1
120 do iyear=1,nyears
121 mrec=irec+(iyear-1)*12
122 irectmp=mrec
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 irectmp = irec
153 c-- Read time averages and the monthly mean data.
154 call active_read_xyz( fnametheta, tbar, irec,
155 & doglobalread, ladinit,
156 & optimcycle, mythid,
157 & xx_tbar_mean_dummy )
158 #endif
159 c-- Determine the month to be read.
160 levoff = mod(modelstartdate(1)/100,100)
161 levmon = (irectmp-1) + levoff
162 levmon = mod(levmon-1,12)+1
163
164 call mdsreadfield( tdatfile, cost_iprec, cost_yftype,
165 & nr, tdat, levmon, mythid)
166
167 do bj = jtlo,jthi
168 do bi = itlo,ithi
169
170 c-- Loop over the model layers
171 fctile = 0. _d 0
172 do k = 1,nr
173
174 c-- Determine the mask on weights
175 do j = jmin,jmax
176 do i = imin,imax
177 cmask(i,j) = cosphi(i,j,bi,bj)
178 if (tdat(i,j,k,bi,bj) .eq. 0.) then
179 cmask(i,j) = 0. _d 0
180 else if (tdat(i,j,k,bi,bj) .lt. spval) then
181 cmask(i,j) = 0. _d 0
182 else if (tdat(i,j,k,bi,bj) .gt. spmax) then
183 cmask(i,j) = 0. _d 0
184 endif
185 enddo
186 enddo
187
188 c-- Compute model data misfit and cost function term for
189 c the temperature field.
190 do j = jmin,jmax
191 do i = imin,imax
192 if ( _hFacC(i,j,k,bi,bj) .ne. 0. ) then
193 fctile = fctile +
194 & (wthetaLev(i,j,k,bi,bj)*cmask(i,j)*
195 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
196 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
197 if ( wthetaLev(i,j,k,bi,bj)*cmask(i,j) .ne. 0. )
198 & num_temp(bi,bj) = num_temp(bi,bj) + 1. _d 0
199 diagnosfld3d(i,j,k,bi,bj) =
200 & (wthetaLev(i,j,k,bi,bj)*cmask(i,j)*
201 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj))*
202 & (tbar(i,j,k,bi,bj) - tdat(i,j,k,bi,bj)) )
203 else
204 diagnosfld3d(i,j,k,bi,bj) = 0.
205 endif
206 enddo
207 enddo
208
209 enddo
210 c-- End of loop over layers.
211
212 call mdswritefield( 'DiagnosCost_ClimTheta',
213 & writeBinaryPrec, globalfiles, 'RL', Nr,
214 & diagnosfld3d, irec, optimcycle, mythid )
215
216 fcthread = fcthread + fctile
217 objf_temp(bi,bj) = objf_temp(bi,bj) + fctile
218
219 enddo
220 enddo
221
222 enddo
223 c-- End of loop over records.
224
225 #endif
226
227 return
228 end
229

  ViewVC Help
Powered by ViewVC 1.1.22