/[MITgcm]/MITgcm_contrib/heimbach/SO4x2/code_ad_nodiva/cost_salt.F
ViewVC logotype

Annotation of /MITgcm_contrib/heimbach/SO4x2/code_ad_nodiva/cost_salt.F

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


Revision 1.1 - (hide annotations) (download)
Thu Jan 26 06:27:12 2006 UTC (19 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: HEAD
Setup for Southern Ocean on coarse grid. Test-bed for high-res. adjoint.

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_salt.F,v 1.8 2005/10/15 18:27:32 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_salt( myiter, mytime, mythid )
7    
8     c ==================================================================
9     c SUBROUTINE cost_salt
10     c ==================================================================
11     c
12     c o Evaluate cost function contribution of salinity.
13     c
14     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
15     c
16     c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
17     c
18     c - Restructured the code in order to create a package
19     c for the MITgcmUV.
20     c
21     c changed: Patrick Heimbach heimbach@mit.edu 27-May-2000
22     c
23     c - set ladinit to .true. to initialise adsbar file
24     c
25     c ==================================================================
26     c SUBROUTINE cost_salt
27     c ==================================================================
28    
29     implicit none
30    
31     c == global variables ==
32    
33     #include "EEPARAMS.h"
34     #include "SIZE.h"
35     #include "PARAMS.h"
36     #include "GRID.h"
37     #include "DYNVARS.h"
38    
39     #include "cal.h"
40     #include "ecco_cost.h"
41     #include "ctrl.h"
42     #include "ctrl_dummy.h"
43     #include "optim.h"
44     #ifdef ALLOW_OBCS
45     #include "OBCS.h"
46     #endif
47    
48     c == routine arguments ==
49    
50     integer myiter
51     _RL mytime
52     integer mythid
53    
54     c == local variables ==
55    
56     integer bi,bj
57     integer i,j,k
58     integer itlo,ithi
59     integer jtlo,jthi
60     integer jmin,jmax
61     integer imin,imax
62     integer irec, irectmp
63     integer levmon
64     integer levoff
65     integer ilsalt
66    
67     _RL fctile
68     _RL fcthread
69    
70     _RL cmask (1-olx:snx+olx,1-oly:sny+oly)
71     _RL spval
72     _RL spmax
73    
74     character*(80) fnamesalt
75    
76     logical doglobalread
77     logical ladinit
78    
79     character*(MAX_LEN_MBUF) msgbuf
80    
81     #ifdef GENERIC_BAR_MONTH
82     integer mrec, nyears, iyear
83     #endif
84    
85     _RL diagnosfld3d(1-olx:snx+olx,1-oly:sny+oly,nr,nsx,nsy)
86    
87     c == external functions ==
88    
89     integer ilnblnk
90     external ilnblnk
91    
92     c == end of interface ==
93    
94     jtlo = mybylo(mythid)
95     jthi = mybyhi(mythid)
96     itlo = mybxlo(mythid)
97     ithi = mybxhi(mythid)
98     jmin = 1
99     jmax = sny
100     imin = 1
101     imax = snx
102    
103     spval = 25.
104     spmax = 40.
105    
106     c-- Read tiled data.
107     doglobalread = .false.
108     ladinit = .false.
109    
110     #ifdef ALLOW_SALT_COST_CONTRIBUTION
111    
112     if (optimcycle .ge. 0) then
113     ilsalt = ilnblnk( sbarfile )
114     write(fnamesalt(1:80),'(2a,i10.10)')
115     & sbarfile(1:ilsalt),'.',optimcycle
116     endif
117    
118     fcthread = 0. _d 0
119    
120     #ifdef GENERIC_BAR_MONTH
121     c-- Loop over month
122     do irec = 1,min(nmonsrec,12)
123     nyears=int((nmonsrec-irec)/12)+1
124     do iyear=1,nyears
125     mrec=irec+(iyear-1)*12
126     irectmp=mrec
127     c-- Read time averages and the monthly mean data.
128     call active_read_xyz( fnamesalt, sbar, mrec,
129     & doglobalread, ladinit,
130     & optimcycle, mythid,
131     & xx_sbar_mean_dummy )
132     do bj = jtlo,jthi
133     do bi = itlo,ithi
134     do k = 1,nr
135     do j = jmin,jmax
136     do i = imin,imax
137     if(iyear.eq.1) then
138     sbar_gen(i,j,k,bi,bj) =sbar(i,j,k,bi,bj)
139     elseif(iyear.eq.nyears) then
140     sbar(i,j,k,bi,bj) =(sbar_gen(i,j,k,bi,bj)
141     $ +sbar(i,j,k,bi,bj))/float(nyears)
142     else
143     sbar_gen(i,j,k,bi,bj) =sbar_gen(i,j,k,bi,bj)
144     $ +sbar(i,j,k,bi,bj)
145     endif
146     enddo
147     enddo
148     enddo
149     enddo
150     enddo
151     enddo
152     #else
153     c-- Loop over records.
154     do irec = 1,nmonsrec
155    
156     irectmp=irec
157     c-- Read time averages and the monthly mean data.
158     call active_read_xyz( fnamesalt, sbar, irec,
159     & doglobalread, ladinit,
160     & optimcycle, mythid,
161     & xx_sbar_mean_dummy )
162     #endif
163     c-- Determine the month to be read.
164     levoff = mod(modelstartdate(1)/100,100)
165     levmon = (irectmp-1) + levoff
166     levmon = mod(levmon-1,12)+1
167    
168     call mdsreadfield( sdatfile, cost_iprec, cost_yftype,
169     & nr, sdat, levmon, mythid)
170    
171     do bj = jtlo,jthi
172     do bi = itlo,ithi
173    
174     c-- Loop over the model layers
175     fctile = 0. _d 0
176     do k = 1,nr
177    
178     c-- Determine the mask or weights
179     do j = jmin,jmax
180     do i = imin,imax
181     cmask(i,j) = cosphi(i,j,bi,bj)
182     if (sdat(i,j,k,bi,bj) .eq. 0.) then
183     cmask(i,j) = 0. _d 0
184     else if (sdat(i,j,k,bi,bj) .lt. spval) then
185     cmask(i,j) = 0. _d 0
186     else if (sdat(i,j,k,bi,bj) .gt. spmax) then
187     cmask(i,j) = 0. _d 0
188     #ifdef ALLOW_OBCS_NORTH
189     else if (OB_Jn(i,bi,bj).EQ.j) THEN
190     cmask(i,j) = 0. _d 0
191     #endif
192     endif
193     enddo
194     enddo
195    
196     c-- Compute model data misfit and cost function term for
197     c the salinity field.
198     do j = jmin,jmax
199     do i = imin,imax
200     if ( _hFacC(i,j,k,bi,bj) .ne. 0. ) then
201     fctile = fctile +
202     & (wsaltLev(i,j,k,bi,bj)*cmask(i,j)*
203     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj))*
204     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj)) )
205     if ( wsaltLev(i,j,k,bi,bj)*cmask(i,j) .ne. 0. )
206     & num_salt(bi,bj) = num_salt(bi,bj) + 1. _d 0
207     diagnosfld3d(i,j,k,bi,bj) =
208     & (wsaltLev(i,j,k,bi,bj)*cmask(i,j)*
209     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj))*
210     & (sbar(i,j,k,bi,bj) - sdat(i,j,k,bi,bj)) )
211     else
212     diagnosfld3d(i,j,k,bi,bj) = 0.
213     endif
214     enddo
215     enddo
216    
217     enddo
218     c-- End of loop over layers.
219    
220     call mdswritefield( 'DiagnosCost_ClimSalt',
221     & writeBinaryPrec, globalfiles, 'RL', Nr,
222     & diagnosfld3d, irec, optimcycle, mythid )
223    
224     fcthread = fcthread + fctile
225     objf_salt(bi,bj) = objf_salt(bi,bj) + fctile
226    
227     enddo
228     enddo
229    
230     enddo
231     c-- End of loop over records.
232    
233     #endif
234    
235     return
236     end
237    

  ViewVC Help
Powered by ViewVC 1.1.22