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

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

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

revision 1.5 by adcroft, Tue Sep 4 17:00:48 2001 UTC revision 1.26 by jmc, Sat Jun 26 02:38:54 2004 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    
6    CBOP
7    C !ROUTINE: GAD_CALC_RHS
8    
9    C !INTERFACE: ==========================================================
10        SUBROUTINE GAD_CALC_RHS(        SUBROUTINE GAD_CALC_RHS(
11       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
13         I           uVel, vVel, wVel,
14       I           diffKh, diffK4, KappaRT, Tracer,       I           diffKh, diffK4, KappaRT, Tracer,
15       I           tracerIdentity, advectionScheme,       I           tracerIdentity, advectionScheme, vertAdvecScheme,
16         I           calcAdvection, implicitAdvection,
17       U           fVerT, gTracer,       U           fVerT, gTracer,
18       I           myThid )       I           myThid )
 C     /==========================================================\  
 C     | SUBROUTINE GAD_CALC_RHS                                  |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
19    
20  C     == GLobal variables ==  C !DESCRIPTION:
21    C Calculates the tendancy of a tracer due to advection and diffusion.
22    C It calculates the fluxes in each direction indepentently and then
23    C sets the tendancy to the divergence of these fluxes. The advective
24    C fluxes are only calculated here when using the linear advection schemes
25    C otherwise only the diffusive and parameterized fluxes are calculated.
26    C
27    C Contributions to the flux are calculated and added:
28    C \begin{equation*}
29    C {\bf F} = {\bf F}_{adv} + {\bf F}_{diff} +{\bf F}_{GM} + {\bf F}_{KPP}
30    C \end{equation*}
31    C
32    C The tendancy is the divergence of the fluxes:
33    C \begin{equation*}
34    C G_\theta = G_\theta + \nabla \cdot {\bf F}
35    C \end{equation*}
36    C
37    C The tendancy is assumed to contain data on entry.
38    
39    C !USES: ===============================================================
40          IMPLICIT NONE
41  #include "SIZE.h"  #include "SIZE.h"
42  #include "EEPARAMS.h"  #include "EEPARAMS.h"
43  #include "PARAMS.h"  #include "PARAMS.h"
44  #include "GRID.h"  #include "GRID.h"
45  #include "DYNVARS.h"  #include "SURFACE.h"
46  #include "GAD.h"  #include "GAD.h"
47    
48  C     == Routine arguments ==  #ifdef ALLOW_AUTODIFF_TAMC
49        INTEGER k,kUp,kDown,kM1  #include "tamc.h"
50    #include "tamc_keys.h"
51    #endif /* ALLOW_AUTODIFF_TAMC */
52    
53    C !INPUT PARAMETERS: ===================================================
54    C bi,bj            :: tile indices
55    C iMin,iMax        :: loop range for called routines
56    C jMin,jMax        :: loop range for called routines
57    C kup              :: index into 2 1/2D array, toggles between 1|2
58    C kdown            :: index into 2 1/2D array, toggles between 2|1
59    C kp1              :: =k+1 for k<Nr, =Nr for k=Nr
60    C xA,yA            :: areas of X and Y face of tracer cells
61    C uTrans,vTrans    :: 2-D arrays of volume transports at U,V points
62    C rTrans           :: 2-D arrays of volume transports at W points
63    C rTransKp1        :: 2-D array of volume trans at W pts, interf k+1
64    C maskUp           :: 2-D array for mask at W points
65    C uVel,vVel,wVel   :: 3 components of the velcity field (3-D array)
66    C diffKh           :: horizontal diffusion coefficient
67    C diffK4           :: bi-harmonic diffusion coefficient
68    C KappaRT          :: 3-D array for vertical diffusion coefficient
69    C Tracer           :: tracer field
70    C tracerIdentity   :: tracer identifier (required for KPP,GM)
71    C advectionScheme  :: advection scheme to use (Horizontal plane)
72    C vertAdvecScheme  :: advection scheme to use (Vertical direction)
73    C calcAdvection    :: =False if Advec computed with multiDim scheme
74    C implicitAdvection:: =True if vertical Advec computed implicitly
75    C myThid           :: thread number
76        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
77          INTEGER k,kUp,kDown,kM1
78        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85          _RL uVel  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
86          _RL vVel  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
87          _RL wVel  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
88        _RL diffKh, diffK4        _RL diffKh, diffK4
89        _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
90        _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
91        INTEGER tracerIdentity        INTEGER tracerIdentity
92        INTEGER advectionScheme        INTEGER advectionScheme, vertAdvecScheme
93        _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        LOGICAL calcAdvection
94        _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        LOGICAL implicitAdvection
95        INTEGER myThid        INTEGER myThid
96    
97  C     == Local variables ==  C !OUTPUT PARAMETERS: ==================================================
98  C     I, J, K - Loop counters  C gTracer          :: tendancy array
99    C fVerT            :: 2 1/2D arrays for vertical advective flux
100          _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
101          _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
102    
103    C !LOCAL VARIABLES: ====================================================
104    C i,j              :: loop indices
105    C df4              :: used for storing del^2 T for bi-harmonic term
106    C fZon             :: zonal flux
107    C fmer             :: meridional flux
108    C af               :: advective flux
109    C df               :: diffusive flux
110    C localT           :: local copy of tracer field
111        INTEGER i,j        INTEGER i,j
       LOGICAL TOP_LAYER  
       _RL afFacT, dfFacT  
