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

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

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


Revision 1.1 - (show annotations) (download)
Thu Nov 6 22:10:08 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint53f_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint52l_pre, checkpoint52e_pre, hrcube4, hrcube5, checkpoint52j_post, checkpoint52e_post, checkpoint52d_pre, checkpoint53c_post, checkpoint53d_post, checkpoint55d_pre, checkpoint52j_pre, checkpoint54a_post, branch-netcdf, checkpoint52b_pre, checkpoint52n_post, checkpoint54b_post, checkpoint54d_post, checkpoint54e_post, checkpoint55b_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, checkpoint52l_post, checkpoint52k_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint53g_post, checkpoint52f_post, checkpoint52c_post, ecco_c52_e35, checkpoint54f_post, checkpoint52a_pre, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_post, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_1, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
o merging from ecco-branch
o pkg/ecco now containes ecco-specific part of cost function
o top level routines the_main_loop, forward_step
  supersede those in model/src/
  previous input data.cost now in data.ecco
  (new namelist ecco_cost_nml)

1 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_tmi.F,v 1.1.2.1 2003/06/19 15:21:16 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_tmi(
7 I myiter,
8 I mytime,
9 I mythid
10 & )
11
12 c ==================================================================
13 c SUBROUTINE cost_tmi
14 c ==================================================================
15 c
16 c o Evaluate cost function contribution of TMI SST
17 c
18 c started: Armin Koehl akoehl@ucsd.edu
19 c
20 c ==================================================================
21 c SUBROUTINE cost_tmi
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 irec
54 integer levmon
55 integer levoff
56 integer iltheta
57
58 _RL fctile_tmi
59 _RL fcthread_tmi
60
61 _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
62 _RL spval
63
64 character*(80) fnametheta
65
66 logical doglobalread
67 logical ladinit
68
69 character*(MAX_LEN_MBUF) msgbuf
70
71 c == external functions ==
72
73 integer ilnblnk
74 external ilnblnk
75
76 c == end of interface ==
77
78 jtlo = mybylo(mythid)
79 jthi = mybyhi(mythid)
80 itlo = mybxlo(mythid)
81 ithi = mybxhi(mythid)
82 jmin = 1
83 jmax = sny
84 imin = 1
85 imax = snx
86
87 spval = -9990.
88
89 c-- Read tiled data.
90 doglobalread = .false.
91 ladinit = .false.
92
93 #ifdef ALLOW_TMI_SST_COST_CONTRIBUTION
94
95 #ifdef ECCO_VERBOSE
96 _BEGIN_MASTER( mythid )
97 write(msgbuf,'(a)') ' '
98 call print_message( msgbuf, standardmessageunit,
99 & SQUEEZE_RIGHT , mythid)
100 write(msgbuf,'(a,i8.8)')
101 & ' cost_tmi: number of records to process = ',nmonsrec
102 call print_message( msgbuf, standardmessageunit,
103 & SQUEEZE_RIGHT , mythid)
104 write(msgbuf,'(a)') ' '
105 call print_message( msgbuf, standardmessageunit,
106 & SQUEEZE_RIGHT , mythid)
107 _END_MASTER( mythid )
108 #endif
109
110 if (optimcycle .ge. 0) then
111 iltheta = ilnblnk( tbarfile )
112 write(fnametheta(1:80),'(2a,i10.10)')
113 & tbarfile(1:iltheta),'.',optimcycle
114 else
115 print*
116 print*,' cost_tmi: optimcycle has a wrong value.'
117 print*,' optimcycle = ',optimcycle
118 print*
119 stop ' ... stopped in cost_tmi.'
120 endif
121
122 fcthread_tmi = 0. _d 0
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_theta_dummy )
132
133 do bj = jtlo,jthi
134 do bi = itlo,ithi
135
136 fctile_tmi = 0. _d 0
137 k = 1
138
139 c-- Compute cost rel. to monthly TMI SST climatology field.
140
141 call cost_ReadTMIFields( irec, mythid )
142
143 c-- Determine the mask on weights
144 do j = jmin,jmax
145 do i = imin,imax
146 cmask(i,j) = 1. _d 0
147 if (tmidat(i,j,bi,bj) .eq. 0.) then
148 cmask(i,j) = 0. _d 0
149 endif
150
151 if (tmidat(i,j,bi,bj) .le. spval) then
152 cmask(i,j) = 0. _d 0
153 endif
154
155 ! set cmask=0 in areas shallower than 1000m
156 if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
157 cmask(i,j) = 0. _d 0
158 endif
159 enddo
160 enddo
161
162 do j = jmin,jmax
163 do i = imin,imax
164 if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
165 fctile_tmi = fctile_tmi +
166 & wsst(i,j,bi,bj)*cosphi(i,j,bi,bj)*cmask(i,j)*
167 & ( (tbar(i,j,k,bi,bj)-tmidat(i,j,bi,bj))*
168 & (tbar(i,j,k,bi,bj)-tmidat(i,j,bi,bj))*
169 & sstmask(i,j,bi,bj) )
170 endif
171 enddo
172 enddo
173
174
175
176 fcthread_tmi = fcthread_tmi + fctile_tmi
177 objf_tmi(bi,bj) = objf_tmi(bi,bj) + fctile_tmi
178
179 #ifdef ECCO_VERBOSE
180 c-- Print cost function for each tile in each thread.
181 write(msgbuf,'(a)') ' '
182 call print_message( msgbuf, standardmessageunit,
183 & SQUEEZE_RIGHT , mythid)
184 write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
185 & ' cost_tmi: irec,bi,bj = ',irec,bi,bj
186 call print_message( msgbuf, standardmessageunit,
187 & SQUEEZE_RIGHT , mythid)
188 write(msgbuf,'(a,d22.15)')
189 & ' cost function (tmi) = ',
190 & fctile_tmi
191 call print_message( msgbuf, standardmessageunit,
192 & SQUEEZE_RIGHT , mythid)
193 #endif
194
195 enddo
196 enddo
197
198 #ifdef ECCO_VERBOSE
199 c-- Print cost function for all tiles.
200 _GLOBAL_SUM_R8( fcthread_tmi , myThid )
201 write(msgbuf,'(a)') ' '
202 call print_message( msgbuf, standardmessageunit,
203 & SQUEEZE_RIGHT , mythid)
204 write(msgbuf,'(a,i8.8)')
205 & ' cost_tmi: irec = ',irec
206 call print_message( msgbuf, standardmessageunit,
207 & SQUEEZE_RIGHT , mythid)
208 write(msgbuf,'(a,a,d22.15)')
209 & ' global cost function value',
210 & ' ( TMI ) = ',fcthread_tmi
211 call print_message( msgbuf, standardmessageunit,
212 & SQUEEZE_RIGHT , mythid)
213 write(msgbuf,'(a)') ' '
214 call print_message( msgbuf, standardmessageunit,
215 & SQUEEZE_RIGHT , mythid)
216 #endif
217
218 enddo
219 c-- End of loop over records.
220
221 #else
222 c-- Do not enter the calculation of the temperature contribution to
223 c-- the final cost function.
224
225 fctile_tmi = 0. _d 0
226 fcthread_tmi = 0. _d 0
227
228 _BEGIN_MASTER( mythid )
229 write(msgbuf,'(a)') ' '
230 call print_message( msgbuf, standardmessageunit,
231 & SQUEEZE_RIGHT , mythid)
232 write(msgbuf,'(a,a)')
233 & ' cost_tmi: no contribution of temperature field ',
234 & 'to cost function.'
235 call print_message( msgbuf, standardmessageunit,
236 & SQUEEZE_RIGHT , mythid)
237 write(msgbuf,'(a,a,i9.8)')
238 & ' cost_tmi: number of records that would have',
239 & ' been processed: ',nmonsrec
240 call print_message( msgbuf, standardmessageunit,
241 & SQUEEZE_RIGHT , mythid)
242 write(msgbuf,'(a)') ' '
243 call print_message( msgbuf, standardmessageunit,
244 & SQUEEZE_RIGHT , mythid)
245 _END_MASTER( mythid )
246 #endif
247
248 return
249 end
250

  ViewVC Help
Powered by ViewVC 1.1.22