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

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

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


Revision 1.13 - (hide annotations) (download)
Sat Jul 13 04:59:42 2002 UTC (21 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46l_post, checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46l_pre, checkpoint46d_pre, checkpoint46j_pre, checkpoint46a_post, checkpoint46j_post, checkpoint46k_post, checkpoint46e_pre, checkpoint46b_pre, checkpoint46c_pre, checkpoint46, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint46g_post, checkpoint46i_post, checkpoint46c_post, checkpoint46e_post, checkpoint46h_post, checkpoint46d_post
Changes since 1.12: +1 -1 lines
Merging from release1_p5 (cf. tag-index for checkpoint46).

1 heimbach 1.13 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.8.4.2 2002/07/11 21:43:28 jmc Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4 adcroft 1.4 CBOI
5     C !TITLE: pkg/generic\_advdiff
6     C !AUTHORS: adcroft@mit.edu
7 adcroft 1.8 C !INTRODUCTION: Generic Advection Diffusion Package
8 adcroft 1.4 C
9     C Package "generic\_advdiff" provides a common set of routines for calculating
10     C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).
11     C
12     C Many different advection schemes are available: the standard centered
13     C second order, centered fourth order and upwind biased third order schemes
14     C are known as linear methods and require some stable time-stepping method
15     C such as Adams-Bashforth. Alternatives such as flux-limited schemes are
16     C stable in the forward sense and are best combined with the multi-dimensional
17     C method provided in gad\_advection.
18     C
19     C There are two high-level routines:
20     C \begin{itemize}
21     C \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used
22     C for the standard linear schemes. This must be used in conjuction with
23     C Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are
24     C always calculated here.
25     C \item{GAD\_ADVECTION} calculates just the advective fluxes using the
26     C non-linear schemes and can not be used in conjuction with Adams-Bashforth
27     C time-stepping.
28     C \end{itemize}
29     CEOI
30    
31 adcroft 1.1 #include "GAD_OPTIONS.h"
32    
33 adcroft 1.4 CBOP
34     C !ROUTINE: GAD_ADVECTION
35    
36     C !INTERFACE: ==========================================================
37 adcroft 1.1 SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
38     U Tracer,Gtracer,
39     I myTime,myIter,myThid)
40 adcroft 1.4
41     C !DESCRIPTION:
42     C Calculates the tendancy of a tracer due to advection.
43     C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
44     C and can only be used for the non-linear advection schemes such as the
45     C direct-space-time method and flux-limiters.
46     C
47     C The algorithm is as follows:
48     C \begin{itemize}
49     C \item{$\theta^{(n+1/3)} = \theta^{(n)}
50 adcroft 1.5 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
51 adcroft 1.4 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
52 adcroft 1.5 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
53 adcroft 1.4 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
54 adcroft 1.5 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
55 adcroft 1.4 C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
56     C \end{itemize}
57     C
58     C The tendancy (output) is over-written by this routine.
59    
60     C !USES: ===============================================================
61 adcroft 1.1 IMPLICIT NONE
62     #include "SIZE.h"
63     #include "EEPARAMS.h"
64     #include "PARAMS.h"
65     #include "DYNVARS.h"
66     #include "GRID.h"
67     #include "GAD.h"
68 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
69     # include "tamc.h"
70     # include "tamc_keys.h"
71     #endif
72 adcroft 1.1
73 adcroft 1.4 C !INPUT PARAMETERS: ===================================================
74     C bi,bj :: tile indices
75     C advectionScheme :: advection scheme to use
76     C tracerIdentity :: identifier for the tracer (required only for OBCS)
77     C Tracer :: tracer field
78     C myTime :: current time
79     C myIter :: iteration number
80     C myThid :: thread number
81 adcroft 1.1 INTEGER bi,bj
82     INTEGER advectionScheme
83     INTEGER tracerIdentity
84 adcroft 1.9 _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85 adcroft 1.1 _RL myTime
86     INTEGER myIter
87     INTEGER myThid
88    
89 adcroft 1.4 C !OUTPUT PARAMETERS: ==================================================
90     C gTracer :: tendancy array
91 adcroft 1.9 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
92 adcroft 1.4
93     C !LOCAL VARIABLES: ====================================================
94     C maskUp :: 2-D array for mask at W points
95     C iMin,iMax,jMin,jMax :: loop range for called routines
96     C i,j,k :: loop indices
97     C kup :: index into 2 1/2D array, toggles between 1 and 2
98     C kdown :: index into 2 1/2D array, toggles between 2 and 1
99     C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
100     C xA,yA :: areas of X and Y face of tracer cells
101     C uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
102 jmc 1.11 C rTransKp1 :: vertical volume transport at interface k+1
103 adcroft 1.4 C af :: 2-D array for horizontal advective flux
104     C fVerT :: 2 1/2D arrays for vertical advective flux
105     C localTij :: 2-D array used as temporary local copy of tracer fld
106     C localTijk :: 3-D array used as temporary local copy of tracer fld
107     C kp1Msk :: flag (0,1) to act as over-riding mask for W levels
108     C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
109     C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
110     C nipass :: number of passes to make in multi-dimensional method
111     C ipass :: number of the current pass being made
112 adcroft 1.1 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113     INTEGER iMin,iMax,jMin,jMax
114 jmc 1.11 INTEGER i,j,k,kup,kDown
115 adcroft 1.1 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117     _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118     _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119     _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 jmc 1.11 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121 adcroft 1.1 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122     _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
123     _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124     _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
125     _RL kp1Msk
126 adcroft 1.3 LOGICAL calc_fluxes_X,calc_fluxes_Y
127     INTEGER nipass,ipass
128 adcroft 1.4 CEOP
129 adcroft 1.1
130 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
131     act1 = bi - myBxLo(myThid)
132     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
133     act2 = bj - myByLo(myThid)
134     max2 = myByHi(myThid) - myByLo(myThid) + 1
135     act3 = myThid - 1
136     max3 = nTx*nTy
137     act4 = ikey_dynamics - 1
138     ikey = (act1 + 1) + act2*max1
139     & + act3*max1*max2
140     & + act4*max1*max2*max3
141     #endif /* ALLOW_AUTODIFF_TAMC */
142    
143 adcroft 1.1 C-- Set up work arrays with valid (i.e. not NaN) values
144     C These inital values do not alter the numerical results. They
145     C just ensure that all memory references are to valid floating
146     C point numbers. This prevents spurious hardware signals due to
147     C uninitialised but inert locations.
148     DO j=1-OLy,sNy+OLy
149     DO i=1-OLx,sNx+OLx
150     xA(i,j) = 0. _d 0
151     yA(i,j) = 0. _d 0
152     uTrans(i,j) = 0. _d 0
153     vTrans(i,j) = 0. _d 0
154     rTrans(i,j) = 0. _d 0
155     fVerT(i,j,1) = 0. _d 0
156     fVerT(i,j,2) = 0. _d 0
157 jmc 1.11 rTransKp1(i,j)= 0. _d 0
158 adcroft 1.1 ENDDO
159     ENDDO
160    
161     iMin = 1-OLx
162     iMax = sNx+OLx
163     jMin = 1-OLy
164     jMax = sNy+OLy
165    
166     C-- Start of k loop for horizontal fluxes
167     DO k=1,Nr
168 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
169     kkey = (ikey-1)*Nr + k
170     CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
171     #endif /* ALLOW_AUTODIFF_TAMC */
172 adcroft 1.1
173     C-- Get temporary terms used by tendency routines
174     CALL CALC_COMMON_FACTORS (
175     I bi,bj,iMin,iMax,jMin,jMax,k,
176     O xA,yA,uTrans,vTrans,rTrans,maskUp,
177     I myThid)
178    
179 jmc 1.11 #ifdef ALLOW_GMREDI
180     C-- Residual transp = Bolus transp + Eulerian transp
181     IF (useGMRedi)
182     & CALL GMREDI_CALC_UVFLOW(
183     & uTrans, vTrans, bi, bj, k, myThid)
184     #endif /* ALLOW_GMREDI */
185    
186 adcroft 1.1 C-- Make local copy of tracer array
187     DO j=1-OLy,sNy+OLy
188     DO i=1-OLx,sNx+OLx
189     localTij(i,j)=tracer(i,j,k,bi,bj)
190     ENDDO
191     ENDDO
192    
193 adcroft 1.3 IF (useCubedSphereExchange) THEN
194     nipass=3
195     ELSE
196     nipass=1
197     ENDIF
198 heimbach 1.6 cph nipass=1
199 adcroft 1.3
200     C-- Multiple passes for different directions on different tiles
201     DO ipass=1,nipass
202 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
203     passkey = ipass + (k-1) *maxpass
204     & + (ikey-1)*maxpass*Nr
205     IF (nipass .GT. maxpass) THEN
206     STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'
207     ENDIF
208     #endif /* ALLOW_AUTODIFF_TAMC */
209 adcroft 1.3
210     IF (nipass.EQ.3) THEN
211     calc_fluxes_X=.FALSE.
212     calc_fluxes_Y=.FALSE.
213     IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
214     calc_fluxes_X=.TRUE.
215     ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
216     calc_fluxes_Y=.TRUE.
217     ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
218     calc_fluxes_Y=.TRUE.
219     ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
220     calc_fluxes_X=.TRUE.
221     ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
222     calc_fluxes_Y=.TRUE.
223     ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
224     calc_fluxes_X=.TRUE.
225     ENDIF
226     ELSE
227     calc_fluxes_X=.TRUE.
228     calc_fluxes_Y=.TRUE.
229     ENDIF
230    
231     C-- X direction
232     IF (calc_fluxes_X) THEN
233    
234     C-- Internal exchange for calculations in X
235     IF (useCubedSphereExchange) THEN
236     DO j=1,Oly
237     DO i=1,Olx
238     localTij( 1-i , 1-j )=localTij( 1-j , i )
239     localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
240     localTij(sNx+i, 1-j )=localTij(sNx+j, i )
241     localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
242     ENDDO
243     ENDDO
244     ENDIF
245    
246 adcroft 1.1 C- Advective flux in X
247     DO j=1-Oly,sNy+Oly
248     DO i=1-Olx,sNx+Olx
249     af(i,j) = 0.
250     ENDDO
251     ENDDO
252 heimbach 1.6
253     #ifdef ALLOW_AUTODIFF_TAMC
254 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
255 heimbach 1.6 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
256     #endif
257     #endif /* ALLOW_AUTODIFF_TAMC */
258    
259 adcroft 1.1 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
260     CALL GAD_FLUXLIMIT_ADV_X(
261     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
262     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
263     CALL GAD_DST3_ADV_X(
264     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
265     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
266     CALL GAD_DST3FL_ADV_X(
267     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
268     ELSE
269 adcroft 1.9 STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
270 adcroft 1.1 ENDIF
271 heimbach 1.6
272 adcroft 1.1 DO j=1-Oly,sNy+Oly
273     DO i=1-Olx,sNx+Olx-1
274     localTij(i,j)=localTij(i,j)-deltaTtracer*
275     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
276     & *recip_rA(i,j,bi,bj)
277     & *( af(i+1,j)-af(i,j)
278     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
279     & )
280     ENDDO
281     ENDDO
282    
283     #ifdef ALLOW_OBCS
284     C-- Apply open boundary conditions
285     IF (useOBCS) THEN
286     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
287     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
288     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
289     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
290     END IF
291     END IF
292     #endif /* ALLOW_OBCS */
293    
294 adcroft 1.3 C-- End of X direction
295     ENDIF
296    
297     C-- Y direction
298     IF (calc_fluxes_Y) THEN
299    
300     C-- Internal exchange for calculations in Y
301     IF (useCubedSphereExchange) THEN
302     DO j=1,Oly
303     DO i=1,Olx
304     localTij( 1-i , 1-j )=localTij( j , 1-i )
305     localTij( 1-i ,sNy+j)=localTij( j ,sNy+i)
306     localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
307     localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
308     ENDDO
309     ENDDO
310     ENDIF
311    
312 adcroft 1.1 C- Advective flux in Y
313     DO j=1-Oly,sNy+Oly
314     DO i=1-Olx,sNx+Olx
315     af(i,j) = 0.
316     ENDDO
317     ENDDO
318 heimbach 1.6
319     #ifdef ALLOW_AUTODIFF_TAMC
320 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
321 heimbach 1.6 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
322     #endif
323     #endif /* ALLOW_AUTODIFF_TAMC */
324    
325 adcroft 1.1 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
326     CALL GAD_FLUXLIMIT_ADV_Y(
327     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
328     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
329     CALL GAD_DST3_ADV_Y(
330     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
331     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
332     CALL GAD_DST3FL_ADV_Y(
333     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
334     ELSE
335     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
336     ENDIF
337 heimbach 1.6
338 adcroft 1.1 DO j=1-Oly,sNy+Oly-1
339     DO i=1-Olx,sNx+Olx
340     localTij(i,j)=localTij(i,j)-deltaTtracer*
341     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
342     & *recip_rA(i,j,bi,bj)
343     & *( af(i,j+1)-af(i,j)
344     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
345     & )
346     ENDDO
347     ENDDO
348 adcroft 1.3
349 adcroft 1.1 #ifdef ALLOW_OBCS
350     C-- Apply open boundary conditions
351     IF (useOBCS) THEN
352     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
353     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
354     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
355     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
356     END IF
357     END IF
358     #endif /* ALLOW_OBCS */
359 adcroft 1.3
360     C-- End of Y direction
361     ENDIF
362    
363     DO j=1-Oly,sNy+Oly
364 adcroft 1.1 DO i=1-Olx,sNx+Olx
365     localTijk(i,j,k)=localTij(i,j)
366     ENDDO
367     ENDDO
368    
369 adcroft 1.3 C-- End of ipass loop
370     ENDDO
371 adcroft 1.1
372     C-- End of K loop for horizontal fluxes
373     ENDDO
374    
375     C-- Start of k loop for vertical flux
376     DO k=Nr,1,-1
377 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
378     kkey = (ikey-1)*Nr + k
379     #endif /* ALLOW_AUTODIFF_TAMC */
380 adcroft 1.1
381     C-- kup Cycles through 1,2 to point to w-layer above
382     C-- kDown Cycles through 2,1 to point to w-layer below
383     kup = 1+MOD(k+1,2)
384     kDown= 1+MOD(k,2)
385 jmc 1.11 c kp1=min(Nr,k+1)
386     kp1Msk=1.
387     if (k.EQ.Nr) kp1Msk=0.
388 heimbach 1.6
389     #ifdef ALLOW_AUTODIFF_TAMC
390     CADJ STORE localTijk(:,:,k)
391 heimbach 1.12 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
392     CADJ STORE rTrans(:,:)
393 heimbach 1.6 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
394     #endif /* ALLOW_AUTODIFF_TAMC */
395 adcroft 1.1
396 jmc 1.11 C-- Compute Vertical transport
397 adcroft 1.1 C Note: wVel needs to be masked
398 jmc 1.11
399     IF (k.EQ.1) THEN
400     C- Surface interface :
401    
402     DO j=1-Oly,sNy+Oly
403     DO i=1-Olx,sNx+Olx
404     rTransKp1(i,j) = rTrans(i,j)
405     rTrans(i,j) = 0.
406     fVerT(i,j,kUp) = 0.
407     ENDDO
408     ENDDO
409    
410     ELSE
411     C- Interior interface :
412     DO j=1-Oly,sNy+Oly
413     DO i=1-Olx,sNx+Olx
414     rTransKp1(i,j) = kp1Msk*rTrans(i,j)
415     rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
416     & *maskC(i,j,k-1,bi,bj)
417     af(i,j) = 0.
418     ENDDO
419     ENDDO
420    
421     #ifdef ALLOW_GMREDI
422     C-- Residual transp = Bolus transp + Eulerian transp
423     IF (useGMRedi)
424     & CALL GMREDI_CALC_WFLOW(
425     & rTrans, bi, bj, k, myThid)
426     #endif /* ALLOW_GMREDI */
427    
428 adcroft 1.1 C- Compute vertical advective flux in the interior:
429     IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
430     CALL GAD_FLUXLIMIT_ADV_R(
431     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
432     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
433 adcroft 1.2 CALL GAD_DST3_ADV_R(
434     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
435 adcroft 1.1 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
436 adcroft 1.2 CALL GAD_DST3FL_ADV_R(
437     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
438 adcroft 1.1 ELSE
439     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
440     ENDIF
441 jmc 1.11 C- add the advective flux to fVerT
442 adcroft 1.1 DO j=1-Oly,sNy+Oly
443     DO i=1-Olx,sNx+Olx
444 jmc 1.11 fVerT(i,j,kUp) = af(i,j)
445 adcroft 1.1 ENDDO
446 jmc 1.11 ENDDO
447    
448     C- end Surface/Interior if bloc
449 adcroft 1.1 ENDIF
450    
451     C-- Divergence of fluxes
452     DO j=1-Oly,sNy+Oly
453     DO i=1-Olx,sNx+Olx
454     localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
455     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
456     & *recip_rA(i,j,bi,bj)
457     & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
458 jmc 1.11 & -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))
459 adcroft 1.1 & )*rkFac
460     gTracer(i,j,k,bi,bj)=
461     & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
462     ENDDO
463     ENDDO
464    
465     C-- End of K loop for vertical flux
466     ENDDO
467    
468     RETURN
469     END

  ViewVC Help
Powered by ViewVC 1.1.22