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

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

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


Revision 1.15 - (hide annotations) (download)
Thu Oct 29 13:39:54 2015 UTC (8 years, 8 months ago) by gforget
Branch: MAIN
CVS Tags: HEAD
Changes since 1.14: +1 -1 lines
FILE REMOVED
- remove codes that have been replaced with generic function calls.

1 gforget 1.15 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_xbt.F,v 1.14 2014/10/18 18:15:45 gforget Exp $
2 jmc 1.7 C $Name: $
3 heimbach 1.1
4 jmc 1.13 #include "ECCO_OPTIONS.h"
5 heimbach 1.1
6    
7     subroutine cost_XBT(
8     I myiter,
9     I mytime,
10     I mythid
11     & )
12    
13     c ==================================================================
14     c SUBROUTINE cost_XBT
15     c ==================================================================
16     c
17     c o Evaluate cost function contribution of XBT 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_XBT
24     c ==================================================================
25    
26     implicit none
27    
28     c == global variables ==
29    
30 gforget 1.14 #ifdef ALLOW_XBT_COST_CONTRIBUTION
31 heimbach 1.1 #include "EEPARAMS.h"
32     #include "SIZE.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35    
36     #include "cal.h"
37     #include "ecco_cost.h"
38 heimbach 1.12 #include "CTRL_SIZE.h"
39 heimbach 1.1 #include "ctrl.h"
40     #include "ctrl_dummy.h"
41     #include "optim.h"
42 gforget 1.14 #endif
43 heimbach 1.1
44     c == routine arguments ==
45    
46     integer myiter
47     _RL mytime
48     integer mythid
49    
50 gforget 1.14 #ifdef ALLOW_XBT_COST_CONTRIBUTION
51 heimbach 1.1 c == local variables ==
52    
53     integer bi,bj
54     integer i,j,k
55     integer itlo,ithi
56     integer jtlo,jthi
57     integer jmin,jmax
58     integer imin,imax
59     integer nrec
60     integer irec
61     integer ilu
62 jmc 1.7
63 heimbach 1.1 _RL fctile_xbt
64     _RL fcthread_xbt
65     _RL www (1-olx:snx+olx,1-oly:sny+oly)
66     _RL tmpobs (1-olx:snx+olx,1-oly:sny+oly)
67 jmc 1.7 _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
68 heimbach 1.1 _RL spval
69 heimbach 1.4 _RL spmax
70 heimbach 1.1 _RL ztop,rl_35,rl_0
71 jmc 1.7
72 heimbach 1.1 character*(80) fnametheta
73    
74     logical doglobalread
75     logical ladinit
76    
77     character*(MAX_LEN_MBUF) msgbuf
78    
79 heimbach 1.3 cnew(
80     integer il
81     integer mody, modm
82     integer iyear, imonth
83     character*(80) fnametmp
84     logical exst
85     cnew)
86    
87 heimbach 1.1 c == external functions ==
88    
89     integer ilnblnk
90     external ilnblnk
91     _RL SW_PTMP
92     external SW_PTMP
93    
94     c == end of interface ==
95    
96     jtlo = mybylo(mythid)
97     jthi = mybyhi(mythid)
98     itlo = mybxlo(mythid)
99     ithi = mybxhi(mythid)
100     jmin = 1
101     jmax = sny
102     imin = 1
103     imax = snx
104 jmc 1.7
105 heimbach 1.3 spval = -1.8
106 heimbach 1.4 spmax = 40.
107 heimbach 1.1 ztop = -.981*1.027
108     rl_35 = 35.0
109     rl_0 = 0.0
110    
111     c-- Read state record from global file.
112     doglobalread = .false.
113     ladinit = .false.
114 jmc 1.7
115 heimbach 1.1 if (optimcycle .ge. 0) then
116     ilu=ilnblnk( tbarfile )
117 jmc 1.7 write(fnametheta(1:80),'(2a,i10.10)')
118 heimbach 1.3 & tbarfile(1:ilu),'.',optimcycle
119 heimbach 1.1 endif
120 jmc 1.7
121 heimbach 1.1 fcthread_xbt = 0. _d 0
122    
123 heimbach 1.3 cnew(
124     mody = modelstartdate(1)/10000
125     modm = modelstartdate(1)/100 - mody*100
126     cnew)
127    
128 heimbach 1.1 c-- Loop over records.
129     do irec = 1,nmonsrec
130    
131     c-- Read time averages and the monthly mean data.
132 heimbach 1.2 call active_read_xyz( fnametheta, tbar, irec,
133 heimbach 1.1 & doglobalread, ladinit,
134     & optimcycle, mythid
135     & , xx_tbar_mean_dummy )
136 jmc 1.7
137 heimbach 1.3 cnew(
138     iyear = mody + INT((modm-1+irec-1)/12)
139     imonth = 1 + MOD(modm-1+irec-1,12)
140     il=ilnblnk(xbtfile)
141 jmc 1.7 write(fnametmp(1:80),'(2a,i4)')
142 heimbach 1.3 & xbtfile(1:il), '_', iyear
143     inquire( file=fnametmp, exist=exst )
144     if (.NOT. exst) then
145     write(fnametmp(1:80),'(a)') xbtfile(1:il)
146     imonth = irec
147     endif
148 heimbach 1.1
149 heimbach 1.3 call mdsreadfield( fnametmp, cost_iprec, 'RL', nr, xbtobs,
150     & imonth, mythid)
151     cnew)
152 heimbach 1.1
153 jmc 1.10 c-- Loop over this thread tiles.
154 heimbach 1.1 do bj = jtlo,jthi
155     do bi = itlo,ithi
156     c-- Loop over the model layers
157    
158     fctile_xbt = 0. _d 0
159    
160     do k = 1,nr
161    
162     c-- Determine the weights to be used.
163     do j = jmin,jmax
164     do i = imin,imax
165 heimbach 1.5 cmask(i,j) = cosphi(i,j,bi,bj)
166 heimbach 1.4 if ( xbtobs(i,j,k,bi,bj) .lt. spval .or.
167 jmc 1.11 & xbtobs(i,j,k,bi,bj) .gt. spmax .or.
168 heimbach 1.4 & xbtobs(i,j,k,bi,bj) .eq. 0. ) then
169 heimbach 1.1 cmask(i,j) = 0. _d 0
170     endif
171    
172     cph(
173     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
174     cph below statement could be replaced by following
175     cph to make it independnet of Nr:
176     cph
177     cph if ( rC(K) .GT. -1000. ) then
178     cph)
179 jmc 1.7
180 heimbach 1.1 enddo
181     enddo
182 jmc 1.7
183 heimbach 1.1 do j = jmin,jmax
184     do i = imin,imax
185 heimbach 1.9 if ( _hFacC(i,j,k,bi,bj) .ne. 0. ) then
186 heimbach 1.5 tmpobs(i,j) = SW_PTMP(rl_35,
187 jmc 1.7 $ xbtobs(i,j,k,bi,bj),ztop*rc(k),rl_0)
188 heimbach 1.1 c-- The array ctdtobs contains CTD temperature.
189    
190 jmc 1.7 fctile_xbt = fctile_xbt +
191 heimbach 1.5 & (wtheta2(i,j,k,bi,bj)*cmask(i,j))*
192     & (tbar(i,j,k,bi,bj)-tmpobs(i,j))*
193     & (tbar(i,j,k,bi,bj)-tmpobs(i,j))
194     if ( wtheta2(i,j,k,bi,bj)*cmask(i,j) .ne. 0. )
195     & num_xbt(bi,bj) = num_xbt(bi,bj) + 1. _d 0
196 heimbach 1.6 endif
197 heimbach 1.1 enddo
198     enddo
199     c-- End of loop over layers.
200     enddo
201    
202     fcthread_xbt = fcthread_xbt + fctile_xbt
203 jmc 1.7 objf_xbt(bi,bj) = objf_xbt(bi,bj) + fctile_xbt
204 heimbach 1.1
205     #ifdef ECCO_VERBOSE
206     write(msgbuf,'(a)') ' '
207     call print_message( msgbuf, standardmessageunit,
208     & SQUEEZE_RIGHT , mythid)
209     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
210     & ' COST_XBT: irec,bi,bj = ',irec,bi,bj
211     call print_message( msgbuf, standardmessageunit,
212     & SQUEEZE_RIGHT , mythid)
213     write(msgbuf,'(a,d22.15)')
214     & ' COST_XBT: cost function = ', fctile_xbt
215     call print_message( msgbuf, standardmessageunit,
216     & SQUEEZE_RIGHT , mythid)
217     write(msgbuf,'(a)') ' '
218     call print_message( msgbuf, standardmessageunit,
219     & SQUEEZE_RIGHT , mythid)
220     #endif
221    
222     enddo
223     enddo
224    
225     #ifdef ECCO_VERBOSE
226     c-- Print cost function for all tiles.
227 jmc 1.8 _GLOBAL_SUM_RL( fcthread_xbt , myThid )
228 heimbach 1.1 write(msgbuf,'(a)') ' '
229     call print_message( msgbuf, standardmessageunit,
230     & SQUEEZE_RIGHT , mythid)
231     write(msgbuf,'(a,i8.8)')
232     & ' cost_XBT: irec = ',irec
233     call print_message( msgbuf, standardmessageunit,
234     & SQUEEZE_RIGHT , mythid)
235     write(msgbuf,'(a,a,d22.15)')
236     & ' global cost function value',
237     & ' ( XBT temp. ) = ',fcthread_xbt
238     call print_message( msgbuf, standardmessageunit,
239     & SQUEEZE_RIGHT , mythid)
240     write(msgbuf,'(a)') ' '
241     call print_message( msgbuf, standardmessageunit,
242     & SQUEEZE_RIGHT , mythid)
243     #endif
244    
245     enddo
246     c-- End of second loop over records.
247    
248     #endif
249    
250     return
251     end

  ViewVC Help
Powered by ViewVC 1.1.22