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

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

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

revision 1.17 by cnh, Fri Nov 6 22:44:44 1998 UTC revision 1.30 by adcroft, Tue Sep 18 19:07:35 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
 CStartOfInterFace  
6        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
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,maskC,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
9       I           K13,K23,KappaRS,KapGM,       I           KappaRS,
10       U           af,df,fZon,fMer,fVerS,       U           fVerS,
11       I           myCurrentTime, myThid )       I           myCurrentTime, myThid )
12  C     /==========================================================\  C     /==========================================================\
13  C     | SUBROUTINE CALC_GS                                       |  C     | SUBROUTINE CALC_GS                                       |
# Line 41  C     == GLobal variables == Line 41  C     == GLobal variables ==
41  #include "DYNVARS.h"  #include "DYNVARS.h"
42  #include "EEPARAMS.h"  #include "EEPARAMS.h"
43  #include "PARAMS.h"  #include "PARAMS.h"
44  #include "GRID.h"  #include "GAD.h"
 #include "FFIELDS.h"  
45    
46  C     == Routine arguments ==  C     == Routine arguments ==
 C     fZon    - Work array for flux of temperature in the east-west  
 C               direction at the west face of a cell.  
 C     fMer    - Work array for flux of temperature in the north-south  
 C               direction at the south face of a cell.  
47  C     fVerS   - Flux of salt (S) in the vertical  C     fVerS   - Flux of salt (S) in the vertical
48  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.
49  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
 C     maskC   - Land mask for salt cells (used in TOP_LAYER only)  
50  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
51  C     yA      - Tracer cell face area normal to X  C     yA      - Tracer cell face area normal to X
52  C     uTrans  - Zonal volume transport through cell face  C     uTrans  - Zonal volume transport through cell face
53  C     vTrans  - Meridional volume transport through cell face  C     vTrans  - Meridional volume transport through cell face
54  C     wTrans  - Vertical volume transport through cell face  C     rTrans  - Vertical volume transport through cell face
 C     af      - Advective flux component work array  
 C     df      - Diffusive flux component work array  
55  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
56  C                                      results will be set.  C                                      results will be set.
57  C     myThid - Instance number for this innvocation of CALC_GT  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)  
58        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
59        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 72  C     myThid - Instance number for this Line 62  C     myThid - Instance number for this
62        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
65        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
       _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)  
66        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
67        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
       INTEGER myThid  
