/[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.29 by heimbach, Tue Aug 21 15:46:15 2001 UTC revision 1.30 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_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,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
# Line 45  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 ==
47  C     fVerS   - Flux of salt (S) in the vertical  C     fVerS   - Flux of salt (S) in the vertical
# Line 72  C     myThid - Instance number for this Line 67  C     myThid - Instance number for this
67        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
68        _RL     myCurrentTime        _RL     myCurrentTime
69        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
70    
71  C     == Local variables ==  C     == Local variables ==
 C     I, J, K - Loop counters  
       INTEGER i,j  
       LOGICAL TOP_LAYER  
       _RL afFacS, dfFacS  
       _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)  
72    
73  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
74  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
75  C--   the kDown is still required  C--   the kDown is still required
76        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
77  #endif  #endif
       DO j=1-OLy,sNy+OLy  
        DO i=1-OLx,sNx+OLx  
         fZon(i,j)      = 0.0  
         fMer(i,j)      = 0.0  
         fVerS(i,j,kUp) = 0.0  
        ENDDO  
       ENDDO  
   
       afFacS = 1. _d 0  
       dfFacS = 1. _d 0  
       TOP_LAYER = K .EQ. 1  
   
 C---  Calculate advective and diffusive fluxes between cells.  
   
 C     o Zonal tracer gradient  
       DO j=1-Oly,sNy+Oly  
        DO i=1-Olx+1,sNx+Olx  
         fZon(i,j) = _recip_dxC(i,j,bi,bj)*xA(i,j)  
      &   *(salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))  
 #ifdef COSINEMETH_III  
      &   *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)  
      &   *(salt(i,j,k,bi,bj)-salt(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 S, needed for bi-harmonic (del^4) term  
       IF (diffK4S .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  
   
 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     o Diffusive component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -diffKhS*xA(i,j)*_recip_dxC(i,j,bi,bj)*  
      &  (salt(i,j,k,bi,bj)-salt(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,salt,  
      U     df,  
      I     myThid)  
 #endif  
 C     o Add the bi-harmonic contribution  
       IF (diffK4S .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + xA(i,j)*  
      &    diffK4S*(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  
 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     Diffusive component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = -diffKhS*yA(i,j)*_recip_dyC(i,j,bi,bj)*  
      &  (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
      &   *CosFacV(j,bi,bj)  
        ENDDO  
       ENDDO  
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_YTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     yA,salt,  
      U     df,  
      I     myThid)  
 #endif  
 C     o Add the bi-harmonic contribution  
       IF (diffK4S .NE. 0.) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = df(i,j) + yA(i,j)*  
      &    diffK4S*(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  
   
 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  
   
 C--   Vertical flux ( fVerS(,,kUp) is at upper face of "Tracer" cell )  
 C     o Advective component of vertical flux : assume W_bottom=0 (mask)  
 C     Note: For K=1 then KM1=1 this gives a barZ(S) = S  
 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)*  
      &       (salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0  
         ENDDO  
        ENDDO  
       ELSE  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          af(i,j) = rTrans(i,j)*(  
      &      maskC(i,j,kM1,bi,bj)*  
      &       (salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0  
      &    +(maskC(i,j,k,bi,bj)-maskC(i,j,kM1,bi,bj))*  
      &        salt(i,j,k,bi,bj) )  
         ENDDO  
        ENDDO  
       ENDIF  
 C     o Diffusive component of vertical flux  
 C     Note: For K=1 then KM1=1 and this gives a dS/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)*(  
      &    KappaRS(i,j,k)*recip_drC(k)  
      &    *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))*rkFac  
      &    )  
         ENDDO  
        ENDDO  
       ENDIF  
   
 #ifdef ALLOW_GMREDI  
       IF (useGMRedi) CALL GMREDI_RTRANSPORT(  
      I     iMin,iMax,jMin,jMax,bi,bj,K,  
      I     maskUp,salt,  
      U     df,  
      I     myThid)  
 #endif  
   
 #ifdef ALLOW_KPP  
 C--   Add non-local KPP transport term (ghat) to diffusive salt flux.  
       IF (useKPP) CALL KPP_TRANSPORT_S(  
      I     iMin,iMax,jMin,jMax,bi,bj,k,km1,  
      I     KappaRS,  
      U     df )  
 #endif  
78    
79  C     Net vertical flux        CALL GAD_CALC_RHS(
80        DO j=jMin,jMax       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
81         DO i=iMin,iMax       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
82          fVerS(i,j,kUp) = afFacS*af(i,j) + dfFacS*df(i,j)*maskUp(i,j)       I           diffKhS, diffK4S, KappaRS, Salt,
83         ENDDO       I           GAD_SALINITY, saltAdvScheme,
84        ENDDO       U           fVerS, gS,
85         I           myThid )
 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  
         gS(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) )  
      &    +( 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(

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

  ViewVC Help
Powered by ViewVC 1.1.22