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

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

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

revision 1.34 by jmc, Mon Dec 20 19:10:13 2004 UTC revision 1.44 by jmc, Tue Jan 9 22:28:20 2007 UTC
# Line 17  C !INTERFACE: ========================== Line 17  C !INTERFACE: ==========================
17       I     bi,bj, myTime,myIter,myThid)       I     bi,bj, myTime,myIter,myThid)
18    
19  C !DESCRIPTION:  C !DESCRIPTION:
20  C Calculates the tendancy of a tracer due to advection.  C Calculates the tendency of a tracer due to advection.
21  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}  C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
22  C and can only be used for the non-linear advection schemes such as the  C and can only be used for the non-linear advection schemes such as the
23  C direct-space-time method and flux-limiters.  C direct-space-time method and flux-limiters.
24  C  C
25  C The algorithm is as follows:  C The algorithm is as follows:
26  C \begin{itemize}  C \begin{itemize}
# Line 33  C      - \Delta t \partial_r (w\theta^{( Line 33  C      - \Delta t \partial_r (w\theta^{(
33  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}  C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
34  C \end{itemize}  C \end{itemize}
35  C  C
36  C The tendancy (output) is over-written by this routine.  C The tendency (output) is over-written by this routine.
37    
38  C !USES: ===============================================================  C !USES: ===============================================================
39        IMPLICIT NONE        IMPLICIT NONE
# Line 80  C  myThid            :: thread number Line 80  C  myThid            :: thread number
80        INTEGER myThid        INTEGER myThid
81    
82  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
83  C  gTracer           :: tendancy array  C  gTracer           :: tendency array
84        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)        _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85    
86  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
# Line 92  C  jMin,jMax     :: loop range for calle Line 92  C  jMin,jMax     :: loop range for calle
92  C [iMin,iMax]Upd :: loop range to update tracer field  C [iMin,iMax]Upd :: loop range to update tracer field
93  C [jMin,jMax]Upd :: loop range to update tracer field  C [jMin,jMax]Upd :: loop range to update tracer field
94  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
95  C  kup           :: index into 2 1/2D array, toggles between 1 and 2  C  kUp           :: index into 2 1/2D array, toggles between 1 and 2
96  C  kdown         :: index into 2 1/2D array, toggles between 2 and 1  C  kDown         :: index into 2 1/2D array, toggles between 2 and 1
97  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr  C  kp1           :: =k+1 for k<Nr, =Nr for k=Nr
98  C  xA,yA         :: areas of X and Y face of tracer cells  C  xA,yA         :: areas of X and Y face of tracer cells
99    C  uFld,vFld     :: 2-D local copy of horizontal velocity, U,V components
100    C  wFld          :: 2-D local copy of vertical velocity
101  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
102  C  rTrans        :: 2-D arrays of volume transports at W points  C  rTrans        :: 2-D arrays of volume transports at W points
103  C  rTransKp1     :: vertical volume transport at interface k+1  C  rTransKp1     :: vertical volume transport at interface k+1
# Line 112  C  interiorOnly  :: only update the inte Line 114  C  interiorOnly  :: only update the inte
114  C  overlapOnly   :: only update the edges of myTile, but not the interior  C  overlapOnly   :: only update the edges of myTile, but not the interior
115  C  nipass        :: number of passes in multi-dimensional method  C  nipass        :: number of passes in multi-dimensional method
116  C  ipass         :: number of the current pass being made  C  ipass         :: number of the current pass being made
117  C  myTile        :: variables used to determine which cube face  C  myTile        :: variables used to determine which cube face
118  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
119  C                :: multi-dim advection.  C                :: multi-dim advection.
120  C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube  C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
121        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
125        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
126        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kUp,kDown
127        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129          _RL uFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130          _RL vFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131          _RL wFld    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 138  C [N,S,E,W]_edge :: true if N,S,E,W edge Line 143  C [N,S,E,W]_edge :: true if N,S,E,W edge
143        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
144        LOGICAL interiorOnly, overlapOnly        LOGICAL interiorOnly, overlapOnly
145        INTEGER nipass,ipass        INTEGER nipass,ipass
146        INTEGER myTile, nCFace        INTEGER nCFace
147        LOGICAL N_edge, S_edge, E_edge, W_edge        LOGICAL N_edge, S_edge, E_edge, W_edge
148    #ifdef ALLOW_EXCH2
149          INTEGER myTile
150    #endif
151  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
152        CHARACTER*8 diagName        CHARACTER*8 diagName
153        CHARACTER*4 GAD_DIAG_SUFX, diagSufx        CHARACTER*4 GAD_DIAG_SUFX, diagSufx
# Line 169  CEOP Line 177  CEOP
177  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
178    
179  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
180  C--   Set diagnostic suffix for the current tracer  C--   Set diagnostic suffix for the current tracer
181        IF ( useDiagnostics ) THEN        IF ( useDiagnostics ) THEN
182          diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )          diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
183        ENDIF        ENDIF
# Line 190  C     uninitialised but inert locations. Line 198  C     uninitialised but inert locations.
198          fVerT(i,j,1) = 0. _d 0          fVerT(i,j,1) = 0. _d 0
199          fVerT(i,j,2) = 0. _d 0          fVerT(i,j,2) = 0. _d 0
200          rTransKp1(i,j)= 0. _d 0          rTransKp1(i,j)= 0. _d 0
201    #ifdef ALLOW_AUTODIFF_TAMC
202            localTij(i,j) = 0. _d 0
203            wfld(i,j)    = 0. _d 0
204    #endif
205         ENDDO         ENDDO
206        ENDDO        ENDDO
207    
# Line 215  C--   Set tile-specific parameters for h Line 227  C--   Set tile-specific parameters for h
227  #endif  #endif
228        ELSE        ELSE
229         nipass=2         nipass=2
230           nCFace = bi
231         N_edge = .FALSE.         N_edge = .FALSE.
232         S_edge = .FALSE.         S_edge = .FALSE.
233         E_edge = .FALSE.         E_edge = .FALSE.
# Line 236  CADJ &     comlev1_bibj_k_gad, key=kkey, Line 249  CADJ &     comlev1_bibj_k_gad, key=kkey,
249    
250  C--   Get temporary terms used by tendency routines  C--   Get temporary terms used by tendency routines
251        CALL CALC_COMMON_FACTORS (        CALL CALC_COMMON_FACTORS (
252       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         uVel, vVel,
253       O         xA,yA,uTrans,vTrans,rTrans,maskUp,       O         uFld, vFld, uTrans, vTrans, xA, yA,
254       I         myThid)       I         k,bi,bj, myThid )
255    
256  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
257  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
258        IF (useGMRedi)        IF (useGMRedi)
259       &   CALL GMREDI_CALC_UVFLOW(       &   CALL GMREDI_CALC_UVFLOW(
260       &            uTrans, vTrans, bi, bj, k, myThid)       U                  uFld, vFld, uTrans, vTrans,
261         I                  k, bi, bj, myThid )
262  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
263    
264  C--   Make local copy of tracer array and mask West & South  C--   Make local copy of tracer array and mask West & South
# Line 259  C--   Make local copy of tracer array an Line 273  C--   Make local copy of tracer array an
273  #ifndef ALLOW_AUTODIFF_TAMC  #ifndef ALLOW_AUTODIFF_TAMC
274        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
275          withSigns = .FALSE.          withSigns = .FALSE.
276          CALL FILL_CS_CORNER_UV_RS(          CALL FILL_CS_CORNER_UV_RS(
277       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
278        ENDIF        ENDIF
279  #endif  #endif
# Line 307  C-    not CubedSphere Line 321  C-    not CubedSphere
321          calc_fluxes_X = MOD(ipass,2).EQ.1          calc_fluxes_X = MOD(ipass,2).EQ.1
322          calc_fluxes_Y = .NOT.calc_fluxes_X          calc_fluxes_Y = .NOT.calc_fluxes_X
323        ENDIF        ENDIF
324    
325  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
326  C--   X direction  C--   X direction
327    C-     Advective flux in X
328            DO j=1-Oly,sNy+Oly
329             DO i=1-Olx,sNx+Olx
330              af(i,j) = 0.
331             ENDDO
332            ENDDO
333    C
334    #ifdef ALLOW_AUTODIFF_TAMC
335    # ifndef DISABLE_MULTIDIM_ADVECTION
336    CADJ STORE localTij(:,:)  =
337    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
338    CADJ STORE af(:,:)  =
339    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
340    # endif
341    #endif /* ALLOW_AUTODIFF_TAMC */
342    C
343        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
344    
345  C-     Do not compute fluxes if  C-     Do not compute fluxes if
346  C       a) needed in overlap only  C       a) needed in overlap only
347  C   and b) the overlap of myTile are not cube-face Edges  C   and b) the overlap of myTile are not cube-face Edges
348         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
349    
# Line 329  C-     Internal exchange for calculation Line 359  C-     Internal exchange for calculation
359          ENDIF          ENDIF
360  #endif  #endif
361    
 C-     Advective flux in X  
         DO j=1-Oly,sNy+Oly  
          DO i=1-Olx,sNx+Olx  
           af(i,j) = 0.  
          ENDDO  
         ENDDO  
   
