/[MITgcm]/MITgcm/model/src/calc_gtr1.F
ViewVC logotype

Diff of /MITgcm/model/src/calc_gtr1.F

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

revision 1.2 by heimbach, Tue Aug 21 15:46:15 2001 UTC revision 1.3 by adcroft, Tue Sep 18 19:07:35 2001 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
 #define COSINEMETH_III  
 #undef  ISOTROPIC_COS_SCALING  
   
 CStartOfInterFace  
6        SUBROUTINE CALC_GTR1(        SUBROUTINE CALC_GTR1(
7       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
8       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
# Line 17  C     /================================= Line 13  C     /=================================
13  C     | SUBROUTINE CALC_GTR1                                     |  C     | SUBROUTINE CALC_GTR1                                     |
14  C     | o Calculate the passive tracer tendency terms.           |  C     | o Calculate the passive tracer tendency terms.           |
15  C     |==========================================================|  C     |==========================================================|
 C     | A procedure called EXTERNAL_FORCING_TR1 is called from   |  
 C     | here. These procedures can be used to add per problem    |  
 C     | heat flux source terms.                                  |  
 C     | Note: Although it is slightly counter-intuitive the      |  
 C     |       EXTERNAL_FORCING routine is not the place to put   |  
 C     |       file I/O. Instead files that are required to       |  
 C     |       calculate the external source terms are generally  |  
 C     |       read during the model main loop. This makes the    |  
 C     |       logisitics of multi-processing simpler and also    |  
 C     |       makes the adjoint generation simpler. It also      |  
 C     |       allows for I/O to overlap computation where that   |  
 C     |       is supported by hardware.                          |  
 C     | Aside from the problem specific term the code here       |  
 C     | forms the tendency terms due to advection and mixing     |  
 C     | The baseline implementation here uses a centered         |  
 C     | difference form for the advection term and a tensorial   |  
 C     | divergence of a flux form for the diffusive term. The    |  
 C     | diffusive term is formulated so that isopycnal mixing and|  
 C     | GM-style subgrid-scale terms can be incorporated b simply|  
 C     | setting the diffusion tensor terms appropriately.        |  
16  C     \==========================================================/  C     \==========================================================/
17        IMPLICIT NONE        IMPLICIT NONE
18    
# Line 45  C     == GLobal variables == Line 21  C     == GLobal variables ==
21  #include "DYNVARS.h"  #include "DYNVARS.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
24  #include "GRID.h"  #include "GAD.h"
 #include "FFIELDS.h"  
25  #include "TR1.h"  #include "TR1.h"
 c #include "GM_ARRAYS.h"  
   
26    
27  C     == Routine arguments ==  C     == Routine arguments ==
28  C     fVerT   - Flux of passive tracer (TR1) in the vertical  C     fVerT   - Flux of temperature (T) in the vertical
29  C               direction at the upper(U) and lower(D) faces of a cell.  C               direction at the upper(U) and lower(D) faces of a cell.
30  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
31  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
# Line 62  C     vTrans  - Meridional volume transp Line 35  C     vTrans  - Meridional volume transp
35  C     rTrans  - Vertical volume transport through cell face  C     rTrans  - Vertical volume transport through cell face
36  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
37  C                                      results will be set.  C                                      results will be set.
38  C     myThid - Instance number for this innvocation of CALC_GTR1  C     myThid - Instance number for this innvocation of CALC_GT
39        _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
40        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 75  C     myThid - Instance number for this Line 48  C     myThid - Instance number for this
48        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
49        INTEGER myThid        INTEGER myThid
50        _RL     myCurrentTime        _RL     myCurrentTime
 CEndOfInterface  
51    
52  C     == Local variables ==  C     == Local variables ==
 C     I, J, K - Loop counters  
       INTEGER i,j  
       LOGICAL TOP_LAYER  
       _RL afFacT, dfFacT  
       _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
53    
54  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
55  C--   only the kUp part of fverT is set in this subroutine  C--   only the kUp part of fverT is set in this subroutine
56  C--   the kDown is still required  C--   the kDown is still required
57        fVerT(1,1,kDown) = fVerT(1,1,kDown)        fVerT(1,1,kDown) = fVerT(1,1,kDown)
58  #endif  #endif
       DO j=1-OLy,sNy+OLy  
        DO i=1-OLx,sNx+OLx  
         fZon(i,j)      = 0.0  
         fMer(i,j)      = 0.0  
         fVerT(i,j,kUp) = 0.0  
        ENDDO  
       ENDDO  
   
       afFacT = 1. _d 0  
       dfFacT = 1. _d 0  
       TOP_LAYER = K .EQ. 1  
   
 C---  Calculate advective and diffusive fluxes between cells.  
59    
60  #ifdef INCLUDE_TR1_DIFFUSION_CODE        CALL GAD_CALC_RHS(
61  C     o Zonal tracer gradient       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
62        DO j=1-Oly,sNy+Oly       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
63         DO i=1-Olx+1,sNx+Olx       I           diffKhT, diffK4T, KappaRT, tr1,
64          fZon(i,j) = _recip_dxC(i,j,bi,bj)*xA(i,j)       I           GAD_TR1, tracerAdvScheme,
65       &  *(tr1(i,j,k,bi,bj)-tr1(i-1,j,k,bi,bj))       U           fVerT, gTr1,
66  #ifdef COSINEMETH_III       I           myThid )
      &   *sqCosFacU(j,bi,bj)  
 #endif  
        ENDDO  
       ENDDO  
 C     o Meridional tracer gradient  
       DO j=1-Oly+1,sNy+Oly  
        DO i=1-Olx,sNx+Olx  
         fMer(i,j) = _recip_dyC(i,j,bi,bj)*yA(i,j)  
      &  *(tr1(i,j,k,bi,bj)-tr1(i,j-1,k,bi,bj))  
 #ifdef ISOTROPIC_COS_SCALING  
 #ifdef COSINEMETH_III  
      &   *sqCosFacV(j,bi,bj)  
 #endif  
 #endif  
        ENDDO  
       ENDDO  
 C--   del^2 of T, needed for bi-harmonic (del^4) term  
       IF (diffK4T .NE. 0.) THEN  
        DO j=1-Oly+1,sNy+Oly-1  
         DO i=1-Olx+1,sNx+Olx-1  
          df4(i,j)= _recip_hFacC(i,j,k,bi,bj)  
      &             *recip_drF(k)/_rA(i,j,bi,bj)  
      &            *(  
      &             +( fZon(i+1,j)-fZon(i,j) )  
      &             +( fMer(i,j+1)-fMer(i,j) )  
      &             )  
         ENDDO  
        ENDDO  
       ENDIF  
 #endif  
   
 C--   Zonal flux (fZon is at west face of "tr1" cell)  
 #ifdef INCLUDE_TR1_ADVECTION_CODE  
 C     o Advective component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   uTrans(i,j)*(tr1(i,j,k,bi,bj)+tr1(i-1,j,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 #endif /* INCLUDE_TR1_ADVECTION_CODE */  
 #ifdef INCLUDE_TR1_DIFFUSION_CODE  
 C     o Diffusive component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -diffKhT*xA(i,j)*_recip_dxC(i,j,bi,bj)*  
      &  (tr1(i,j,k,bi,bj)-tr1(i-1,j,k,bi,bj))  
      &   *CosFacU(j,bi,bj)  
        ENDDO  
       ENDDO  
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_XTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     xA,tr1,  
      U     df,  
      I     myThid)  
 #endif  
 C     o Add the bi-harmonic contribution  
       IF (diffK4T .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + xA(i,j)*  
      &    diffK4T*(df4(i,j)-df4(i-1,j))*_recip_dxC(i,j,bi,bj)  
 #ifdef COSINEMETH_III  
      &   *sqCosFacU(j,bi,bj)  
 #else  
      &   *CosFacU(j,bi,bj)  
 #endif  
         ENDDO  
        ENDDO  
       ENDIF  
 #endif /* INCLUDE_TR1_DIFFUSION_CODE */  
 C     o Net zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fZon(i,j) = 0.  
      & _ADT( + afFacT*af(i,j) )  
      & _LPT( + dfFacT*df(i,j) )  
        ENDDO  
       ENDDO  
   
 C--   Meridional flux (fMer is at south face of "tr1" cell)  
 #ifdef INCLUDE_TR1_ADVECTION_CODE  
 C     o Advective component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   vTrans(i,j)*(tr1(i,j,k,bi,bj)+tr1(i,j-1,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 #endif /* INCLUDE_TR1_ADVECTION_CODE */  
 #ifdef INCLUDE_TR1_DIFFUSION_CODE  
 C     o Diffusive component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -diffKhT*yA(i,j)*_recip_dyC(i,j,bi,bj)*  
      &  (tr1(i,j,k,bi,bj)-tr1(i,j-1,k,bi,bj))  
 #ifdef ISOTROPIC_COS_SCALING  
      &   *CosFacV(j,bi,bj)  
 #endif  
        ENDDO  
       ENDDO  
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_YTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     yA,tr1,  
      U     df,  
      I     myThid)  
 #endif  
 C     o Add the bi-harmonic contribution  
       IF (diffK4T .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + yA(i,j)*  
      &    diffK4T*(df4(i,j)-df4(i,j-1))*_recip_dyC(i,j,bi,bj)  
 #ifdef ISOTROPIC_COS_SCALING  
 #ifdef COSINEMETH_III  
      &   *sqCosFacV(j,bi,bj)  
 #else  
      &   *CosFacV(j,bi,bj)  
 #endif  
 #endif  
         ENDDO  
        ENDDO  
       ENDIF  
 #endif /* INCLUDE_TR1_DIFFUSION_CODE */  
 C     o Net meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fMer(i,j) = 0.  
      & _ADT( + afFacT*af(i,j) )  
      & _LPT( + dfFacT*df(i,j) )  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux ( fVerT(,,kUp) is at upper face of "Tracer" cell )  
 #ifdef INCLUDE_TR1_ADVECTION_CODE  
 C     o Advective component of vertical flux : assume W_bottom=0 (mask)  
 C     Note: For K=1 then KM1=1 this gives a barZ(T) = T  
 C     (this plays the role of the free-surface correction)  
       IF ( rigidLid .AND. TOP_LAYER) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          af(i,j) = 0.  
         ENDDO  
        ENDDO  
       ELSEIF ( rigidLid ) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          af(i,j) = rTrans(i,j)*  
      &       (tr1(i,j,k,bi,bj)+tr1(i,j,kM1,bi,bj))*0.5 _d 0  
         ENDDO  
        ENDDO  
       ELSE  
 C-  include "free-surface correction" :  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          af(i,j) = rTrans(i,j)*(  
      &      maskC(i,j,kM1,bi,bj)*  
      &       (tr1(i,j,k,bi,bj)+tr1(i,j,kM1,bi,bj))*0.5 _d 0  
      &    +(maskC(i,j,k,bi,bj)-maskC(i,j,kM1,bi,bj))*  
      &        tr1(i,j,k,bi,bj) )  
         ENDDO  
        ENDDO  
       ENDIF  
 #endif /* INCLUDE_TR1_ADVECTION_CODE */  
 #ifdef INCLUDE_TR1_DIFFUSION_CODE  
 C     o Diffusive component of vertical flux  
 C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper  
 C           boundary condition.  
       IF (implicitDiffusion) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = 0.  
         ENDDO  
        ENDDO  
       ELSE  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = - _rA(i,j,bi,bj)*(  
      &    KappaRT(i,j,k)*recip_drC(k)  
      &    *(tr1(i,j,kM1,bi,bj)-tr1(i,j,k,bi,bj))*rkFac  
      &    )  
         ENDDO  
        ENDDO  
       ENDIF  
 #endif /* INCLUDE_TR1_DIFFUSION_CODE */  
   
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_RTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     maskUp,tr1,  
      U     df,  
      I     myThid)  
 #endif  
   
 #ifdef ALLOW_KPP  
 C--   Add non local KPP transport term (ghat) to diffusive T flux.  
       IF (useKPP) CALL KPP_TRANSPORT_T(  
      I     iMin,iMax,jMin,jMax,bi,bj,k,km1,  
      I     KappaRT,  
      U     df )  
 #endif  
   
 C     o Net vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
 c       fVerT(i,j,kUp) = afFacT*af(i,j) + dfFacT*df(i,j)*maskUp(i,j)  
         fVerT(i,j,kUp) = 0.  
      & _ADT( +afFacT*af(i,j) )  
      & _LPT( +dfFacT*df(i,j)*maskUp(i,j) )  
        ENDDO  
       ENDDO  
   
 C--   Tendency is minus divergence of the fluxes.  
 C     Note. Tendency terms will only be correct for range  
 C           i=iMin+1:iMax-1, j=jMin+1:jMax-1. Edge points  
 C           will contain valid floating point numbers but  
 C           they are not algorithmically correct. These points  
 C           are not used.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gtr1(i,j,k,bi,bj)=  
      &   -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  
      &    *recip_rA(i,j,bi,bj)  
      &   *(  
      &    +( fZon(i+1,j)-fZon(i,j) )  
      &    +( fMer(i,j+1)-fMer(i,j) )  
      &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac  
      &    )  
        ENDDO  
       ENDDO  
67    
68  #ifdef INCLUDE_TR1_FORCING_CODE  #ifdef INCLUDE_TR_FORCING_CODE
69  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
70        CALL EXTERNAL_FORCING_TR1(        CALL EXTERNAL_FORCING_TR(
71       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
72       I     myCurrentTime,myThid)       I     myCurrentTime,myThid)
73  #endif /*  INCLUDE_TR1_FORCING_CODE */  #endif /*  INCLUDE_TR_FORCING_CODE */
74    
75        RETURN        RETURN
76        END        END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.3

  ViewVC Help
Powered by ViewVC 1.1.22