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

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

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


Revision 1.4 - (show annotations) (download)
Mon Mar 28 23:49:49 2005 UTC (19 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint57m_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58t_post, checkpoint58h_post, checkpoint58w_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.3: +3 -1 lines
Adding counters to cost terms.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_ctds.F,v 1.3 2005/03/28 19:40:59 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_CTDS(
7 I myiter,
8 I mytime,
9 I mythid
10 & )
11
12 c ==================================================================
13 c SUBROUTINE cost_CTDS
14 c ==================================================================
15 c
16 c o Evaluate cost function contribution of CTD temperature data.
17 c
18 c started: Elisabeth Remy eremy@ucsd.edu 30-Aug-2000
19 c
20 c ==================================================================
21 c SUBROUTINE cost_CTDS
22 c ==================================================================
23
24 implicit none
25
26 c == global variables ==
27
28 #include "EEPARAMS.h"
29 #include "SIZE.h"
30 #include "GRID.h"
31 #include "DYNVARS.h"
32
33 #include "cal.h"
34 #include "ecco_cost.h"
35 #include "ctrl.h"
36 #include "ctrl_dummy.h"
37 #include "optim.h"
38
39 c == routine arguments ==
40
41 integer myiter
42 _RL mytime
43 integer mythid
44
45 c == local variables ==
46
47 integer bi,bj
48 integer i,j,k
49 integer itlo,ithi
50 integer jtlo,jthi
51 integer jmin,jmax
52 integer imin,imax
53 integer nrec
54 integer irec
55 integer ilu
56
57 _RL fctile_ctds
58 _RL fcthread_ctds
59 _RL www (1-olx:snx+olx,1-oly:sny+oly)
60 _RL wtmp (1-olx:snx+olx,1-oly:sny+oly)
61 _RL tmpobs (1-olx:snx+olx,1-oly:sny+oly)
62 _RL tmpbar (1-olx:snx+olx,1-oly:sny+oly)
63 _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
64 _RL spval
65 _RL spmax
66
67 character*(80) fnamesalt
68
69 logical doglobalread
70 logical ladinit
71
72 character*(MAX_LEN_MBUF) msgbuf
73
74 cnew(
75 integer il
76 integer mody, modm
77 integer iyear, imonth
78 character*(80) fnametmp
79 logical exst
80 cnew)
81
82 c == external functions ==
83
84 integer ilnblnk
85 external ilnblnk
86
87 c == end of interface ==
88
89 jtlo = mybylo(mythid)
90 jthi = mybyhi(mythid)
91 itlo = mybxlo(mythid)
92 ithi = mybxhi(mythid)
93 jmin = 1
94 jmax = sny
95 imin = 1
96 imax = snx
97
98 spval = 25.
99 spmax = 40.
100
101 c-- Read state record from global file.
102 doglobalread = .false.
103 ladinit = .false.
104
105 #ifdef ALLOW_CTDS_COST_CONTRIBUTION
106
107 if (optimcycle .ge. 0) then
108 ilu=ilnblnk( sbarfile )
109 write(fnamesalt(1:80),'(2a,i10.10)')
110 & sbarfile(1:ilu),'.',optimcycle
111 endif
112
113 fcthread_ctds = 0. _d 0
114
115 cnew(
116 mody = modelstartdate(1)/10000
117 modm = modelstartdate(1)/100 - mody*100
118 cnew)
119
120 c-- Loop over records.
121 do irec = 1,nmonsrec
122
123 c-- Read time averages and the monthly mean data.
124 call active_read_xyz( fnamesalt, sbar, irec,
125 & doglobalread, ladinit,
126 & optimcycle, mythid, xx_sbar_mean_dummy )
127
128 cnew(
129 iyear = mody + INT((modm-1+irec-1)/12)
130 imonth = 1 + MOD(modm-1+irec-1,12)
131 il=ilnblnk(ctdsfile)
132 write(fnametmp(1:80),'(2a,i4)')
133 & ctdsfile(1:il), '_', iyear
134 inquire( file=fnametmp, exist=exst )
135 if (.NOT. exst) then
136 write(fnametmp(1:80),'(a)') ctdsfile(1:il)
137 imonth = irec
138 endif
139
140 call mdsreadfield( fnametmp, cost_iprec, 'RL', nr, ctdsobs,
141 & imonth, mythid)
142 cnew)
143
144 c-- Loop over this thread's tiles.
145 do bj = jtlo,jthi
146 do bi = itlo,ithi
147 c-- Loop over the model layers
148
149 fctile_ctds = 0. _d 0
150
151 do k = 1,nr
152
153 c-- Determine the weights to be used.
154 do j = jmin,jmax
155 do i = imin,imax
156 cmask(i,j) = 1. _d 0
157 if (ctdsobs(i,j,k,bi,bj) .lt. spval .or.
158 & ctdsobs(i,j,k,bi,bj) .gt. spmax .or.
159 & ctdsobs(i,j,k,bi,bj) .eq. 0. ) then
160 cmask(i,j) = 0. _d 0
161 endif
162
163 cph(
164 cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
165 cph below statement could be replaced by following
166 cph to make it independnet of Nr:
167 cph
168 cph if ( rC(K) .GT. -1000. ) then
169 cph)
170 if (
171 & (_hFacC(i,j,13,bi,bj) .ne. 0.).and.
172 & (_hFacC(i,j,k,bi,bj) .ne. 0.)) then
173
174 www(i,j) = cosphi(i,j,bi,bj)*cmask(i,j)
175 tmpobs(i,j) = ctdsobs(i,j,k,bi,bj)
176 tmpbar(i,j) = sbar(i,j,k,bi,bj)
177 wtmp(i,j) = wsalt2(i,j,k,bi,bj)
178
179 fctile_ctds = fctile_ctds +
180 & (wtmp(i,j)*www(i,j))*
181 & (tmpbar(i,j)-tmpobs(i,j))*
182 & (tmpbar(i,j)-tmpobs(i,j))
183 if ( wtmp(i,j)*www(i,j) .ne. 0. )
184 & num_ctds(bi,bj) = num_ctds(bi,bj) + 1. _d 0
185 endif
186 enddo
187 enddo
188 enddo
189 c-- End of loop over layers.
190
191 fcthread_ctds = fcthread_ctds + fctile_ctds
192 objf_ctds(bi,bj) = objf_ctds(bi,bj) + fctile_ctds
193
194 #ifdef ECCO_VERBOSE
195 write(msgbuf,'(a)') ' '
196 call print_message( msgbuf, standardmessageunit,
197 & SQUEEZE_RIGHT , mythid)
198 write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
199 & ' COST_CTDS: irec,bi,bj = ',irec,bi,bj
200 call print_message( msgbuf, standardmessageunit,
201 & SQUEEZE_RIGHT , mythid)
202 write(msgbuf,'(a,d22.15)')
203 & ' COST_CTDS: cost function = ', fctile_ctds
204 call print_message( msgbuf, standardmessageunit,
205 & SQUEEZE_RIGHT , mythid)
206 write(msgbuf,'(a)') ' '
207 call print_message( msgbuf, standardmessageunit,
208 & SQUEEZE_RIGHT , mythid)
209 #endif
210
211 enddo
212 enddo
213
214 #ifdef ECCO_VERBOSE
215 c-- Print cost function for all tiles.
216 _GLOBAL_SUM_R8( fcthread_ctds , myThid )
217 write(msgbuf,'(a)') ' '
218 call print_message( msgbuf, standardmessageunit,
219 & SQUEEZE_RIGHT , mythid)
220 write(msgbuf,'(a,i8.8)')
221 & ' cost_CTDS: irec = ',irec
222 call print_message( msgbuf, standardmessageunit,
223 & SQUEEZE_RIGHT , mythid)
224 write(msgbuf,'(a,a,d22.15)')
225 & ' global cost function value',
226 & ' ( CTD sal. ) = ',fcthread_ctds
227 call print_message( msgbuf, standardmessageunit,
228 & SQUEEZE_RIGHT , mythid)
229 write(msgbuf,'(a)') ' '
230 call print_message( msgbuf, standardmessageunit,
231 & SQUEEZE_RIGHT , mythid)
232 #endif
233
234 enddo
235 c-- End of second loop over records.
236
237 #else
238 c-- Do not enter the calculation of the CTD temperature contribution
239 c-- to the final cost function.
240
241 fctile_ctds = 0. _d 0
242 fcthread_ctds = 0. _d 0
243
244 crg
245 nrec = 1
246 crg
247
248 _BEGIN_MASTER( mythid )
249 write(msgbuf,'(a)') ' '
250 call print_message( msgbuf, standardmessageunit,
251 & SQUEEZE_RIGHT , mythid)
252 write(msgbuf,'(a,a)')
253 & ' cost_CTDS: no contribution of CTD temperature ',
254 & ' to cost function.'
255 call print_message( msgbuf, standardmessageunit,
256 & SQUEEZE_RIGHT , mythid)
257 write(msgbuf,'(a,a,i9.8)')
258 & ' cost_CDTS: number of records that would have',
259 & ' been processed: ',nrec
260 call print_message( msgbuf, standardmessageunit,
261 & SQUEEZE_RIGHT , mythid)
262 write(msgbuf,'(a)') ' '
263 call print_message( msgbuf, standardmessageunit,
264 & SQUEEZE_RIGHT , mythid)
265 _END_MASTER( mythid )
266 #endif
267
268 return
269 end

  ViewVC Help
Powered by ViewVC 1.1.22