/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_calc_rhs.F
ViewVC logotype

Annotation of /MITgcm/pkg/generic_advdiff/gad_calc_rhs.F

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


Revision 1.22 - (hide annotations) (download)
Thu Sep 25 03:01:59 2003 UTC (21 years, 9 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint52d_pre, checkpoint51o_pre, checkpoint51l_post, checkpoint52, checkpoint51f_post, checkpoint51t_post, checkpoint51n_post, checkpoint51s_post, checkpoint51j_post, checkpoint52e_pre, checkpoint51n_pre, checkpoint52b_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint52b_post, checkpoint52c_post, checkpoint51h_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint52d_post, checkpoint52a_pre, checkpoint51i_pre, branch-netcdf, checkpoint51o_post, checkpoint52a_post, checkpoint51g_post, ecco_c52_e35, checkpoint51m_post, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, netcdf-sm0, checkpoint51n_branch
Changes since 1.21: +2 -7 lines
o Mods and bug fixes to pkg/cal, pkg/exf, etc., needed for computation
  of tracer Green's fucntions for ocean inversion project.

1 dimitri 1.22 C $Header: /usr/local/gcmpack/MITgcm/pkg/generic_advdiff/gad_calc_rhs.F,v 1.21 2003/09/24 04:52:38 dimitri Exp $
2 jmc 1.2 C $Name: $
3 adcroft 1.1
4     #include "GAD_OPTIONS.h"
5    
6 adcroft 1.11 CBOP
7     C !ROUTINE: GAD_CALC_RHS
8    
9     C !INTERFACE: ==========================================================
10 adcroft 1.1 SUBROUTINE GAD_CALC_RHS(
11     I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12     I xA,yA,uTrans,vTrans,rTrans,maskUp,
13     I diffKh, diffK4, KappaRT, Tracer,
14 jmc 1.14 I tracerIdentity, advectionScheme, calcAdvection,
15 adcroft 1.1 U fVerT, gTracer,
16     I myThid )
17 adcroft 1.11
18     C !DESCRIPTION:
19     C Calculates the tendancy of a tracer due to advection and diffusion.
20     C It calculates the fluxes in each direction indepentently and then
21     C sets the tendancy to the divergence of these fluxes. The advective
22     C fluxes are only calculated here when using the linear advection schemes
23     C otherwise only the diffusive and parameterized fluxes are calculated.
24     C
25     C Contributions to the flux are calculated and added:
26     C \begin{equation*}
27     C {\bf F} = {\bf F}_{adv} + {\bf F}_{diff} +{\bf F}_{GM} + {\bf F}_{KPP}
28     C \end{equation*}
29     C
30     C The tendancy is the divergence of the fluxes:
31     C \begin{equation*}
32     C G_\theta = G_\theta + \nabla \cdot {\bf F}
33     C \end{equation*}
34     C
35     C The tendancy is assumed to contain data on entry.
36    
37     C !USES: ===============================================================
38 adcroft 1.1 IMPLICIT NONE
39     #include "SIZE.h"
40     #include "EEPARAMS.h"
41     #include "PARAMS.h"
42     #include "GRID.h"
43     #include "DYNVARS.h"
44 jmc 1.16 #include "SURFACE.h"
45 adcroft 1.1 #include "GAD.h"
46    
47 heimbach 1.13 #ifdef ALLOW_AUTODIFF_TAMC
48     #include "tamc.h"
49     #include "tamc_keys.h"
50     #endif /* ALLOW_AUTODIFF_TAMC */
51    
52 adcroft 1.11 C !INPUT PARAMETERS: ===================================================
53     C bi,bj :: tile indices
54     C iMin,iMax,jMin,jMax :: loop range for called routines
55     C kup :: index into 2 1/2D array, toggles between 1 and 2
56     C kdown :: index into 2 1/2D array, toggles between 2 and 1
57     C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
58     C xA,yA :: areas of X and Y face of tracer cells
59     C uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
60     C maskUp :: 2-D array for mask at W points
61     C diffKh :: horizontal diffusion coefficient
62     C diffK4 :: bi-harmonic diffusion coefficient
63     C KappaRT :: 3-D array for vertical diffusion coefficient
64     C Tracer :: tracer field
65 dimitri 1.19 C tracerIdentity :: identifier for the tracer (required for KPP and GM)
66 adcroft 1.11 C advectionScheme :: advection scheme to use
67 jmc 1.14 C calcAdvection :: =False if Advec terms computed with multiDim scheme
68 adcroft 1.11 C myThid :: thread number
69     INTEGER bi,bj,iMin,iMax,jMin,jMax
70 adcroft 1.1 INTEGER k,kUp,kDown,kM1
71     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73     _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74     _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75     _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76     _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77     _RL diffKh, diffK4
78     _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
79     _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
80     INTEGER tracerIdentity
81 adcroft 1.3 INTEGER advectionScheme
82 jmc 1.14 LOGICAL calcAdvection
83 adcroft 1.11 INTEGER myThid
84    
85     C !OUTPUT PARAMETERS: ==================================================
86     C gTracer :: tendancy array
87     C fVerT :: 2 1/2D arrays for vertical advective flux
88     _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
89 adcroft 1.1 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
90    
91 adcroft 1.11 C !LOCAL VARIABLES: ====================================================
92     C i,j :: loop indices
93     C df4 :: used for storing del^2 T for bi-harmonic term
94     C fZon :: zonal flux
95     C fmer :: meridional flux
96     C af :: advective flux
97     C df :: diffusive flux
98     C localT :: local copy of tracer field
99 adcroft 1.1 INTEGER i,j
100     _RL df4 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101     _RL fZon (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102     _RL fMer (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103     _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104     _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105     _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 adcroft 1.11 CEOP
107 adcroft 1.1
108     #ifdef ALLOW_AUTODIFF_TAMC
109     C-- only the kUp part of fverT is set in this subroutine
110     C-- the kDown is still required
111     fVerT(1,1,kDown) = fVerT(1,1,kDown)
112     #endif
113 heimbach 1.13
114 adcroft 1.1 DO j=1-OLy,sNy+OLy
115     DO i=1-OLx,sNx+OLx
116 heimbach 1.12 fZon(i,j) = 0. _d 0
117     fMer(i,j) = 0. _d 0
118     fVerT(i,j,kUp) = 0. _d 0
119 heimbach 1.13 df(i,j) = 0. _d 0
120     df4(i,j) = 0. _d 0
121     localT(i,j) = 0. _d 0
122 adcroft 1.1 ENDDO
123     ENDDO
124    
125     C-- Make local copy of tracer array
126     DO j=1-OLy,sNy+OLy
127     DO i=1-OLx,sNx+OLx
128     localT(i,j)=tracer(i,j,k,bi,bj)
129     ENDDO
130     ENDDO
131    
132 adcroft 1.8 C-- Unless we have already calculated the advection terms we initialize
133     C the tendency to zero.
134 jmc 1.20 C <== now done earlier at the beginning of thermodynamics.
135     c IF (calcAdvection) THEN
136     c DO j=1-Oly,sNy+Oly
137     c DO i=1-Olx,sNx+Olx
138     c gTracer(i,j,k,bi,bj)=0. _d 0
139     c ENDDO
140     c ENDDO
141     c ENDIF
142 adcroft 1.1
143     C-- Pre-calculate del^2 T if bi-harmonic coefficient is non-zero
144     IF (diffK4 .NE. 0.) THEN
145     CALL GAD_GRAD_X(bi,bj,k,xA,localT,fZon,myThid)
146     CALL GAD_GRAD_Y(bi,bj,k,yA,localT,fMer,myThid)
147     CALL GAD_DEL2(bi,bj,k,fZon,fMer,df4,myThid)
148     ENDIF
149    
150     C-- Initialize net flux in X direction
151     DO j=1-Oly,sNy+Oly
152     DO i=1-Olx,sNx+Olx
153 heimbach 1.12 fZon(i,j) = 0. _d 0
154 adcroft 1.1 ENDDO
155     ENDDO
156    
157     C- Advective flux in X
158 jmc 1.14 IF (calcAdvection) THEN
159 adcroft 1.3 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
160 adcroft 1.1 CALL GAD_C2_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
161 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
162 adcroft 1.1 CALL GAD_FLUXLIMIT_ADV_X(
163     & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
164 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
165 jmc 1.2 CALL GAD_U3_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
166 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
167 adcroft 1.1 CALL GAD_C4_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
168 adcroft 1.4 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
169     CALL GAD_DST3_ADV_X(
170     & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
171     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
172     CALL GAD_DST3FL_ADV_X(
173     & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
174 adcroft 1.1 ELSE
175 adcroft 1.3 STOP 'GAD_CALC_RHS: Bad advectionScheme (X)'
176 adcroft 1.1 ENDIF
177 adcroft 1.5 DO j=1-Oly,sNy+Oly
178     DO i=1-Olx,sNx+Olx
179 adcroft 1.1 fZon(i,j) = fZon(i,j) + af(i,j)
180     ENDDO
181     ENDDO
182 adcroft 1.8 ENDIF
183 adcroft 1.1
184     C- Diffusive flux in X
185     IF (diffKh.NE.0.) THEN
186     CALL GAD_DIFF_X(bi,bj,k,xA,diffKh,localT,df,myThid)
187     ELSE
188 adcroft 1.5 DO j=1-Oly,sNy+Oly
189     DO i=1-Olx,sNx+Olx
190 heimbach 1.12 df(i,j) = 0. _d 0
191 adcroft 1.1 ENDDO
192     ENDDO
193     ENDIF
194    
195     #ifdef ALLOW_GMREDI
196     C- GM/Redi flux in X
197     IF (useGMRedi) THEN
198     C *note* should update GMREDI_XTRANSPORT to use localT and set df *aja*
199     CALL GMREDI_XTRANSPORT(
200     I iMin,iMax,jMin,jMax,bi,bj,K,
201 heimbach 1.15 I xA,Tracer,tracerIdentity,
202 adcroft 1.1 U df,
203     I myThid)
204     ENDIF
205     #endif
206 adcroft 1.5 DO j=1-Oly,sNy+Oly
207     DO i=1-Olx,sNx+Olx
208 adcroft 1.1 fZon(i,j) = fZon(i,j) + df(i,j)
209     ENDDO
210     ENDDO
211    
212     C- Bi-harmonic duffusive flux in X
213     IF (diffK4 .NE. 0.) THEN
214     CALL GAD_BIHARM_X(bi,bj,k,xA,df4,diffK4,df,myThid)
215 adcroft 1.5 DO j=1-Oly,sNy+Oly
216     DO i=1-Olx,sNx+Olx
217 adcroft 1.1 fZon(i,j) = fZon(i,j) + df(i,j)
218     ENDDO
219     ENDDO
220     ENDIF
221    
222     C-- Initialize net flux in Y direction
223     DO j=1-Oly,sNy+Oly
224     DO i=1-Olx,sNx+Olx
225 heimbach 1.12 fMer(i,j) = 0. _d 0
226 adcroft 1.1 ENDDO
227     ENDDO
228    
229     C- Advective flux in Y
230 jmc 1.14 IF (calcAdvection) THEN
231 adcroft 1.3 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
232 adcroft 1.1 CALL GAD_C2_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
233 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
234 adcroft 1.1 CALL GAD_FLUXLIMIT_ADV_Y(
235     & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
236 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
237 jmc 1.2 CALL GAD_U3_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
238 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
239 adcroft 1.1 CALL GAD_C4_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
240 adcroft 1.4 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
241     CALL GAD_DST3_ADV_Y(
242     & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
243     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
244     CALL GAD_DST3FL_ADV_Y(
245     & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
246 adcroft 1.1 ELSE
247 adcroft 1.3 STOP 'GAD_CALC_RHS: Bad advectionScheme (Y)'
248 adcroft 1.1 ENDIF
249     DO j=1-Oly,sNy+Oly
250     DO i=1-Olx,sNx+Olx
251     fMer(i,j) = fMer(i,j) + af(i,j)
252     ENDDO
253     ENDDO
254 adcroft 1.8 ENDIF
255 adcroft 1.1
256     C- Diffusive flux in Y
257     IF (diffKh.NE.0.) THEN
258     CALL GAD_DIFF_Y(bi,bj,k,yA,diffKh,localT,df,myThid)
259     ELSE
260     DO j=1-Oly,sNy+Oly
261     DO i=1-Olx,sNx+Olx
262 heimbach 1.12 df(i,j) = 0. _d 0
263 adcroft 1.1 ENDDO
264     ENDDO
265     ENDIF
266    
267     #ifdef ALLOW_GMREDI
268     C- GM/Redi flux in Y
269     IF (useGMRedi) THEN
270 heimbach 1.7 C *note* should update GMREDI_YTRANSPORT to use localT and set df *aja*
271 adcroft 1.1 CALL GMREDI_YTRANSPORT(
272     I iMin,iMax,jMin,jMax,bi,bj,K,
273 heimbach 1.15 I yA,Tracer,tracerIdentity,
274 adcroft 1.1 U df,
275     I myThid)
276     ENDIF
277     #endif
278     DO j=1-Oly,sNy+Oly
279     DO i=1-Olx,sNx+Olx
280     fMer(i,j) = fMer(i,j) + df(i,j)
281     ENDDO
282     ENDDO
283    
284     C- Bi-harmonic flux in Y
285     IF (diffK4 .NE. 0.) THEN
286     CALL GAD_BIHARM_Y(bi,bj,k,yA,df4,diffK4,df,myThid)
287     DO j=1-Oly,sNy+Oly
288     DO i=1-Olx,sNx+Olx
289     fMer(i,j) = fMer(i,j) + df(i,j)
290     ENDDO
291     ENDDO
292     ENDIF
293    
294 jmc 1.16 #ifdef NONLIN_FRSURF
295     C-- Compute vertical flux fVerT(kDown) at interface k+1 (between k & k+1):
296     IF ( calcAdvection .AND. K.EQ.Nr .AND.
297     & useRealFreshWaterFlux .AND.
298     & buoyancyRelation .EQ. 'OCEANICP' ) THEN
299     DO j=1-Oly,sNy+Oly
300     DO i=1-Olx,sNx+Olx
301     fVerT(i,j,kDown) = convertEmP2rUnit*PmEpR(i,j,bi,bj)
302     & *rA(i,j,bi,bj)*maskC(i,j,k,bi,bj)*Tracer(i,j,k,bi,bj)
303     ENDDO
304     ENDDO
305     ENDIF
306     #endif /* NONLIN_FRSURF */
307    
308     C-- Compute vertical flux fVerT(kUp) at interface k (between k-1 & k):
309 adcroft 1.1 C- Advective flux in R
310 jmc 1.14 IF (calcAdvection) THEN
311 jmc 1.2 C Note: wVel needs to be masked
312     IF (K.GE.2) THEN
313     C- Compute vertical advective flux in the interior:
314 adcroft 1.3 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
315 jmc 1.2 CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
316 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
317 jmc 1.2 CALL GAD_FLUXLIMIT_ADV_R(
318 adcroft 1.1 & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
319 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
320 jmc 1.2 CALL GAD_U3_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
321 adcroft 1.3 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
322 jmc 1.2 CALL GAD_C4_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
323 adcroft 1.4 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
324 adcroft 1.9 CALL GAD_DST3_ADV_R(
325     & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
326 adcroft 1.4 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
327 adcroft 1.9 CALL GAD_DST3FL_ADV_R(
328     & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
329 jmc 1.2 ELSE
330 adcroft 1.3 STOP 'GAD_CALC_RHS: Bad advectionScheme (R)'
331 jmc 1.2 ENDIF
332     C- Surface "correction" term at k>1 :
333     DO j=1-Oly,sNy+Oly
334     DO i=1-Olx,sNx+Olx
335     af(i,j) = af(i,j)
336     & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
337     & rTrans(i,j)*Tracer(i,j,k,bi,bj)
338     ENDDO
339     ENDDO
340 adcroft 1.1 ELSE
341 jmc 1.2 C- Surface "correction" term at k=1 :
342     DO j=1-Oly,sNy+Oly
343     DO i=1-Olx,sNx+Olx
344     af(i,j) = rTrans(i,j)*Tracer(i,j,k,bi,bj)
345     ENDDO
346     ENDDO
347 adcroft 1.1 ENDIF
348 jmc 1.2 C- add the advective flux to fVerT
349 adcroft 1.5 DO j=1-Oly,sNy+Oly
350     DO i=1-Olx,sNx+Olx
351 adcroft 1.11 fVerT(i,j,kUp) = fVerT(i,j,kUp) + af(i,j)
352 adcroft 1.1 ENDDO
353     ENDDO
354 adcroft 1.8 ENDIF
355 adcroft 1.1
356     C- Diffusive flux in R
357     C Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
358     C boundary condition.
359     IF (implicitDiffusion) THEN
360 adcroft 1.5 DO j=1-Oly,sNy+Oly
361     DO i=1-Olx,sNx+Olx
362 heimbach 1.12 df(i,j) = 0. _d 0
363 adcroft 1.1 ENDDO
364     ENDDO
365     ELSE
366     CALL GAD_DIFF_R(bi,bj,k,KappaRT,tracer,df,myThid)
367     ENDIF
368    
369     #ifdef ALLOW_GMREDI
370     C- GM/Redi flux in R
371     IF (useGMRedi) THEN
372     C *note* should update GMREDI_RTRANSPORT to set df *aja*
373     CALL GMREDI_RTRANSPORT(
374     I iMin,iMax,jMin,jMax,bi,bj,K,
375 heimbach 1.15 I Tracer,tracerIdentity,
376 adcroft 1.1 U df,
377     I myThid)
378     ENDIF
379     #endif
380    
381 adcroft 1.5 DO j=1-Oly,sNy+Oly
382     DO i=1-Olx,sNx+Olx
383 adcroft 1.11 fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
384 adcroft 1.1 ENDDO
385     ENDDO
386    
387     #ifdef ALLOW_KPP
388     C- Add non local KPP transport term (ghat) to diffusive T flux.
389     IF (useKPP) THEN
390 adcroft 1.5 DO j=1-Oly,sNy+Oly
391     DO i=1-Olx,sNx+Olx
392 heimbach 1.12 df(i,j) = 0. _d 0
393 adcroft 1.1 ENDDO
394     ENDDO
395     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
396     C *note* should update KPP_TRANSPORT_T to set df *aja*
397     CALL KPP_TRANSPORT_T(
398     I iMin,iMax,jMin,jMax,bi,bj,k,km1,
399     I KappaRT,
400     U df )
401     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
402     CALL KPP_TRANSPORT_S(
403     I iMin,iMax,jMin,jMax,bi,bj,k,km1,
404     I KappaRT,
405     U df )
406 mlosch 1.18 #ifdef ALLOW_PTRACERS
407 dimitri 1.22 ELSEIF (tracerIdentity .GE. GAD_TR1) THEN
408 mlosch 1.18 CALL KPP_TRANSPORT_PTR(
409     I iMin,iMax,jMin,jMax,bi,bj,k,km1,
410 dimitri 1.21 I tracerIdentity-GAD_TR1+1,KappaRT,
411 mlosch 1.18 U df )
412     #endif
413 adcroft 1.1 ELSE
414 mlosch 1.18 PRINT*,'invalid tracer indentity: ', tracerIdentity
415 adcroft 1.1 STOP 'GAD_CALC_RHS: Ooops'
416     ENDIF
417 adcroft 1.5 DO j=1-Oly,sNy+Oly
418     DO i=1-Olx,sNx+Olx
419 adcroft 1.11 fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
420 adcroft 1.1 ENDDO
421     ENDDO
422     ENDIF
423     #endif
424    
425     C-- Divergence of fluxes
426 adcroft 1.10 DO j=1-Oly,sNy+Oly-1
427     DO i=1-Olx,sNx+Olx-1
428 adcroft 1.8 gTracer(i,j,k,bi,bj)=gTracer(i,j,k,bi,bj)
429 adcroft 1.1 & -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
430     & *recip_rA(i,j,bi,bj)
431     & *(
432     & +( fZon(i+1,j)-fZon(i,j) )
433     & +( fMer(i,j+1)-fMer(i,j) )
434     & +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
435     & )
436     ENDDO
437     ENDDO
438 jmc 1.17
439     #ifdef NONLIN_FRSURF
440     C-- account for 3.D divergence of the flow in rStar coordinate:
441     IF (calcAdvection .AND. select_rStar.GT.0) THEN
442     DO j=1-Oly,sNy+Oly-1
443     DO i=1-Olx,sNx+Olx-1
444     gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
445     & - (rStarExpC(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
446     & *tracer(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
447     ENDDO
448     ENDDO
449     ENDIF
450     IF (calcAdvection .AND. select_rStar.LT.0) THEN
451     DO j=1-Oly,sNy+Oly-1
452     DO i=1-Olx,sNx+Olx-1
453     gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
454     & - rStarDhCDt(i,j,bi,bj)
455     & *tracer(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
456     ENDDO
457     ENDDO
458     ENDIF
459     #endif /* NONLIN_FRSURF */
460    
461 adcroft 1.1
462     RETURN
463     END

  ViewVC Help
Powered by ViewVC 1.1.22