/[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.10 by adcroft, Thu Sep 13 17:46:49 2001 UTC revision 1.11 by adcroft, Wed Sep 19 20:45:09 2001 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,maskUp,
# Line 10  C $Name$ Line 14  C $Name$
14       I           tracerIdentity, advectionScheme,       I           tracerIdentity, advectionScheme,
15       U           fVerT, gTracer,       U           fVerT, gTracer,
16       I           myThid )       I           myThid )
 C     /==========================================================\  
 C     | SUBROUTINE GAD_CALC_RHS                                  |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
17    
18  C     == GLobal variables ==  C !DESCRIPTION:
19    C Calculates the tendancy of a tracer due to advection and diffusion.
20    C It calculates the fluxes in each direction indepentently and then
21    C sets the tendancy to the divergence of these fluxes. The advective
22    C fluxes are only calculated here when using the linear advection schemes
23    C otherwise only the diffusive and parameterized fluxes are calculated.
24    C
25    C Contributions to the flux are calculated and added:
26    C \begin{equation*}
27    C {\bf F} = {\bf F}_{adv} + {\bf F}_{diff} +{\bf F}_{GM} + {\bf F}_{KPP}
28    C \end{equation*}
29    C
30    C The tendancy is the divergence of the fluxes:
31    C \begin{equation*}
32    C G_\theta = G_\theta + \nabla \cdot {\bf F}
33    C \end{equation*}
34    C
35    C The tendancy is assumed to contain data on entry.
36    
37    C !USES: ===============================================================
38          IMPLICIT NONE
39  #include "SIZE.h"  #include "SIZE.h"
40  #include "EEPARAMS.h"  #include "EEPARAMS.h"
41  #include "PARAMS.h"  #include "PARAMS.h"
# Line 24  C     == GLobal variables == Line 43  C     == GLobal variables ==
43  #include "DYNVARS.h"  #include "DYNVARS.h"
44  #include "GAD.h"  #include "GAD.h"
45    
46  C     == Routine arguments ==  C !INPUT PARAMETERS: ===================================================
47        INTEGER k,kUp,kDown,kM1  C  bi,bj                :: tile indices
48    C  iMin,iMax,jMin,jMax  :: loop range for called routines
49    C  kup                  :: index into 2 1/2D array, toggles between 1 and 2
50    C  kdown                :: index into 2 1/2D array, toggles between 2 and 1
51    C  kp1                  :: =k+1 for k<Nr, =Nr for k=Nr
52    C  xA,yA                :: areas of X and Y face of tracer cells
53    C  uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
54    C  maskUp               :: 2-D array for mask at W points
55    C  diffKh               :: horizontal diffusion coefficient
56    C  diffK4               :: bi-harmonic diffusion coefficient
57    C  KappaRT              :: 3-D array for vertical diffusion coefficient
58    C  Tracer               :: tracer field
59    C  tracerIdentity       :: identifier for the tracer (required only for KPP)
60    C  advectionScheme      :: advection scheme to use
61    C  myThid               :: thread number
62        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
63          INTEGER k,kUp,kDown,kM1
64        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 38  C     == Routine arguments == Line 72  C     == Routine arguments ==
72        _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)
73        INTEGER tracerIdentity        INTEGER tracerIdentity
74        INTEGER advectionScheme        INTEGER advectionScheme
       _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  
       _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)  
75        INTEGER myThid        INTEGER myThid
76    
77  C     == Local variables ==  C !OUTPUT PARAMETERS: ==================================================
78  C     I, J, K - Loop counters  C  gTracer              :: tendancy array
79    C  fVerT                :: 2 1/2D arrays for vertical advective flux
80          _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
81          _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
82    
83    C !LOCAL VARIABLES: ====================================================
84    C  i,j                  :: loop indices
85    C  df4                  :: used for storing del^2 T for bi-harmonic term
86    C  fZon                 :: zonal flux
87    C  fmer                 :: meridional flux
88    C  af                   :: advective flux
89    C  df                   :: diffusive flux
90    C  localT               :: local copy of tracer field
91        INTEGER i,j        INTEGER i,j
       LOGICAL TOP_LAYER  
       _RL afFacT, dfFacT  
92        _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97        _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98    CEOP
99    
100  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
101  C--   only the kUp part of fverT is set in this subroutine  C--   only the kUp part of fverT is set in this subroutine
# Line 67  C--   the kDown is still required Line 110  C--   the kDown is still required
110         ENDDO         ENDDO
111        ENDDO        ENDDO
112    
       afFacT = 1. _d 0  
       dfFacT = 1. _d 0  
       TOP_LAYER = K .EQ. 1  
   
113  C--   Make local copy of tracer array  C--   Make local copy of tracer array
114        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
115         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 300  C-    Surface "correction" term at k=1 : Line 339  C-    Surface "correction" term at k=1 :
339  C-    add the advective flux to fVerT  C-    add the advective flux to fVerT
340        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
341         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
342          fVerT(i,j,kUp) = fVerT(i,j,kUp) + afFacT*af(i,j)          fVerT(i,j,kUp) = fVerT(i,j,kUp) + af(i,j)
343         ENDDO         ENDDO
344        ENDDO        ENDDO
345        ENDIF        ENDIF
# Line 319  C           boundary condition. Line 358  C           boundary condition.
358        ENDIF        ENDIF
359  c     DO j=1-Oly,sNy+Oly  c     DO j=1-Oly,sNy+Oly
360  c      DO i=1-Olx,sNx+Olx  c      DO i=1-Olx,sNx+Olx
361  c       fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)  c       fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
362  c      ENDDO  c      ENDDO
363  c     ENDDO  c     ENDDO
364    
# Line 334  C *note* should update GMREDI_RTRANSPORT Line 373  C *note* should update GMREDI_RTRANSPORT
373       I     myThid)       I     myThid)
374  c      DO j=1-Oly,sNy+Oly  c      DO j=1-Oly,sNy+Oly
375  c       DO i=1-Olx,sNx+Olx  c       DO i=1-Olx,sNx+Olx
376  c        fVerT(i,j,kUp) = fVerT(i,j,kUp) + dfFacT*df(i,j)*maskUp(i,j)  c        fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
377  c       ENDDO  c       ENDDO
378  c      ENDDO  c      ENDDO
379        ENDIF        ENDIF
# Line 342  c      ENDDO Line 381  c      ENDDO
381    
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          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)
385         ENDDO         ENDDO
386        ENDDO        ENDDO
387    
# Line 370  C *note* should update KPP_TRANSPORT_T t Line 409  C *note* should update KPP_TRANSPORT_T t
409         ENDIF         ENDIF
410         DO j=1-Oly,sNy+Oly         DO j=1-Oly,sNy+Oly
411          DO i=1-Olx,sNx+Olx          DO i=1-Olx,sNx+Olx
412           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)
413          ENDDO          ENDDO
414         ENDDO         ENDDO
415        ENDIF        ENDIF

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22