/[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.32 by jmc, Sat Dec 4 00:20:27 2004 UTC revision 1.48 by jmc, Wed Apr 4 01:39:06 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
152          CHARACTER*8 diagName
153          CHARACTER*4 GAD_DIAG_SUFX, diagSufx
154          EXTERNAL    GAD_DIAG_SUFX
155    #endif
156  CEOP  CEOP
157    
158  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 163  CEOP Line 176  CEOP
176            endif            endif
177  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
178    
179    #ifdef ALLOW_DIAGNOSTICS
180    C--   Set diagnostic suffix for the current tracer
181          IF ( useDiagnostics ) THEN
182            diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
183          ENDIF
184    #endif
185    
186  C--   Set up work arrays with valid (i.e. not NaN) values  C--   Set up work arrays with valid (i.e. not NaN) values
187  C     These inital values do not alter the numerical results. They  C     These inital values do not alter the numerical results. They
188  C     just ensure that all memory references are to valid floating  C     just ensure that all memory references are to valid floating
# Line 178  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 203  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 224  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 247  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 295  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 317  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            CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
371       I                              uTrans, uVel, maskLocW, localTij,            CALL GAD_DST2U1_ADV_X( bi,bj,k, advectionScheme, .TRUE.,
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, .TRUE., dTtracerLev(k),
376         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, .TRUE., 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, .TRUE., dTtracerLev(k),
384       I                              uTrans, uVel, maskLocW, localTij,       I                              uTrans, uFld, maskLocW, localTij,
385         O                              af, myThid )
386    #ifndef ALLOW_AUTODIFF_TAMC
387            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
388              CALL GAD_OS7MP_ADV_X(     bi,bj,k, .TRUE., dTtracerLev(k),
389         I                              uTrans, uFld, maskLocW, localTij,
390       O                              af, myThid )       O                              af, myThid )
391    #endif
392          ELSE          ELSE
393           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
394          ENDIF          ENDIF
# Line 363  C      update in overlap-Only Line 409  C      update in overlap-Only
409         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
410          iMinUpd = 1-Olx+1          iMinUpd = 1-Olx+1
411          iMaxUpd = sNx+Olx-1          iMaxUpd = sNx+Olx-1
412  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
413  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
414          IF ( W_edge ) iMinUpd = 1          IF ( W_edge ) iMinUpd = 1
415          IF ( E_edge ) iMaxUpd = sNx          IF ( E_edge ) iMaxUpd = sNx
# Line 371  C         in corner region) but safer to Line 417  C         in corner region) but safer to
417          IF ( S_edge ) THEN          IF ( S_edge ) THEN
418           DO j=1-Oly,0           DO j=1-Oly,0
419            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
420             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
421       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
422       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
423         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
424       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
425       &         -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))
426       &        )       &        )
# Line 383  C         in corner region) but safer to Line 430  C         in corner region) but safer to
430          IF ( N_edge ) THEN          IF ( N_edge ) THEN
431           DO j=sNy+1,sNy+Oly           DO j=sNy+1,sNy+Oly
432            DO i=iMinUpd,iMaxUpd            DO i=iMinUpd,iMaxUpd
433             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
434       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
435       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
436         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
437       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
438       &         -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))
439       &        )       &        )
# Line 395  C         in corner region) but safer to Line 443  C         in corner region) but safer to
443    
444         ELSE         ELSE
445  C      do not only update the overlap  C      do not only update the overlap
446          jMinUpd = 1-Oly          jMinUpd = 1-Oly
447          jMaxUpd = sNy+Oly          jMaxUpd = sNy+Oly
448          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1          IF ( interiorOnly .AND. S_edge ) jMinUpd = 1
449          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy          IF ( interiorOnly .AND. N_edge ) jMaxUpd = sNy
450          DO j=jMinUpd,jMaxUpd          DO j=jMinUpd,jMaxUpd
451           DO i=1-Olx+1,sNx+Olx-1           DO i=1-Olx+1,sNx+Olx-1
452             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
453       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
454       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
455         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
456       &       *( af(i+1,j)-af(i,j)       &       *( af(i+1,j)-af(i,j)
457       &         -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))
458       &        )       &        )
# Line 423  C-     Apply open boundary conditions Line 472  C-     Apply open boundary conditions
472            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
473           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
474            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
475    #ifdef ALLOW_PTRACERS
476             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
477              CALL OBCS_APPLY_PTRACER( bi, bj, k,
478         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
479    #endif /* ALLOW_PTRACERS */
480           ENDIF           ENDIF
481          ENDIF          ENDIF
482  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
483    
484  C-     end if/else update overlap-Only  C-     end if/else update overlap-Only
485         ENDIF         ENDIF
486            
487  C--   End of X direction  C--   End of X direction
488        ENDIF        ENDIF
489    
490  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
491  C--   Y direction  C--   Y direction
492    cph-test
493    C-     Advective flux in Y
494            DO j=1-Oly,sNy+Oly
495             DO i=1-Olx,sNx+Olx
496              af(i,j) = 0.
497             ENDDO
498            ENDDO
499    C
500    #ifdef ALLOW_AUTODIFF_TAMC
501    # ifndef DISABLE_MULTIDIM_ADVECTION
502    CADJ STORE localTij(:,:)  =
503    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
504    CADJ STORE af(:,:)  =
505    CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
506    # endif
507    #endif /* ALLOW_AUTODIFF_TAMC */
508    C
509        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
510    
511  C-     Do not compute fluxes if  C-     Do not compute fluxes if
# Line 468  CADJ &     comlev1_bibj_k_gad_pass, key= Line 539  CADJ &     comlev1_bibj_k_gad_pass, key=
539  #endif  #endif
540  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
541    
542          IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN          IF ( advectionScheme.EQ.ENUM_UPWIND_1RST
543            CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, dTtracerLev(k),       &     .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
544       I                              vTrans, vVel, maskLocS, localTij,            CALL GAD_DST2U1_ADV_Y( bi,bj,k, advectionScheme, .TRUE.,
545         I                           dTtracerLev(k),vTrans,vFld,localTij,
546         O                           af, myThid )
547            ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
548              CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, .TRUE., dTtracerLev(k),
549         I                              vTrans, vFld, maskLocS, localTij,
550       O                              af, myThid )       O                              af, myThid )
551          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
552            CALL GAD_DST3_ADV_Y(      bi,bj,k, dTtracerLev(k),            CALL GAD_DST3_ADV_Y(      bi,bj,k, .TRUE., dTtracerLev(k),
553       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
554       O                              af, myThid )       O                              af, myThid )
555          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN          ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
556            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, dTtracerLev(k),            CALL GAD_DST3FL_ADV_Y(    bi,bj,k, .TRUE., dTtracerLev(k),
557       I                              vTrans, vVel, maskLocS, localTij,       I                              vTrans, vFld, maskLocS, localTij,
558       O                              af, myThid )       O                              af, myThid )
559    #ifndef ALLOW_AUTODIFF_TAMC
560            ELSEIF (advectionScheme.EQ.ENUM_OS7MP ) THEN
561              CALL GAD_OS7MP_ADV_Y(     bi,bj,k, .TRUE., dTtracerLev(k),
562         I                              vTrans, vFld, maskLocS, localTij,
563         O                              af, myThid )
564    #endif
565          ELSE          ELSE
566           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
567          ENDIF          ENDIF
# Line 498  C-     Update the local tracer field whe Line 580  C-     Update the local tracer field whe
580    
581  C      update in overlap-Only  C      update in overlap-Only
582         IF ( overlapOnly ) THEN         IF ( overlapOnly ) THEN
583          jMinUpd = 1-Oly+1          jMinUpd = 1-Oly+1
584          jMaxUpd = sNy+Oly-1          jMaxUpd = sNy+Oly-1
585  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
586  C         in corner region) but safer to keep them.  C         in corner region) but safer to keep them.
587          IF ( S_edge ) jMinUpd = 1          IF ( S_edge ) jMinUpd = 1
588          IF ( N_edge ) jMaxUpd = sNy          IF ( N_edge ) jMaxUpd = sNy
# Line 508  C         in corner region) but safer to Line 590  C         in corner region) but safer to
590          IF ( W_edge ) THEN          IF ( W_edge ) THEN
591           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
592            DO i=1-Olx,0            DO i=1-Olx,0
593             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
594       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
595       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
596         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
597       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
598       &         -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))
599       &        )       &        )
# Line 520  C         in corner region) but safer to Line 603  C         in corner region) but safer to
603          IF ( E_edge ) THEN          IF ( E_edge ) THEN
604           DO j=jMinUpd,jMaxUpd           DO j=jMinUpd,jMaxUpd
605            DO i=sNx+1,sNx+Olx            DO i=sNx+1,sNx+Olx
606             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
607       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
608       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
609         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
610       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
611       &         -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))
612       &        )       &        )
# Line 538  C      do not only update the overlap Line 622  C      do not only update the overlap
622          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx          IF ( interiorOnly .AND. E_edge ) iMaxUpd = sNx
623          DO j=1-Oly+1,sNy+Oly-1          DO j=1-Oly+1,sNy+Oly-1
624           DO i=iMinUpd,iMaxUpd           DO i=iMinUpd,iMaxUpd
625             localTij(i,j)=localTij(i,j)-dTtracerLev(k)*             localTij(i,j) = localTij(i,j)
626       &       _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
627       &       *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
628         &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
629       &       *( af(i,j+1)-af(i,j)       &       *( af(i,j+1)-af(i,j)
630       &         -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))
631       &        )       &        )
# Line 560  C-     Apply open boundary conditions Line 645  C-     Apply open boundary conditions
645            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
646           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN           ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
647            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )            CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
648    #ifdef ALLOW_PTRACERS
649             ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
650              CALL OBCS_APPLY_PTRACER( bi, bj, k,
651         &         tracerIdentity-GAD_TR1+1, localTij, myThid )
652    #endif /* ALLOW_PTRACERS */
653           ENDIF           ENDIF
654          ENDIF          ENDIF
655  #endif /* ALLOW_OBCS */  #endif /* ALLOW_OBCS */
# Line 583  C-    explicit advection is done ; store Line 673  C-    explicit advection is done ; store
673          ENDDO          ENDDO
674        ELSE        ELSE
675  C-    horizontal advection done; store intermediate result in 3D array:  C-    horizontal advection done; store intermediate result in 3D array:
676         DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
677          DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
678           localTijk(i,j,k)=localTij(i,j)            localTijk(i,j,k)=localTij(i,j)
679             ENDDO
680          ENDDO          ENDDO
        ENDDO  