112        _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117        _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118          _RL advFac, rAdvFac
119    CEOP
120    
121  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
122  C--   only the kUp part of fverT is set in this subroutine  C--   only the kUp part of fverT is set in this subroutine
123  C--   the kDown is still required  C--   the kDown is still required
124        fVerT(1,1,kDown) = fVerT(1,1,kDown)        fVerT(1,1,kDown) = fVerT(1,1,kDown)
125  #endif  #endif
126    
127          advFac  = 0. _d 0
128          IF (calcAdvection) advFac = 1. _d 0
129          rAdvFac = rkFac*advFac
130          IF (implicitAdvection) rAdvFac = 0. _d 0
131    
132        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
133         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
134          fZon(i,j)      = 0.0          fZon(i,j)      = 0. _d 0
135          fMer(i,j)      = 0.0          fMer(i,j)      = 0. _d 0
136          fVerT(i,j,kUp) = 0.0          fVerT(i,j,kUp) = 0. _d 0
137            df(i,j)        = 0. _d 0
138            df4(i,j)       = 0. _d 0
139         ENDDO         ENDDO
140        ENDDO        ENDDO
141    
       afFacT = 1. _d 0  
       dfFacT = 1. _d 0  
       TOP_LAYER = K .EQ. 1  
   
142  C--   Make local copy of tracer array  C--   Make local copy of tracer array
143        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
144         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 78  C--   Make local copy of tracer array Line 146  C--   Make local copy of tracer array
146         ENDDO         ENDDO
147        ENDDO        ENDDO
148    
149    C--   Unless we have already calculated the advection terms we initialize
150    C     the tendency to zero.
151    C     <== now done earlier at the beginning of thermodynamics.
152    c     IF (calcAdvection) THEN
153    c      DO j=1-Oly,sNy+Oly
154    c       DO i=1-Olx,sNx+Olx
155    c        gTracer(i,j,k,bi,bj)=0. _d 0
156    c       ENDDO
157    c      ENDDO
158    c     ENDIF
159    
160  C--   Pre-calculate del^2 T if bi-harmonic coefficient is non-zero  C--   Pre-calculate del^2 T if bi-harmonic coefficient is non-zero
161        IF (diffK4 .NE. 0.) THEN        IF (diffK4 .NE. 0.) THEN
# Line 89  C--   Pre-calculate del^2 T if bi-harmon Line 167  C--   Pre-calculate del^2 T if bi-harmon
167  C--   Initialize net flux in X direction  C--   Initialize net flux in X direction
168        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
169         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
170          fZon(i,j) = 0.          fZon(i,j) = 0. _d 0
171         ENDDO         ENDDO
172        ENDDO        ENDDO
173    
174  C-    Advective flux in X  C-    Advective flux in X
175          IF (calcAdvection) THEN
176        IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN        IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
177         CALL GAD_C2_ADV_X(bi,bj,k,uTrans,localT,af,myThid)         CALL GAD_C2_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
178        ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
# Line 117  C-    Advective flux in X Line 196  C-    Advective flux in X
196          fZon(i,j) = fZon(i,j) + af(i,j)          fZon(i,j) = fZon(i,j) + af(i,j)
197         ENDDO         ENDDO
198        ENDDO        ENDDO
199          ENDIF
200    
201  C-    Diffusive flux in X  C-    Diffusive flux in X
202        IF (diffKh.NE.0.) THEN        IF (diffKh.NE.0.) THEN
# Line 124  C-    Diffusive flux in X Line 204  C-    Diffusive flux in X
204        ELSE        ELSE
205         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
206          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
207           df(i,j) = 0.           df(i,j) = 0. _d 0
208          ENDDO          ENDDO
209         ENDDO         ENDDO
210        ENDIF        ENDIF
# Line 135  C-    GM/Redi flux in X Line 215  C-    GM/Redi flux in X
215  C *note* should update GMREDI_XTRANSPORT to use localT and set df  *aja*  C *note* should update GMREDI_XTRANSPORT to use localT and set df  *aja*
216          CALL GMREDI_XTRANSPORT(          CALL GMREDI_XTRANSPORT(
217       I     iMin,iMax,jMin,jMax,bi,bj,K,       I     iMin,iMax,jMin,jMax,bi,bj,K,
218       I     xA,Tracer,       I     xA,Tracer,tracerIdentity,
219       U     df,       U     df,
220       I     myThid)       I     myThid)
221        ENDIF        ENDIF
# Line 159  C-    Bi-harmonic duffusive flux in X Line 239  C-    Bi-harmonic duffusive flux in X
239  C--   Initialize net flux in Y direction  C--   Initialize net flux in Y direction
240        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
241         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
242          fMer(i,j) = 0.          fMer(i,j) = 0. _d 0
243         ENDDO         ENDDO
244        ENDDO        ENDDO
245    
246  C-    Advective flux in Y  C-    Advective flux in Y
247          IF (calcAdvection) THEN
248        IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN        IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
249         CALL GAD_C2_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)         CALL GAD_C2_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
250        ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
# Line 187  C-    Advective flux in Y Line 268  C-    Advective flux in Y
268          fMer(i,j) = fMer(i,j) + af(i,j)          fMer(i,j) = fMer(i,j) + af(i,j)
269         ENDDO         ENDDO
270        ENDDO        ENDDO
271          ENDIF
272    
273  C-    Diffusive flux in Y  C-    Diffusive flux in Y
274        IF (diffKh.NE.0.) THEN        IF (diffKh.NE.0.) THEN
# Line 194  C-    Diffusive flux in Y Line 276  C-    Diffusive flux in Y
276        ELSE        ELSE
277         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
278          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
279           df(i,j) = 0.           df(i,j) = 0. _d 0
280          ENDDO          ENDDO
281         ENDDO         ENDDO
282        ENDIF        ENDIF
# Line 202  C-    Diffusive flux in Y Line 284  C-    Diffusive flux in Y
284  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
285  C-    GM/Redi flux in Y  C-    GM/Redi flux in Y
286        IF (useGMRedi) THEN        IF (useGMRedi) THEN
        CALL GMREDI_YTRANSPORT(  
287  C *note* should update GMREDI_YTRANSPORT to use localT and set df  *aja*  C *note* should update GMREDI_YTRANSPORT to use localT and set df  *aja*
288           CALL GMREDI_YTRANSPORT(
289       I     iMin,iMax,jMin,jMax,bi,bj,K,       I     iMin,iMax,jMin,jMax,bi,bj,K,
290       I     yA,Tracer,       I     yA,Tracer,tracerIdentity,
291       U     df,       U     df,
292       I     myThid)       I     myThid)
293        ENDIF        ENDIF
# Line 226  C-    Bi-harmonic flux in Y Line 308  C-    Bi-harmonic flux in Y
308         ENDDO         ENDDO
309        ENDIF        ENDIF
310    
311  C--   Initialize net flux in R  C--   Compute vertical flux fVerT(kUp) at interface k (between k-1 & k):
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         fVerT(i,j,kUp) = 0.  
        ENDDO  
       ENDDO  
   