68        _RL     myCurrentTime        _RL     myCurrentTime
69  CEndOfInterface        INTEGER myThid
70    
71  C     == Local variables ==  C     == Local variables ==
 C     I, J, K - Loop counters  
       INTEGER i,j  
       LOGICAL TOP_LAYER  
       _RL afFacS, dfFacS  
       _RL dSdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL dSdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
   
       afFacS = 1. _d 0  
       dfFacS = 1. _d 0  
       TOP_LAYER = K .EQ. 1  
   
 C---  Calculate advective and diffusive fluxes between cells.  
   
 C--   Zonal flux (fZon is at west face of "salt" cell)  
 C     Advective component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Zonal tracer gradient  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dSdx(i,j) = _recip_dxC(i,j,bi,bj)*  
      &  (salt(i,j,k,bi,bj)-salt(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) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i-1,j)))*  
      &            xA(i,j)*dSdx(i,j)  
        ENDDO  
       ENDDO  
 C     Net zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fZon(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Meridional flux (fMer is at south face of "salt" 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)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Zonal tracer gradient  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dSdy(i,j) = _recip_dyC(i,j,bi,bj)*  
      &  (salt(i,j,k,bi,bj)-salt(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) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i,j-1)))*  
      &            yA(i,j)*dSdy(i,j)  
        ENDDO  
       ENDDO  
 C     Net meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fMer(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
72    
73  C--   Interpolate terms for Redi/GM scheme  #ifdef ALLOW_AUTODIFF_TAMC
74        DO j=jMin,jMax  C--   only the kUp part of fverS is set in this subroutine
75         DO i=iMin,iMax  C--   the kDown is still required
76          dSdx(i,j) = 0.5*(        fVerS(1,1,kDown) = fVerS(1,1,kDown)
77       &   +0.5*(_maskW(i+1,j,k,bi,bj)  #endif
      &         *_recip_dxC(i+1,j,bi,bj)*  
      &           (salt(i+1,j,k,bi,bj)-salt(i,j,k,bi,bj))  
      &        +_maskW(i,j,k,bi,bj)  
      &         *_recip_dxC(i,j,bi,bj)*  
      &           (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj)))  
      &   +0.5*(_maskW(i+1,j,km1,bi,bj)  
      &         *_recip_dxC(i+1,j,bi,bj)*  
      &           (salt(i+1,j,km1,bi,bj)-salt(i,j,km1,bi,bj))  
      &        +_maskW(i,j,km1,bi,bj)  
      &         *_recip_dxC(i,j,bi,bj)*  
      &           (salt(i,j,km1,bi,bj)-salt(i-1,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dSdy(i,j) = 0.5*(  
      &   +0.5*(_maskS(i,j,k,bi,bj)  
      &         *_recip_dyC(i,j,bi,bj)*  
      &           (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
      &        +_maskS(i,j+1,k,bi,bj)  
      &         *_recip_dyC(i,j+1,bi,bj)*  
      &           (salt(i,j+1,k,bi,bj)-salt(i,j,k,bi,bj)))  
      &   +0.5*(_maskS(i,j,km1,bi,bj)  
      &         *_recip_dyC(i,j,bi,bj)*  
      &           (salt(i,j,km1,bi,bj)-salt(i,j-1,km1,bi,bj))  
      &        +_maskS(i,j+1,km1,bi,bj)  
      &         *_recip_dyC(i,j+1,bi,bj)*  
      &           (salt(i,j+1,km1,bi,bj)-salt(i,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux (fVerS) 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) =  
      &   rTrans(i,j)*(salt(i,j,k,bi,bj)+salt(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 dS/dz = 0 upper  
 C           boundary condition.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = _rA(i,j,bi,bj)*(  
      &   -KapGM(i,j)*K13(i,j,k)*dSdx(i,j)  
      &   -KapGM(i,j)*K23(i,j,k)*dSdy(i,j)  
      &   )  
        ENDDO  
       ENDDO  
       IF (.NOT.implicitDiffusion) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + _rA(i,j,bi,bj)*(  
      &    -KappaRS(i,j,k)*recip_drC(k)  
      &    *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))*rkFac  
      &    )  
         ENDDO  
        ENDDO  
       ENDIF  
 C     Net vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fVerS(i,j,kUp) = ( afFacS*af(i,j)+  dfFacS*df(i,j) )*maskUp(i,j)  
        ENDDO  
       ENDDO  
       IF ( TOP_LAYER ) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          fVerS(i,j,kUp) = afFacS*af(i,j)*freeSurfFac  
         ENDDO  
        ENDDO  
       ENDIF  
78    
79  C--   Tendency is minus divergence of the fluxes.        CALL GAD_CALC_RHS(
80  C     Note. Tendency terms will only be correct for range       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
81  C           i=iMin+1:iMax-1, j=jMin+1:jMax-1. Edge points       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
82  C           will contain valid floating point numbers but       I           diffKhS, diffK4S, KappaRS, Salt,
83  C           they are not algorithmically correct. These points       I           GAD_SALINITY, saltAdvScheme,
84  C           are not used.       U           fVerS, gS,
85        DO j=jMin,jMax       I           myThid )
        DO i=iMin,iMax  
 #define _recip_VolS1(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)  
 #define _recip_VolS2(i,j,k,bi,bj) /_rA(i,j,bi,bj)  
         gS(i,j,k,bi,bj)=  
      &   -_recip_VolS1(i,j,k,bi,bj)  
      &    _recip_VolS2(i,j,k,bi,bj)  
      &   *(  
      &    +( fZon(i+1,j)-fZon(i,j) )  
      &    +( fMer(i,j+1)-fMer(i,j) )  
      &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )*rkFac  
      &    )  
        ENDDO  
       ENDDO  
86    
87  C--   External forcing term(s)  C--   External forcing term(s)
88        CALL EXTERNAL_FORCING_S(        CALL EXTERNAL_FORCING_S(
89       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
      I     maskC,  
90       I     myCurrentTime,myThid)       I     myCurrentTime,myThid)
91    
 #ifdef INCLUDE_LAT_CIRC_FFT_FILTER_CODE  
 C--  
       CALL FILTER_LATCIRCS_FFT_APPLY( gS, 1, sNy, k, k, bi, bj, 1, myThid)  
 #endif  
   
92        RETURN        RETURN
93        END        END

Legend:
Removed from v.1.17  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.22