681        ENDIF        ENDIF
682    
683    #ifdef ALLOW_DIAGNOSTICS
684            IF ( useDiagnostics ) THEN
685              diagName = 'ADVx'//diagSufx
686              CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
687              diagName = 'ADVy'//diagSufx
688              CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
689            ENDIF
690    #endif
691    
692  #ifdef ALLOW_DEBUG  #ifdef ALLOW_DEBUG
693        IF ( debugLevel .GE. debLevB        IF ( debugLevel .GE. debLevB
694       &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE       &   .AND. tracerIdentity.EQ.GAD_TEMPERATURE
# Line 612  C--   Start of k loop for vertical flux Line 711  C--   Start of k loop for vertical flux
711  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
712           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
713  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
714  C--   kup    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
715  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
716          kup  = 1+MOD(k+1,2)          kUp  = 1+MOD(k+1,2)
717          kDown= 1+MOD(k,2)          kDown= 1+MOD(k,2)
718  c       kp1=min(Nr,k+1)  c       kp1=min(Nr,k+1)
719          kp1Msk=1.          kp1Msk=1.
# Line 630  C- a hack to prevent Water-Vapor vert.tr Line 729  C- a hack to prevent Water-Vapor vert.tr
729          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
730  #endif  #endif
731    
732    #ifdef ALLOW_AUTODIFF_TAMC
733    CADJ STORE rtrans(:,:)  =
734    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
735    CADJ STORE wfld(:,:)  =
736    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
737    #endif /* ALLOW_AUTODIFF_TAMC */
738    
739  C- Surface interface :  C- Surface interface :
740           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
741            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
742             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
743               wFld(i,j)   = 0.
744             rTrans(i,j) = 0.             rTrans(i,j) = 0.
745             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
746            ENDDO            ENDDO
747           ENDDO           ENDDO
748    
749          ELSE          ELSE
 C- Interior interface :  
750    
751    #ifdef ALLOW_AUTODIFF_TAMC
752    CADJ STORE rtrans(:,:)  =
753    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
754    CADJ STORE wfld(:,:)  =
755    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
756    #endif /* ALLOW_AUTODIFF_TAMC */
757    
758    C- Interior interface :
759           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
760            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
761             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
762               wFld(i,j)   = wVel(i,j,k,bi,bj)
763             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)
764         &                 *deepFac2F(k)*rhoFacF(k)
765       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
766             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
767            ENDDO            ENDDO
# Line 653  C- Interior interface : Line 769  C- Interior interface :
769    
770  #ifdef ALLOW_GMREDI  #ifdef ALLOW_GMREDI
771  C--   Residual transp = Bolus transp + Eulerian transp  C--   Residual transp = Bolus transp + Eulerian transp
772           IF (useGMRedi)           IF (useGMRedi)
773       &   CALL GMREDI_CALC_WFLOW(       &     CALL GMREDI_CALC_WFLOW(
774       &                    rTrans, bi, bj, k, myThid)       U                 wFld, rTrans,
775         I                 k, bi, bj, myThid )
776  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
777    
778  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 666  CADJ &     = comlev1_bibj_k_gad, key=kke Line 783  CADJ &     = comlev1_bibj_k_gad, key=kke
783  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
784    
785  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
786           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF ( vertAdvecScheme.EQ.ENUM_UPWIND_1RST
787  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|       &      .OR. vertAdvecScheme.EQ.ENUM_DST2 ) THEN
788               CALL GAD_DST2U1_ADV_R( bi,bj,k, advectionScheme,
789         I                            dTtracerLev(k),rTrans,wFld,localTijk,
790         O                            fVerT(1-Olx,1-Oly,kUp), myThid )
791             ELSEIF( vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
792             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, dTtracerLev(k),
793       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
794       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
795           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3 ) THEN
796             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),             CALL GAD_DST3_ADV_R(      bi,bj,k, dTtracerLev(k),
797       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
798       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
799           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF( vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
800             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),             CALL GAD_DST3FL_ADV_R(    bi,bj,k, dTtracerLev(k),
801       I                               rTrans, wVel, localTijk,       I                               rTrans, wFld, localTijk,
802       O                               fVerT(1-Olx,1-Oly,kUp), myThid )       O                               fVerT(1-Olx,1-Oly,kUp), myThid )
803    #ifndef ALLOW_AUTODIFF_TAMC
804             ELSEIF (vertAdvecScheme.EQ.ENUM_OS7MP ) THEN
805               CALL GAD_OS7MP_ADV_R(     bi,bj,k, dTtracerLev(k),
806         I                               rTrans, wFld, localTijk,
807         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
808    #endif
809           ELSE           ELSE
810            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
811           ENDIF           ENDIF
# Line 696  CADJ &     = comlev1_bibj_k_gad, key=kke Line 823  CADJ &     = comlev1_bibj_k_gad, key=kke
823  C--   Divergence of vertical fluxes  C--   Divergence of vertical fluxes
824          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
825           DO i=1-Olx,sNx+Olx           DO i=1-Olx,sNx+Olx
826            localTij(i,j)=localTijk(i,j,k)-dTtracerLev(k)*            localTij(i,j) = localTijk(i,j,k)
827       &     _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &      -dTtracerLev(k)*recip_rhoFacC(k)
828       &     *recip_rA(i,j,bi,bj)       &       *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
829       &     *( fVerT(i,j,kUp)-fVerT(i,j,kDown)       &       *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
830       &       -tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))       &       *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
831       &      )*rkFac       &         -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
832         &        )*rkSign
833            gTracer(i,j,k,bi,bj)=            gTracer(i,j,k,bi,bj)=
834       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)       &     (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
835           ENDDO           ENDDO
836          ENDDO          ENDDO
837    
838    #ifdef ALLOW_DIAGNOSTICS
839            IF ( useDiagnostics ) THEN
840              diagName = 'ADVr'//diagSufx
841              CALL DIAGNOSTICS_FILL( fVerT(1-Olx,1-Oly,kUp),
842         &                           diagName, k,1, 2,bi,bj, myThid)
843            ENDIF
844    #endif
845    
846  C--   End of K loop for vertical flux  C--   End of K loop for vertical flux
847         ENDDO         ENDDO
848  C--   end of if not.implicitAdvection block  C--   end of if not.implicitAdvection block
849        ENDIF        ENDIF
850    
851        RETURN        RETURN
852        END        END

Legend:
Removed from v.1.32  
changed lines
  Added in v.1.48

  ViewVC Help
Powered by ViewVC 1.1.22