312  C-    Advective flux in R  C-    Advective flux in R
313  C     Note: wVel needs to be masked  #ifdef ALLOW_AIM
314        IF (K.GE.2) THEN  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
315          IF (calcAdvection .AND. .NOT.implicitAdvection .AND. K.GE.2 .AND.
316         &     (.NOT.useAIM .OR.tracerIdentity.NE.GAD_SALINITY .OR.K.LT.Nr)
317         &   ) THEN
318    #else
319          IF (calcAdvection .AND. .NOT.implicitAdvection .AND. K.GE.2) THEN
320    #endif
321  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
322         IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN         IF (vertAdvecScheme.EQ.ENUM_CENTERED_2ND) THEN
323          CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)          CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
324         ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN         ELSEIF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
325          CALL GAD_FLUXLIMIT_ADV_R(          CALL GAD_FLUXLIMIT_ADV_R(
326       &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)       &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
327         ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN         ELSEIF (vertAdvecScheme.EQ.ENUM_UPWIND_3RD ) THEN
328          CALL GAD_U3_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)          CALL GAD_U3_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
329         ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN         ELSEIF (vertAdvecScheme.EQ.ENUM_CENTERED_4TH) THEN
330          CALL GAD_C4_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)          CALL GAD_C4_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
331         ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN         ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
332  c       CALL GAD_DST3_ADV_R(          CALL GAD_DST3_ADV_R(
333  c    &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)       &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
334          STOP 'GAD_CALC_RHS: GAD_DST3_ADV_R not coded yet'         ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
335         ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          CALL GAD_DST3FL_ADV_R(
336  c       CALL GAD_DST3FL_ADV_R(       &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
 c    &       bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)  
         STOP 'GAD_CALC_RHS: GAD_DST3FL_ADV_R not coded yet'  
337         ELSE         ELSE
338          STOP 'GAD_CALC_RHS: Bad advectionScheme (R)'          STOP 'GAD_CALC_RHS: Bad vertAdvecScheme (R)'
339         ENDIF         ENDIF
340  C-    Surface "correction" term at k>1 :  C-     add the advective flux to fVerT
341         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
342          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
343           af(i,j) = af(i,j)           fVerT(i,j,kUp) = fVerT(i,j,kUp) + af(i,j)
      &           + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*  
      &             rTrans(i,j)*Tracer(i,j,k,bi,bj)  
344          ENDDO          ENDDO
        ENDDO  
       ELSE  
 C-    Surface "correction" term at k=1 :  
        DO j=1-Oly,sNy+Oly  
         DO i=1-Olx,sNx+Olx  
          af(i,j) = rTrans(i,j)*Tracer(i,j,k,bi,bj)  
         ENDDO  
        ENDDO  
       ENDIF  
 C-    add the advective flux to fVerT  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         fVerT(i,j,kUp) = fVerT(i,j,kUp) + afFacT*af(i,j)  
345         ENDDO         ENDDO
346        ENDDO        ENDIF
347    
348  C-    Diffusive flux in R  C-    Diffusive flux in R
349  C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper  C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
# Line 286  C           boundary condition. Line 351  C           boundary condition.
351        IF (implicitDiffusion) THEN        IF (implicitDiffusion) THEN
352         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
353          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
354           df(i,j) = 0.           df(i,j) = 0. _d 0
355          ENDDO          ENDDO
356         ENDDO         ENDDO
357        ELSE        ELSE
358         CALL GAD_DIFF_R(bi,bj,k,KappaRT,tracer,df,myThid)         CALL GAD_DIFF_R(bi,bj,k,KappaRT,tracer,df,myThid)
359        ENDIF        ENDIF
 c     DO j=1-Oly,sNy+Oly  
 c      DO i=1-Olx,sNx+Olx  
 c       fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)  
 c      ENDDO  
 c     ENDDO  
360    
361  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
362  C-    GM/Redi flux in R  C-    GM/Redi flux in R
# Line 304  C-    GM/Redi flux in R Line 364  C-    GM/Redi flux in R
364  C *note* should update GMREDI_RTRANSPORT to set df  *aja*  C *note* should update GMREDI_RTRANSPORT to set df  *aja*
365         CALL GMREDI_RTRANSPORT(         CALL GMREDI_RTRANSPORT(
366       I     iMin,iMax,jMin,jMax,bi,bj,K,       I     iMin,iMax,jMin,jMax,bi,bj,K,
367       I     maskUp,Tracer,       I     Tracer,tracerIdentity,
368       U     df,       U     df,
369       I     myThid)       I     myThid)
 c      DO j=1-Oly,sNy+Oly  
 c       DO i=1-Olx,sNx+Olx  
 c        fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)  
 c       ENDDO  
 c      ENDDO  
