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

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

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


Revision 1.5 - (hide annotations) (download)
Mon Mar 28 23:49:49 2005 UTC (19 years, 3 months 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.4: +3 -2 lines
Adding counters to cost terms.

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

  ViewVC Help
Powered by ViewVC 1.1.22