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

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

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


Revision 1.9 - (show annotations) (download)
Mon Mar 22 02:19:35 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.8: +2 -2 lines
finish removing unbalanced quote (single or double) in commented line

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

  ViewVC Help
Powered by ViewVC 1.1.22