370        ENDIF        ENDIF
371  #endif  #endif
372    
373        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
374         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
375          fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)          fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
376         ENDDO         ENDDO
377        ENDDO        ENDDO
378    
# Line 326  C-    Add non local KPP transport term ( Line 381  C-    Add non local KPP transport term (
381        IF (useKPP) THEN        IF (useKPP) THEN
382         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
383          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
384           df(i,j) = 0.           df(i,j) = 0. _d 0
385          ENDDO          ENDDO
386         ENDDO         ENDDO
387         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN         IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
# Line 340  C *note* should update KPP_TRANSPORT_T t Line 395  C *note* should update KPP_TRANSPORT_T t
395       I     iMin,iMax,jMin,jMax,bi,bj,k,km1,       I     iMin,iMax,jMin,jMax,bi,bj,k,km1,
396       I     KappaRT,       I     KappaRT,
397       U     df )       U     df )
398    #ifdef ALLOW_PTRACERS
399           ELSEIF (tracerIdentity .GE. GAD_TR1) THEN
400            CALL KPP_TRANSPORT_PTR(
401         I     iMin,iMax,jMin,jMax,bi,bj,k,km1,
402         I     tracerIdentity-GAD_TR1+1,KappaRT,
403         U     df )
404    #endif
405         ELSE         ELSE
406            PRINT*,'invalid tracer indentity: ', tracerIdentity
407          STOP 'GAD_CALC_RHS: Ooops'          STOP 'GAD_CALC_RHS: Ooops'
408         ENDIF         ENDIF
409         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
410          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
411           fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)           fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
412          ENDDO          ENDDO
413         ENDDO         ENDDO
414        ENDIF        ENDIF
415  #endif  #endif
416    
417  C--   Divergence of fluxes  C--   Divergence of fluxes
418        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly-1
419         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx-1
420          gTracer(i,j,k,bi,bj)=          gTracer(i,j,k,bi,bj)=gTracer(i,j,k,bi,bj)
421       &   -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)*recip_rA(i,j,bi,bj)
422       &    *recip_rA(i,j,bi,bj)       &   *( (fZon(i+1,j)-fZon(i,j))
423       &    *(       &     +(fMer(i,j+1)-fMer(i,j))
424       &    +( fZon(i+1,j)-fZon(i,j) )       &     +(fVerT(i,j,kUp)-fVerT(i,j,kDown))*rkFac
425       &    +( fMer(i,j+1)-fMer(i,j) )       &     -localT(i,j)*( (uTrans(i+1,j)-uTrans(i,j))
426       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac       &                   +(vTrans(i,j+1)-vTrans(i,j))
427         &                   +(rTrans(i,j)-rTransKp1(i,j))*rAdvFac
428         &                  )*advFac
429       &    )       &    )
430         ENDDO         ENDDO
431        ENDDO        ENDDO

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.26

  ViewVC Help
Powered by ViewVC 1.1.22