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

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

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


Revision 1.8 - (show annotations) (download)
Wed Jun 17 15:11:32 2009 UTC (15 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.7: +2 -2 lines
Remove depth limitations for in-situ costs.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_argo_theta.F,v 1.7 2009/04/28 18:13:27 jmc Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_argo_theta(
8 I myiter,
9 I mytime,
10 I mythid
11 & )
12
13 c ==================================================================
14 c SUBROUTINE cost_argo_theta
15 c ==================================================================
16 c
17 c o Evaluate cost function contribution of ARGO 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_argo_theta
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_argot
60 _RL fcthread_argot
61 _RL www (1-olx:snx+olx,1-oly:sny+oly)
62 _RL tmpobs (1-olx:snx+olx,1-oly:sny+oly)
63 _RL spval
64 _RL ztop,rl_35,rl_0
65 _RL spmax
66
67 character*(80) fnametheta
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 _RL SW_PTMP
87 external SW_PTMP
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 ztop = -.981*1.027
103 rl_35= 35.0
104 rl_0 = 0.0
105 c-- Read state record from global file.
106 doglobalread = .false.
107 ladinit = .false.
108
109 #ifdef ALLOW_ARGO_THETA_COST_CONTRIBUTION
110
111 if (optimcycle .ge. 0) then
112 ilu=ilnblnk( tbarfile )
113 write(fnametheta(1:80),'(2a,i10.10)')
114 & tbarfile(1:ilu),'.',optimcycle
115 endif
116
117 fcthread_argot = 0. _d 0
118
119 cnew(
120 mody = modelstartdate(1)/10000
121 modm = modelstartdate(1)/100 - mody*100
122 cnew)
123
124 c-- Loop over records.
125 do irec = 1,nmonsrec
126
127 c-- Read time averages and the monthly mean data.
128 call active_read_xyz( fnametheta, tbar, irec,
129 & doglobalread, ladinit,
130 & optimcycle, mythid
131 & , xx_tbar_mean_dummy )
132
133 cnew(
134 iyear = mody + INT((modm-1+irec-1)/12)
135 imonth = 1 + MOD(modm-1+irec-1,12)
136 il=ilnblnk(argotfile)
137 write(fnametmp(1:80),'(2a,i4)')
138 & argotfile(1:il), '_', iyear
139 inquire( file=fnametmp, exist=exst )
140 if (.NOT. exst) then
141 write(fnametmp(1:80),'(a)') argotfile(1:il)
142 imonth = irec
143 endif
144
145 call mdsreadfield( fnametmp, cost_iprec, 'RL', nr, argotobs,
146 & imonth, mythid)
147 cnew)
148
149 c-- Loop over this thread's tiles.
150 do bj = jtlo,jthi
151 do bi = itlo,ithi
152 c-- Loop over the model layers
153
154 fctile_argot = 0. _d 0
155
156 do k = 1,nr
157 cph(
158 cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
159 cph below statement could be replaced by following
160 cph to make it independnet of Nr:
161 cph
162 cph if ( rC(K) .GT. -1000. ) then
163 cph)
164 c-- Determine the weights to be used.
165 do j = jmin,jmax
166 do i = imin,imax
167 if( (argotobs(i,j,k,bi,bj) .ne. 0.).and.
168 & (argotobs(i,j,k,bi,bj) .gt. spval).and.
169 & (argotobs(i,j,k,bi,bj) .lt. spmax).and.
170 cph & (_hFacC(i,j,13,bi,bj) .ne. 0.).and.
171 & (_hFacC(i,j,k,bi,bj) .ne. 0.) )then
172 tmpobs(i,j) = SW_PTMP(rl_35,
173 $ argotobs(i,j,k,bi,bj),ztop*rc(k),rl_0)
174 fctile_argot = fctile_argot +
175 & wtheta2(i,j,k,bi,bj)*cosphi(i,j,bi,bj)*
176 & (tbar(i,j,k,bi,bj)-tmpobs(i,j))*
177 & (tbar(i,j,k,bi,bj)-tmpobs(i,j))
178 if ( wtheta2(i,j,k,bi,bj)*cosphi(i,j,bi,bj) .ne. 0. )
179 & num_argot(bi,bj) = num_argot(bi,bj) + 1. _d 0
180 endif
181 enddo
182 enddo
183 c-- End of loop over layers.
184 enddo
185
186 fcthread_argot = fcthread_argot + fctile_argot
187 objf_argot(bi,bj) = objf_argot(bi,bj) + fctile_argot
188
189 #ifdef ECCO_VERBOSE
190 write(msgbuf,'(a)') ' '
191 call print_message( msgbuf, standardmessageunit,
192 & SQUEEZE_RIGHT , mythid)
193 write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
194 & ' COST_ARGO_THETA: irec,bi,bj = ',irec,bi,bj
195 call print_message( msgbuf, standardmessageunit,
196 & SQUEEZE_RIGHT , mythid)
197 write(msgbuf,'(a,d22.15)')
198 & ' COST_ARGO_THETA: cost function = ', fctile_argot
199 call print_message( msgbuf, standardmessageunit,
200 & SQUEEZE_RIGHT , mythid)
201 write(msgbuf,'(a)') ' '
202 call print_message( msgbuf, standardmessageunit,
203 & SQUEEZE_RIGHT , mythid)
204 #endif
205
206 enddo
207 enddo
208
209 #ifdef ECCO_VERBOSE
210 c-- Print cost function for all tiles.
211 c _GLOBAL_SUM_RL( fcthread_argot , myThid )
212 write(msgbuf,'(a)') ' '
213 call print_message( msgbuf, standardmessageunit,
214 & SQUEEZE_RIGHT , mythid)
215 write(msgbuf,'(a,i8.8)')
216 & ' cost_ARGOT: irec = ',irec
217 call print_message( msgbuf, standardmessageunit,
218 & SQUEEZE_RIGHT , mythid)
219 write(msgbuf,'(a,a,d22.15)')
220 & ' global cost function value',
221 & ' ( ARGO temp. ) = ',fcthread_argot
222 call print_message( msgbuf, standardmessageunit,
223 & SQUEEZE_RIGHT , mythid)
224 write(msgbuf,'(a)') ' '
225 call print_message( msgbuf, standardmessageunit,
226 & SQUEEZE_RIGHT , mythid)
227 #endif
228
229 enddo
230 c-- End of second loop over records.
231
232 #else
233 c-- Do not enter the calculation of the CTD temperature contribution
234 c-- to the final cost function.
235
236 fctile_argot = 0. _d 0
237 fcthread_argot = 0. _d 0
238
239 crg
240 nrec = 1
241 crg
242
243 _BEGIN_MASTER( mythid )
244 write(msgbuf,'(a)') ' '
245 call print_message( msgbuf, standardmessageunit,
246 & SQUEEZE_RIGHT , mythid)
247 write(msgbuf,'(a,a)')
248 & ' cost_ARGOT: no contribution of ARGO temperature ',
249 & ' to cost function.'
250 call print_message( msgbuf, standardmessageunit,
251 & SQUEEZE_RIGHT , mythid)
252 write(msgbuf,'(a,a,i9.8)')
253 & ' cost_ARGOT: number of records that would have',
254 & ' been processed: ',nrec
255 call print_message( msgbuf, standardmessageunit,
256 & SQUEEZE_RIGHT , mythid)
257 write(msgbuf,'(a)') ' '
258 call print_message( msgbuf, standardmessageunit,
259 & SQUEEZE_RIGHT , mythid)
260 _END_MASTER( mythid )
261 #endif
262
263 return
264 end

  ViewVC Help
Powered by ViewVC 1.1.22