/[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.2 - (hide annotations) (download)
Wed Dec 3 23:08:40 2003 UTC (20 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint52e_post, checkpoint53c_post, checkpoint55d_pre, checkpoint52j_pre, checkpoint54a_post, checkpoint52d_pre, checkpoint52l_post, checkpoint52k_post, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint53f_post, hrcube_1, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint54, checkpoint54f_post, checkpoint53b_post, checkpoint53, checkpoint52d_post, checkpoint53g_post, checkpoint52f_post, hrcube5, checkpoint52i_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
Changes since 1.1: +3 -9 lines
adjustments in ecco cost terms:
o ARGO: replace cost_readargo*
o cost_drift: change weights
o cost_hyd: SIO misses cost_sst and doesnt use
            cost_ctd?clim terms
o XBT: active_file was wrong (needs xyz instead of xy)

1 heimbach 1.2 C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/ecco/Attic/cost_ctdt.F,v 1.2 2003/12/03 23:08:40 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    
67     character*(80) fnametheta
68    
69     logical doglobalread
70     logical ladinit
71    
72     character*(MAX_LEN_MBUF) msgbuf
73    
74     c == external functions ==
75    
76     integer ilnblnk
77     external ilnblnk
78    
79     c == end of interface ==
80    
81     jtlo = mybylo(mythid)
82     jthi = mybyhi(mythid)
83     itlo = mybxlo(mythid)
84     ithi = mybxhi(mythid)
85     jmin = 1
86     jmax = sny
87     imin = 1
88     imax = snx
89    
90     spval = -9990.
91    
92     c-- Read state record from global file.
93     doglobalread = .false.
94     ladinit = .false.
95    
96     #ifdef ALLOW_CTDT_COST_CONTRIBUTION
97    
98     #ifdef ECCO_VERBOSE
99     write(msgbuf,'(a)') ' '
100     call print_message( msgbuf, standardmessageunit,
101     & SQUEEZE_RIGHT , mythid)
102     write(msgbuf,'(a,i8.8)')
103     & ' cost_CTDT: number of records to process =', nmonsrec
104     call print_message( msgbuf, standardmessageunit,
105     & SQUEEZE_RIGHT , mythid)
106     write(msgbuf,'(a)') ' '
107     call print_message( msgbuf, standardmessageunit,
108     & SQUEEZE_RIGHT , mythid)
109     #endif
110    
111     if (optimcycle .ge. 0) then
112     ilu=ilnblnk( tbarfile )
113 heimbach 1.2 write(fnametheta(1:80),'(2a,i10.10)')
114     & tbarfile(1:ilu), '.', optimcycle
115 heimbach 1.1 endif
116    
117     fcthread_ctdt = 0. _d 0
118    
119     c-- Loop over records.
120     do irec = 1,nmonsrec
121    
122     c-- Read time averages and the monthly mean data.
123     call active_read_xyz( fnametheta, tbar, irec,
124     & doglobalread, ladinit,
125     & optimcycle, mythid, xx_tbar_mean_dummy )
126    
127     call mdsreadfield( ctdtfile, cost_iprec, 'RL', nr, ctdtobs,
128     & irec, mythid)
129    
130     c-- Loop over this thread's tiles.
131     do bj = jtlo,jthi
132     do bi = itlo,ithi
133     c-- Loop over the model layers
134    
135     fctile_ctdt = 0. _d 0
136    
137     do k = 1,nr
138    
139     c-- Determine the weights to be used.
140     do j = jmin,jmax
141     do i = imin,imax
142     cmask(i,j) = 1. _d 0
143     if (ctdtobs(i,j,k,bi,bj) .eq. 0.) then
144     cmask(i,j) = 0. _d 0
145     endif
146    
147     if (ctdtobs(i,j,k,bi,bj) .lt. spval) then
148     cmask(i,j) = 0. _d 0
149     endif
150    
151     cph(
152     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
153     cph below statement could be replaced by following
154     cph to make it independnet of Nr:
155     cph
156     cph if ( rC(K) .GT. -1000. ) then
157     cph)
158     c set cmask=0 in areas shallower than 1000m
159     if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
160     cmask(i,j) = 0. _d 0
161     endif
162    
163     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
164     cmask(i,j) = 0. _d 0
165     endif
166    
167     enddo
168     enddo
169    
170     do j = jmin,jmax
171     do i = imin,imax
172     www(i,j) = cosphi(i,j,bi,bj)*cmask(i,j)
173     tmpobs(i,j) = ctdtobs(i,j,k,bi,bj)
174     tmpbar(i,j) = tbar(i,j,k,bi,bj)
175     c wtmp(i,j) = wtheta(k,bi,bj)
176     wtmp(i,j) = wtheta2(i,j,k,bi,bj)
177     enddo
178     enddo
179    
180     do j = jmin,jmax
181     do i = imin,imax
182     c-- The array ctdtobs contains CTD temperature.
183     fctile_ctdt = fctile_ctdt +
184     & (wtmp(i,j)*www(i,j))*
185     & (tmpbar(i,j)-tmpobs(i,j))*
186     & (tmpbar(i,j)-tmpobs(i,j))
187    
188     enddo
189     enddo
190     enddo
191     c-- End of loop over layers.
192    
193     fcthread_ctdt = fcthread_ctdt + fctile_ctdt
194     objf_ctdt(bi,bj) = objf_ctdt(bi,bj) + fctile_ctdt
195    
196     #ifdef ECCO_VERBOSE
197     write(msgbuf,'(a)') ' '
198     call print_message( msgbuf, standardmessageunit,
199     & SQUEEZE_RIGHT , mythid)
200     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
201     & ' COST_CTDT: irec,bi,bj = ',irec,bi,bj
202     call print_message( msgbuf, standardmessageunit,
203     & SQUEEZE_RIGHT , mythid)
204     write(msgbuf,'(a,d22.15)')
205     & ' COST_CTDT: cost function = ', fctile_ctdt
206     call print_message( msgbuf, standardmessageunit,
207     & SQUEEZE_RIGHT , mythid)
208     write(msgbuf,'(a)') ' '
209     call print_message( msgbuf, standardmessageunit,
210     & SQUEEZE_RIGHT , mythid)
211     #endif
212    
213     enddo
214     enddo
215    
216     #ifdef ECCO_VERBOSE
217     c-- Print cost function for all tiles.
218     _GLOBAL_SUM_R8( fcthread_ctdt , myThid )
219     write(msgbuf,'(a)') ' '
220     call print_message( msgbuf, standardmessageunit,
221     & SQUEEZE_RIGHT , mythid)
222     write(msgbuf,'(a,i8.8)')
223     & ' cost_CTDT: irec = ',irec
224     call print_message( msgbuf, standardmessageunit,
225     & SQUEEZE_RIGHT , mythid)
226     write(msgbuf,'(a,a,d22.15)')
227     & ' global cost function value',
228     & ' ( CTD temp. ) = ',fcthread_ctdt
229     call print_message( msgbuf, standardmessageunit,
230     & SQUEEZE_RIGHT , mythid)
231     write(msgbuf,'(a)') ' '
232     call print_message( msgbuf, standardmessageunit,
233     & SQUEEZE_RIGHT , mythid)
234     #endif
235    
236     enddo
237     c-- End of second loop over records.
238    
239     #else
240     c-- Do not enter the calculation of the CTD temperature contribution
241     c-- to the final cost function.
242    
243     fctile_ctdt = 0. _d 0
244     fcthread_ctdt = 0. _d 0
245    
246     crg
247     nrec = 1
248     crg
249    
250     _BEGIN_MASTER( mythid )
251     write(msgbuf,'(a)') ' '
252     call print_message( msgbuf, standardmessageunit,
253     & SQUEEZE_RIGHT , mythid)
254     write(msgbuf,'(a,a)')
255     & ' cost_CTDT: no contribution of CTD temperature ',
256     & ' to cost function.'
257     call print_message( msgbuf, standardmessageunit,
258     & SQUEEZE_RIGHT , mythid)
259     write(msgbuf,'(a,a,i9.8)')
260     & ' cost_CTDT: number of records that would have',
261     & ' been processed: ',nrec
262     call print_message( msgbuf, standardmessageunit,
263     & SQUEEZE_RIGHT , mythid)
264     write(msgbuf,'(a)') ' '
265     call print_message( msgbuf, standardmessageunit,
266     & SQUEEZE_RIGHT , mythid)
267     _END_MASTER( mythid )
268     #endif
269    
270     return
271     end

  ViewVC Help
Powered by ViewVC 1.1.22