362  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
363  #ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
364  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
365  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
366  #endif  # endif
367  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
368    
369          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
370         &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
371              CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme,
372         I                           dTtracerLev(k),uTrans,uFld,localTij,
373         O                           af, myThid )
374            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
375            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),
376       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
377       O                              af, myThid )       O                              af, myThid )
378          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
379            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_X(      bi,bj,k, dTtracerLev(k),
380       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
381       O                              af, myThid )       O                              af, myThid )
382          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
383            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_X(    bi,bj,k, dTtracerLev(k),
384       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
385       O                              af, myThid )       O                              af, myThid )
386          ELSE          ELSE
387           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
# Line 375  C      update in overlap-Only Line 403  C      update in overlap-Only
403         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
404          iMinUpd = 1-Olx+1          iMinUpd = 1-Olx+1
405          iMaxUpd = sNx+Olx-1          iMaxUpd = sNx+Olx-1
406  C- notes: these 2 lines below have no real effect (because recip_hFac=0  C- notes: these 2 lines below have no real effect (because recip_hFac=0
407  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
408          IF ( W_edge ) iMinUpd = 1          IF ( W_edge ) iMinUpd = 1
409          IF ( E_edge ) iMaxUpd = sNx          IF ( E_edge ) iMaxUpd = sNx
# Line 383  C         in corner region) but safer to Line 411  C         in corner region) but safer to
411          IF ( S_edge ) THEN          IF ( S_edge ) THEN
412           DO j=1-Oly,0           DO j=1-Oly,0
413            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
414             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
415       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
416       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
417         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
418       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
419       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
420       &        )       &        )
# Line 395  C         in corner region) but safer to Line 424  C         in corner region) but safer to
424          IF ( N_edge ) THEN          IF ( N_edge ) THEN
425           DO j=sNy+1,sNy+Oly           DO j=sNy+1,sNy+Oly
426            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
427             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
428       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
429       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
430         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
431       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
432       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
433       &        )       &        )
# Line 407  C         in corner region) but safer to Line 437  C         in corner region) but safer to
437    
438         ELSE         ELSE
439  C      do not only update the overlap  C      do not only update the overlap
440          jMinUpd = 1-Oly          jMinUpd = 1-Oly
441          jMaxUpd = sNy+Oly          jMaxUpd = sNy+Oly
442          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
443          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
444          DO j=jMinUpd,jMaxUpd          DO j=jMinUpd,jMaxUpd
445           DO i=1-Olx+1,sNx+Olx-1           DO i=1-Olx+1,sNx+Olx-1
446             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
447       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
448       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
449         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
450       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
451       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
452       &        )       &        )
# Line 435  C-     Apply open boundary conditions Line 466  C-     Apply open boundary conditions
466            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
467           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
468            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
469    #ifdef ALLOW_PTRACERS
470             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
471              CALL OBCS_APPLY_PTRACER( bi, bj, k,
472         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
473    #endif /* ALLOW_PTRACERS */
474           ENDIF           ENDIF
475          ENDIF          ENDIF
476  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
477    
478  C-     end if/else update overlap-Only  C-     end if/else update overlap-Only
479         ENDIF         ENDIF
480            
481  C--   End of X direction  C--   End of X direction
482        ENDIF        ENDIF
483    
484  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
485  C--   Y direction  C--   Y direction
486    cph-test
487    C-     Advective flux in Y
488            DO j=1-Oly,sNy+Oly
489             DO i=1-Olx,sNx+Olx
490              af(i,j) = 0.
491             ENDDO
492            ENDDO
493    C
494    #ifdef ALLOW_AUTODIFF_TAMC
495    # ifndef DISABLE_MULTIDIM_ADVECTION
496    CADJ STORE localTij(:,:)  =
497    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
498    CADJ STORE af(:,:)  =
499    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
500    # endif
501    #endif /* ALLOW_AUTODIFF_TAMC */
502    C
503        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
504    
505  C-     Do not compute fluxes if  C-     Do not compute fluxes if
# Line 480  CADJ &     comlev1_bibj_k_gad_pass, key= Line 533  CADJ &     comlev1_bibj_k_gad_pass, key=
533  #endif  #endif
534  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
535    
536          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
537         &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
538              CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme,
539         I                           dTtracerLev(k),vTrans,vFld,localTij,
540         O                           af, myThid )
541            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
542            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),
543       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
544       O                              af, myThid )       O                              af, myThid )
545          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
546            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),
547       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
548       O                              af, myThid )       O                              af, myThid )
549          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
550            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),
551       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
552       O                              af, myThid )       O                              af, myThid )
553          ELSE          ELSE
554           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
# Line 510  C-     Update the local tracer field whe Line 568  C-     Update the local tracer field whe
568    
569  C      update in overlap-Only  C      update in overlap-Only
570         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
571          jMinUpd = 1-Oly+1          jMinUpd = 1-Oly+1
572          jMaxUpd = sNy+Oly-1          jMaxUpd = sNy+Oly-1
573  C- notes: these 2 lines below have no real effect (because recip_hFac=0  C- notes: these 2 lines below have no real effect (because recip_hFac=0
574  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
575          IF ( S_edge ) jMinUpd = 1          IF ( S_edge ) jMinUpd = 1
576          IF ( N_edge ) jMaxUpd = sNy          IF ( N_edge ) jMaxUpd = sNy
# Line 520  C         in corner region) but safer to Line 578  C         in corner region) but safer to
578          IF ( W_edge ) THEN          IF ( W_edge ) THEN
579           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
580            DO i=1-Olx,0            DO i=1-Olx,0
581             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
582       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
583       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
584         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
585       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
586       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
587       &        )       &        )
# Line 532  C         in corner region) but safer to Line 591  C         in corner region) but safer to
591          IF ( E_edge ) THEN          IF ( E_edge ) THEN
592           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
593            DO i=sNx+1,sNx+Olx            DO i=sNx+1,sNx+Olx
594             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
595       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
596       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
597         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
598       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
599       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
600       &        )       &        )
# Line 550  C      do not only update the overlap Line 610  C      do not only update the overlap
610          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
611          DO j=1-Oly+1,sNy+Oly-1          DO j=1-Oly+1,sNy+Oly-1
612           DO i=iMinUpd,iMaxUpd           DO i=iMinUpd,iMaxUpd
613             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
614       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
615       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
616         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
617       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
618       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &         -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
619       &        )       &        )
# Line 572  C-     Apply open boundary conditions Line 633  C-     Apply open boundary conditions
633            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
634           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
635            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
636    #ifdef ALLOW_PTRACERS
637             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
638              CALL OBCS_APPLY_PTRACER( bi, bj, k,
639         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
640    #endif /* ALLOW_PTRACERS */
641           ENDIF           ENDIF
642          ENDIF          ENDIF
643  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
# Line 595  C-    explicit advection is done ; store Line 661  C-    explicit advection is done ; store
661          ENDDO          ENDDO
662        ELSE        ELSE
663  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
664         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
665          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
666           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
667             ENDDO
668          ENDDO          ENDDO
        ENDDO  
669        ENDIF        ENDIF
670    
671  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
# Line 633  C--   Start of k loop for vertical flux Line 699  C--   Start of k loop for vertical flux
699  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
700           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
701  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
702  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
703  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
704          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
705          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
706  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
707          kp1Msk=1.          kp1Msk=1.
# Line 651  C- a hack to prevent Water-Vapor vert.tr Line 717  C- a hack to prevent Water-Vapor vert.tr
717          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
718  #endif  #endif
719    
720    #ifdef ALLOW_AUTODIFF_TAMC
721    CADJ STORE rtrans(:,:)  =
722    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
723    CADJ STORE wfld(:,:)  =
724    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
725    #endif /* ALLOW_AUTODIFF_TAMC */
726    
727  C- Surface interface :  C- Surface interface :
728           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
729            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
730             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
731               wFld(i,j)   = 0.
732             rTrans(i,j) = 0.             rTrans(i,j) = 0.
733             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
734            ENDDO            ENDDO
735           ENDDO           ENDDO
736    
737          ELSE          ELSE
 C- Interior interface :  
738    
739    #ifdef ALLOW_AUTODIFF_TAMC
740    CADJ STORE rtrans(:,:)  =
741    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
742    CADJ STORE wfld(:,:)  =
743    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
744    #endif /* ALLOW_AUTODIFF_TAMC */
745    
746    C- Interior interface :
747           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
748            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
749             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
750               wFld(i,j)   = wVel(i,j,k,bi,bj)
751             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
752         &                 *deepFac2F(k)*rhoFacF(k)
753       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
754             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
755            ENDDO            ENDDO
# Line 674  C- Interior interface : Line 757  C- Interior interface :
757    
758  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
759  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
760           IF (useGMRedi)           IF (useGMRedi)
761       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
762       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
763         I                 k, bi, bj, myThid )
764  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
765    
766  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 687  CADJ &     = comlev1_bibj_k_gad, key=kke Line 771  CADJ &     = comlev1_bibj_k_gad, key=kke
771  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
772    
773  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
774           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
775  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|       &      .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
776               CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
777         I                            dTtracerLev(k),rTrans,wFld,localTijk,
778         O                            fVerT(1-Olx,1-Oly,kUp), myThid )
779             ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
780             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
781       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
782       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
783           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
784             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
785       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
786       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
787           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
788             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
789       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
790       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
791           ELSE           ELSE
792            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
# Line 717  CADJ &     = comlev1_bibj_k_gad, key=kke Line 805  CADJ &     = comlev1_bibj_k_gad, key=kke
805  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
806          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
807           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
808            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*            localTij(i,j) = localTijk(i,j,k)
809       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
810       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
811       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
812       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
813       &      )*rkFac       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
814         &        )*rkSign
815            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
816       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
817           ENDDO           ENDDO
818          ENDDO          ENDDO
819    
820  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
821          IF ( useDiagnostics ) THEN          IF ( useDiagnostics ) THEN
822            diagName = 'ADVr'//diagSufx            diagName = 'ADVr'//diagSufx
# Line 739  C--   Divergence of vertical fluxes Line 828  C--   Divergence of vertical fluxes
828  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
829         ENDDO         ENDDO
830  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
831        ENDIF        ENDIF
832    
833        RETURN        RETURN
834        END        END

Legend:
Removed from v.1.34  
changed lines
  Added in v.1.44

  ViewVC Help
Powered by ViewVC 1.1.22