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

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

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

revision 1.3 by adcroft, Wed May 20 21:29:31 1998 UTC revision 1.36 by cnh, Wed Sep 26 18:09:14 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  CStartOfInterFace  CBOP
7    C     !ROUTINE: CALC_GT
8    C     !INTERFACE:
9        SUBROUTINE CALC_GT(        SUBROUTINE CALC_GT(
10       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
11       I           xA,yA,uTrans,vTrans,wTrans,maskup,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
12       I           K13,K23,K33,KapGM,       I           KappaRT,
13       U           af,df,fZon,fMer,fVerT,       U           fVerT,
14       I           myThid )       I           myTime,myIter,myThid )
15  C     /==========================================================\  C     !DESCRIPTION: \bv
16  C     | SUBROUTINE CALC_GT                                       |  C     *==========================================================*
17  C     | o Calculate the temperature tendency terms.              |  C     | SUBROUTINE CALC_GT                                        
18  C     |==========================================================|  C     | o Calculate the temperature tendency terms.              
19  C     | A procedure called EXTERNAL_FORCING_T is called from     |  C     *==========================================================*
20  C     | here. These procedures can be used to add per problem    |  C     | A procedure called EXTERNAL_FORCING_T is called from      
21  C     | heat flux source terms.                                  |  C     | here. These procedures can be used to add per problem    
22  C     | Note: Although it is slightly counter-intuitive the      |  C     | heat flux source terms.                                  
23  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     | Note: Although it is slightly counter-intuitive the      
24  C     |       file I/O. Instead files that are required to       |  C     |       EXTERNAL_FORCING routine is not the place to put    
25  C     |       calculate the external source terms are generally  |  C     |       file I/O. Instead files that are required to        
26  C     |       read during the model main loop. This makes the    |  C     |       calculate the external source terms are generally  
27  C     |       logisitics of multi-processing simpler and also    |  C     |       read during the model main loop. This makes the    
28  C     |       makes the adjoint generation simpler. It also      |  C     |       logisitics of multi-processing simpler and also    
29  C     |       allows for I/O to overlap computation where that   |  C     |       makes the adjoint generation simpler. It also      
30  C     |       is supported by hardware.                          |  C     |       allows for I/O to overlap computation where that    
31  C     | Aside from the problem specific term the code here       |  C     |       is supported by hardware.                          
32  C     | forms the tendency terms due to advection and mixing     |  C     | Aside from the problem specific term the code here        
33  C     | The baseline implementation here uses a centered         |  C     | forms the tendency terms due to advection and mixing      
34  C     | difference form for the advection term and a tensorial   |  C     | The baseline implementation here uses a centered          
35  C     | divergence of a flux form for the diffusive term. The    |  C     | difference form for the advection term and a tensorial    
36  C     | diffusive term is formulated so that isopycnal mixing and|  C     | divergence of a flux form for the diffusive term. The    
37  C     | GM-style subgrid-scale terms can be incorporated b simply|  C     | diffusive term is formulated so that isopycnal mixing and
38  C     | setting the diffusion tensor terms appropriately.        |  C     | GM-style subgrid-scale terms can be incorporated b simply
39  C     \==========================================================/  C     | setting the diffusion tensor terms appropriately.        
40        IMPLICIT NONE  C     *==========================================================*
41    C     \ev
42    
43    C     !USES:
44          IMPLICIT NONE
45  C     == GLobal variables ==  C     == GLobal variables ==
46  #include "SIZE.h"  #include "SIZE.h"
47  #include "DYNVARS.h"  #include "DYNVARS.h"
48  #include "EEPARAMS.h"  #include "EEPARAMS.h"
49  #include "PARAMS.h"  #include "PARAMS.h"
50  #include "GRID.h"  #include "GAD.h"
51    
52    C     !INPUT/OUTPUT PARAMETERS:
53  C     == Routine arguments ==  C     == Routine arguments ==
54  C     fZon    - Work array for flux of temperature in the east-west  C     fVerT   :: Flux of temperature (T) in the vertical
55  C               direction at the west face of a cell.  C                direction at the upper(U) and lower(D) faces of a cell.
56  C     fMer    - Work array for flux of temperature in the north-south  C     maskUp  :: Land mask used to denote base of the domain.
57  C               direction at the south face of a cell.  C     xA      :: Tracer cell face area normal to X
58  C     fVerT   - Flux of temperature (T) in the vertical  C     yA      :: Tracer cell face area normal to X
59  C               direction at the upper(U) and lower(D) faces of a cell.  C     uTrans  :: Zonal volume transport through cell face
60  C     maskUp  - Land mask used to denote base of the domain.  C     vTrans  :: Meridional volume transport through cell face
61  C     xA      - Tracer cell face area normal to X  C     rTrans  :: Vertical volume transport through cell face
62  C     yA      - Tracer cell face area normal to X  C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation
63  C     uTrans  - Zonal volume transport through cell face  C                                       results will be set.
64  C     vTrans  - Meridional volume transport through cell face  C     myThid :: Instance number for this innvocation of CALC_GT
 C     wTrans  - Vertical volume transport through cell face  
 C     af      - Advective flux component work array  
 C     df      - Diffusive flux component work array  
 C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  
 C                                      results will be set.  
 C     myThid - Instance number for this innvocation of CALC_GT  
       _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
65        _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
66        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
       _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)  
       _RL K33   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)  
       _RL KapGM (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)  
