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

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

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


Revision 1.8 - (hide 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 heimbach 1.8 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_argo_salt.F,v 1.7 2009/04/28 18:13:27 jmc Exp $
2 jmc 1.6 C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
6    
7     subroutine cost_argo_salt(
8     I myiter,
9     I mytime,
10     I mythid
11     & )
12    
13     c ==================================================================
14     c SUBROUTINE cost_argo_salt
15     c ==================================================================
16     c
17     c o Evaluate cost function contribution of ARGO salt 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_salt
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 jmc 1.6
59 heimbach 1.1 _RL fctile_argos
60     _RL fcthread_argos
61     _RL www (1-olx:snx+olx,1-oly:sny+oly)
62     _RL wtmp (1-olx:snx+olx,1-oly:sny+oly)
63     _RL tmpobs (1-olx:snx+olx,1-oly:sny+oly)
64     _RL tmpbar (1-olx:snx+olx,1-oly:sny+oly)
65     _RL spval
66 heimbach 1.4 _RL spmax
67 jmc 1.6
68 heimbach 1.1 character*(80) fnamesalt
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 jmc 1.6
99 heimbach 1.4 spval = 25.
100     spmax = 40.
101 heimbach 1.1
102     c-- Read state record from global file.
103     doglobalread = .false.
104     ladinit = .false.
105 jmc 1.6
106 heimbach 1.1 #ifdef ALLOW_ARGO_SALT_COST_CONTRIBUTION
107    
108     if (optimcycle .ge. 0) then
109     ilu=ilnblnk( sbarfile )
110 jmc 1.6 write(fnamesalt(1:80),'(2a,i10.10)')
111 heimbach 1.3 & sbarfile(1:ilu),'.', optimcycle
112 heimbach 1.1 endif
113 jmc 1.6
114 heimbach 1.1 fcthread_argos = 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( fnamesalt, sbar, irec,
126     & doglobalread, ladinit,
127     & optimcycle, mythid
128     & , xx_sbar_mean_dummy )
129 jmc 1.6
130 heimbach 1.3 cnew(
131     iyear = mody + INT((modm-1+irec-1)/12)
132     imonth = 1 + MOD(modm-1+irec-1,12)
133     il=ilnblnk(argosfile)
134 jmc 1.6 write(fnametmp(1:80),'(2a,i4)')
135 heimbach 1.3 & argosfile(1:il), '_', iyear
136     inquire( file=fnametmp, exist=exst )
137     if (.NOT. exst) then
138     write(fnametmp(1:80),'(a)') argosfile(1:il)
139     imonth = irec
140     endif
141    
142     call mdsreadfield( fnametmp, cost_iprec, 'RL', nr, argosobs,
143     & imonth, mythid)
144     cnew)
145 heimbach 1.1
146     c-- Loop over this thread's tiles.
147     do bj = jtlo,jthi
148     do bi = itlo,ithi
149     c-- Loop over the model layers
150    
151     fctile_argos = 0. _d 0
152     do k = 1,nr
153    
154 jmc 1.6 c--
155 heimbach 1.1 cph(
156     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
157     cph below statement could be replaced by following
158     cph to make it independnet of Nr:
159     cph
160     cph if ( rC(K) .GT. -1000. ) then
161     cph)
162     do j = jmin,jmax
163 jmc 1.6 do i = imin,imax
164 heimbach 1.5 if ( (argosobs(i,j,k,bi,bj) .ge. spval) .and.
165     $ (argosobs(i,j,k,bi,bj) .lt. spmax) .and.
166 heimbach 1.8 cph $ (_hFacC(i,j,13,bi,bj) .ne. 0.) .and.
167 heimbach 1.5 $ (_hFacC(i,j,k,bi,bj) .ne. 0.) ) then
168 jmc 1.6 fctile_argos = fctile_argos +
169 heimbach 1.5 & wsalt2(i,j,k,bi,bj)*cosphi(i,j,bi,bj)*
170     & (sbar(i,j,k,bi,bj)-argosobs(i,j,k,bi,bj))*
171     & (sbar(i,j,k,bi,bj)-argosobs(i,j,k,bi,bj))
172     if ( wsalt2(i,j,k,bi,bj)*cosphi(i,j,bi,bj) .ne. 0. )
173     & num_argos(bi,bj) = num_argos(bi,bj) + 1. _d 0
174 jmc 1.6 endif
175 heimbach 1.5 enddo
176 heimbach 1.1 enddo
177     enddo
178     c-- End of loop over layers.
179    
180     fcthread_argos = fcthread_argos + fctile_argos
181 jmc 1.6 objf_argos(bi,bj) = objf_argos(bi,bj) + fctile_argos
182 heimbach 1.1
183     #ifdef ECCO_VERBOSE
184     write(msgbuf,'(a)') ' '
185     call print_message( msgbuf, standardmessageunit,
186     & SQUEEZE_RIGHT , mythid)
187     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3,i6)')
188 heimbach 1.3 & ' COST_ARGO_SALT: irec,bi,bj = ',irec,bi,bj
189 heimbach 1.1 call print_message( msgbuf, standardmessageunit,
190     & SQUEEZE_RIGHT , mythid)
191     write(msgbuf,'(a,d22.15)')
192     & ' COST_ARGO_SALT: cost function = ', fctile_argos
193     call print_message( msgbuf, standardmessageunit,
194     & SQUEEZE_RIGHT , mythid)
195     write(msgbuf,'(a)') ' '
196     call print_message( msgbuf, standardmessageunit,
197     & SQUEEZE_RIGHT , mythid)
198     #endif
199    
200     enddo
201     enddo
202    
203     #ifdef ECCO_VERBOSE
204     c-- Print cost function for all tiles.
205 jmc 1.7 c _GLOBAL_SUM_RL( fcthread_argos , myThid )
206 heimbach 1.1 write(msgbuf,'(a)') ' '
207     call print_message( msgbuf, standardmessageunit,
208     & SQUEEZE_RIGHT , mythid)
209     write(msgbuf,'(a,i8.8)')
210     & ' cost_ARGOT: irec = ',irec
211     call print_message( msgbuf, standardmessageunit,
212     & SQUEEZE_RIGHT , mythid)
213     write(msgbuf,'(a,a,d22.15)')
214     & ' global cost function value',
215     & ' ( ARGO salt. ) = ',fcthread_argos
216     call print_message( msgbuf, standardmessageunit,
217     & SQUEEZE_RIGHT , mythid)
218     write(msgbuf,'(a)') ' '
219     call print_message( msgbuf, standardmessageunit,
220     & SQUEEZE_RIGHT , mythid)
221     #endif
222    
223     enddo
224     c-- End of second loop over records.
225    
226     #else
227     c-- Do not enter the calculation of the ARGO salinity contribution
228     c-- to the final cost function.
229 jmc 1.6
230 heimbach 1.1 fctile_argos = 0. _d 0
231     fcthread_argos = 0. _d 0
232    
233     crg
234     nrec = 1
235     crg
236    
237     _BEGIN_MASTER( mythid )
238     write(msgbuf,'(a)') ' '
239     call print_message( msgbuf, standardmessageunit,
240     & SQUEEZE_RIGHT , mythid)
241     write(msgbuf,'(a,a)')
242     & ' cost_ARGOS: no contribution of ARGO salt ',
243     & ' to cost function.'
244     call print_message( msgbuf, standardmessageunit,
245     & SQUEEZE_RIGHT , mythid)
246     write(msgbuf,'(a,a,i9.8)')
247     & ' cost_ARGOS: number of records that would have',
248     & ' been processed: ',nrec
249     call print_message( msgbuf, standardmessageunit,
250     & SQUEEZE_RIGHT , mythid)
251     write(msgbuf,'(a)') ' '
252     call print_message( msgbuf, standardmessageunit,
253     & SQUEEZE_RIGHT , mythid)
254     _END_MASTER( mythid )
255     #endif
256    
257     return
258     end

  ViewVC Help
Powered by ViewVC 1.1.22