73        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
74        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
75          _RL     myTime
76          INTEGER myIter
77        INTEGER myThid        INTEGER myThid
78  CEndOfInterface  CEOP
79    
80  C     == Local variables ==  #ifdef ALLOW_AUTODIFF_TAMC
81  C     I, J, K - Loop counters  C--   only the kUp part of fverT is set in this subroutine
82        INTEGER i,j  C--   the kDown is still required
83        _RL afFacT, dfFacT        fVerT(1,1,kDown) = fVerT(1,1,kDown)
84        _RL dutdxFac  #endif
85        _RL dTdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
86        _RL dTdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        CALL GAD_CALC_RHS(
87         I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
88        afFacT = 1. _d 0       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
89        dfFacT = 1. _d 0       I           diffKhT, diffK4T, KappaRT, theta,
90        dutdxFac = afFacT       I           GAD_TEMPERATURE, tempAdvScheme,
91         U           fVerT, gT,
92  C---       I           myThid )
 C---  Calculate advective and diffusive fluxes between cells.  
 C---  
   
 C--   Zonal flux (fZon is at west face of "theta" cell)  
 C     Advective component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   uTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i-1,j,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Zonal tracer gradient  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dTdx(i,j) = rdxC(i,j,bi,bj)*  
      &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Diffusive component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i-1,j)))*  
      &            xA(i,j)*dTdx(i,j)  
        ENDDO  
       ENDDO  
 C     Net zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fZon(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Meridional flux (fMer is at south face of "theta" cell)  
 C     Advective component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
 C       Advective component of meridional flux  
         af(i,j) =  
      &   vTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j-1,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Zonal tracer gradient  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dTdy(i,j) = rdyC(i,j,bi,bj)*  
      &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Diffusive component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i,j-1)))*  
      &            yA(i,j)*dTdy(i,j)  
        ENDDO  
       ENDDO  
 C     Net meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fMer(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Interpolate terms for Redi/GM scheme  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dTdx(i,j) = 0.5*(  
      &   +0.5*(maskW(i+1,j,k,bi,bj)*rdxC(i+1,j,bi,bj)*  
      &           (theta(i+1,j,k,bi,bj)-theta(i,j,k,bi,bj))  
      &        +maskW(i,j,k,bi,bj)*rdxC(i,j,bi,bj)*  
      &           (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj)))  
      &   +0.5*(maskW(i+1,j,km1,bi,bj)*rdxC(i+1,j,bi,bj)*  
      &           (theta(i+1,j,km1,bi,bj)-theta(i,j,km1,bi,bj))  
      &        +maskW(i,j,km1,bi,bj)*rdxC(i,j,bi,bj)*  
      &           (theta(i,j,km1,bi,bj)-theta(i-1,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dTdy(i,j) = 0.5*(  
      &   +0.5*(maskS(i,j,k,bi,bj)*rdyC(i,j,bi,bj)*  
      &           (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))  
      &        +maskS(i,j+1,k,bi,bj)*rdyC(i,j+1,bi,bj)*  
      &           (theta(i,j+1,k,bi,bj)-theta(i,j,k,bi,bj)))  
      &   +0.5*(maskS(i,j,km1,bi,bj)*rdyC(i,j,bi,bj)*  
      &           (theta(i,j,km1,bi,bj)-theta(i,j-1,km1,bi,bj))  
      &        +maskS(i,j+1,km1,bi,bj)*rdyC(i,j+1,bi,bj)*  
      &           (theta(i,j+1,km1,bi,bj)-theta(i,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux (fVerT) above  
 C     Advective component of vertical flux  
 C     Note: For K=1 then KM1=1 this gives a barZ(T) = T  
 C     (this plays the role of the free-surface correction)  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   wTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j,kM1,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Diffusive component of vertical flux  
 C     Note: For K=1 then KM1=1 this gives a dT/dz = 0 upper  
 C           boundary condition.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = zA(i,j,bi,bj)*(  
      &   -(diffKzT+KapGM(i,j)*K33(i,j,k))*rdzC(k)  
      &   *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))  
      &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)  
      &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)  
      &   )  
        ENDDO  
       ENDDO  
 C     Net vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fVerT(i,j,kUp) = (afFacT*af(i,j) + 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  
         gT(i,j,k,bi,bj)=  
      &   -rHFacC(i,j,k,bi,bj)*rdzF(k)*rDxF(i,j,bi,bj)*rDyF(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) )  
      &    )  
        ENDDO  
       ENDDO  
93    
94    #ifdef INCLUDE_T_FORCING_CODE
95  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
96          CALL EXTERNAL_FORCING_T(
97         I     iMin,iMax,jMin,jMax,bi,bj,k,
98         I     myTime,myThid)
99    #endif /*  INCLUDE_T_FORCING_CODE */
100    
101          IF ( tempAdvScheme.EQ.ENUM_CENTERED_2ND
102         & .OR.tempAdvScheme.EQ.ENUM_UPWIND_3RD
103         & .OR.tempAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN
104            CALL ADAMS_BASHFORTH2(
105         I                        bi, bj, K,
106         U                        gT, gTnm1,
107         I                        myIter, myThid )
108          ENDIF
109    
110    #ifdef NONLIN_FRSURF
111          IF (nonlinFreeSurf.GT.0) THEN
112            CALL FREESURF_RESCALE_G(
113         I                          bi, bj, K,
114         U                          gT,
115         I                          myThid )
116          ENDIF
117    #endif /* NONLIN_FRSURF */
118    
119        RETURN        RETURN
120        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22