/[MITgcm]/MITgcm/verification/aim.5l_cs/code/calc_gs.F
ViewVC logotype

Diff of /MITgcm/verification/aim.5l_cs/code/calc_gs.F

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

revision 1.2 by adcroft, Wed Sep 19 02:43:27 2001 UTC revision 1.3 by jmc, Thu Sep 27 15:49:45 2001 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  #define COSINEMETH_III  CBOP
7  #undef  ISOTROPIC_COS_SCALING  C     !ROUTINE: CALC_GS
8  #define  USE_3RD_O_ADVEC  C     !INTERFACE:
   
 CStartOfInterFace  
9        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
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,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
12       I           KappaRS,       I           KappaRS,
13       U           fVerS,       U           fVerS,
14       I           myCurrentTime,myIter,myThid )       I           myTime,myIter,myThid )
15  C     /==========================================================\  C     !DESCRIPTION: \bv
16  C     | SUBROUTINE CALC_GS                                       |  C     *==========================================================*
17  C     | o Calculate the salt tendency terms.                     |  C     | SUBROUTINE CALC_GS                                        
18  C     |==========================================================|  C     | o Calculate the salt tendency terms.                      
19  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     *==========================================================*
20  C     | here. These procedures can be used to add per problem    |  C     | A procedure called EXTERNAL_FORCING_S is called from      
21  C     | E-P  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     | E-P  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"
 #include "GRID.h"  
 #include "FFIELDS.h"  
50  #include "GAD.h"  #include "GAD.h"
51    
52    C     !INPUT/OUTPUT PARAMETERS:
53  C     == Routine arguments ==  C     == Routine arguments ==
54  C     fVerS   - Flux of salt (S) in the vertical  C     fVerS   :: Flux of salt (S) in the vertical
55  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.
56  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  :: Land mask used to denote base of the domain.
57  C     xA      - Tracer cell face area normal to X  C     xA      :: Tracer cell face area normal to X
58  C     yA      - Tracer cell face area normal to X  C     yA      :: Tracer cell face area normal to X
59  C     uTrans  - Zonal volume transport through cell face  C     uTrans  :: Zonal volume transport through cell face
60  C     vTrans  - Meridional volume transport through cell face  C     vTrans  :: Meridional volume transport through cell face
61  C     rTrans  - Vertical volume transport through cell face  C     rTrans  :: Vertical volume transport through cell face
62  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
63  C                                      results will be set.  C                                      results will be set.
64  C     myThid - Instance number for this innvocation of CALC_GT  C     myThid :: Instance number for this innvocation of CALC_GT
65        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (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)
# Line 72  C     myThid - Instance number for this Line 72  C     myThid - Instance number for this
72        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
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     myCurrentTime        _RL     myTime
76        INTEGER myIter        INTEGER myIter
77        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
78    
79  C     == Local variables ==  CEOP
 C     I, J, K - Loop counters  
 C     tauUpwH - Horizontal upwind weight : 1=Upwind ; 0=Centered  
 C     tauUpwV - Vertical   upwind weight : 1=Upwind ; 0=Centered  
       INTEGER i,j  
       LOGICAL TOP_LAYER  
       _RL afFacS, dfFacS  
       _RL tauUpwH, tauUpwV  
       _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)  
 c_jmc:  
       _RL ddx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL d2dx2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL ddy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL d2dy2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL phiLo(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL phiHi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL dist  
 c_jmc.  
80    
81  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
82  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
83  C--   the kDown is still required  C--   the kDown is still required
84        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
85  #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  
       tauUpwH = 1. _d 0  
       tauUpwV = 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  
86    
87  C--   Zonal flux (fZon is at west face of "salt" cell)        CALL GAD_CALC_RHS(
88  c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
89  #ifdef USE_3RD_O_ADVEC       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
90  C     o Advective component of zonal flux, 3rd order Advec Scheme       I           diffKhS, diffK4S, KappaRS, Salt,
91        DO j=jMin,jMax       I           GAD_SALINITY, saltAdvScheme,
92         DO i=1-OLx+1,sNx+OLx       U           fVerS, gS,
93          ddx(i,j)   = (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))       I           myThid )
      &               *_recip_dxC(i,j,bi,bj)*_maskW(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=1-OLx,sNx+OLx-1  
         d2dx2(i,j) = ( ddx(i+1,j)-ddx(i,j) )  
      &               *_recip_dxF(i,j,bi,bj)*maskC(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=1-OLx+1,sNx+OLx  
         dist = _dxF(i-1,j,bi,bj)*0.5 _d 0  
         phiLo(i,j) = salt(i-1,j,k,bi,bj)  
      &               +dist  
      &                *( ddx(i  ,j)+ddx(i-1,j) )*0.5 _d 0  
      &               +0.5 _d 0*dist*dist  
      &                *d2dx2(i-1,j)  
         dist = -_dxF(i,j,bi,bj)*0.5 _d 0  
         phiHi(i,j) = salt(i,j,k,bi,bj)  
      &               +dist  
      &                *( ddx(i+1,j)+ddx(i  ,j) )*0.5 _d 0  
      &               +0.5 _d 0*dist*dist  
      &                *d2dx2(i,j)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=1-OLx,sNx+OLx  
         IF ( uTrans(i,j) .GT. 0. ) THEN  
          af(i,j) = uTrans(i,j)*phiLo(i,j)  
         ELSE  
          af(i,j) = uTrans(i,j)*phiHi(i,j)  
         ENDIF  
        ENDDO  
       ENDDO  
 #else  
 C     o Advective component of zonal flux, 1rst & 2nd order Advec Scheme  
       IF (tauUpwH.EQ.0. _d 0) THEN  
 C       Centered scheme :  
         DO j=jMin,jMax  
          DO i=iMin,iMax  
           af(i,j) = uTrans(i,j)*  
      &               (salt(i-1,j,k,bi,bj)+salt(i,j,k,bi,bj))*0.5 _d 0  
          ENDDO  
         ENDDO  
       ELSE  
 C       Upwind weighted scheme :  
         DO j=jMin,jMax  
          DO i=iMin,iMax  
           af(i,j) = uTrans(i,j)*  
      &               (salt(i-1,j,k,bi,bj)+salt(i,j,k,bi,bj))*0.5 _d 0  
      &     +tauUpwH*abs(uTrans(i,j))*  
      &               (salt(i-1,j,k,bi,bj)-salt(i,j,k,bi,bj))*0.5 _d 0  
          ENDDO  
         ENDDO  
       ENDIF  
 #endif  
 c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
 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---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
 #ifdef USE_3RD_O_ADVEC  
 C     o Advective component of meridional flux, 3rd order Advec Scheme  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         ddy(i,j) = (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
      &             *_recip_dyC(i,j,bi,bj)*_maskS(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         d2dy2(i,j) = ( ddy(i,j+1)-ddy(i,j) )  
      &               *_recip_dyF(i,j,bi,bj)*maskC(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dist = _dyF(i,j-1,bi,bj)*0.5 _d 0  
         phiLo(i,j) = salt(i,j-1,k,bi,bj)  
      &               +dist  
      &                *( ddy(i  ,j)+ddy(i,j-1) )*0.5 _d 0  
      &               +0.5 _d 0*dist*dist  
      &                *d2dy2(i,j-1)  
         dist = -_dyF(i,j,bi,bj)*0.5 _d 0  
         phiHi(i,j) = salt(i,j,k,bi,bj)  
      &               +dist  
      &                *( ddy(i,j+1)+ddy(i  ,j) )*0.5 _d 0  
      &               +0.5 _d 0*dist*dist  
      &                *d2dy2(i,j)  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         IF ( vTrans(i,j) .GT. 0. ) THEN  
          af(i,j) = vTrans(i,j)*phiLo(i,j)  
         ELSE  
          af(i,j) = vTrans(i,j)*phiHi(i,j)  
         ENDIF  
        ENDDO  
       ENDDO  
 #else  
 C     o Advective component of meridional flux, 1rst & 2nd order Advec Scheme  
       IF (tauUpwH.EQ.0. _d 0) THEN  
 C       Centered scheme :  
         DO j=jMin,jMax  
          DO i=iMin,iMax  
           af(i,j) = vTrans(i,j)*  
      &               (salt(i,j-1,k,bi,bj)+salt(i,j,k,bi,bj))*0.5 _d 0  
          ENDDO  
         ENDDO  
       ELSE  
 C       Upwind weighted scheme :  
         DO j=jMin,jMax  
          DO i=iMin,iMax  
           af(i,j) = vTrans(i,j)*  
      &               (salt(i,j-1,k,bi,bj)+salt(i,j,k,bi,bj))*0.5 _d 0  
      &     +tauUpwH*abs(vTrans(i,j))*  
      &               (salt(i,j-1,k,bi,bj)-salt(i,j,k,bi,bj))*0.5 _d 0  
          ENDDO  
         ENDDO  
       ENDIF  
 #endif  
 c---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  
 C     o 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 for k=1)  
       IF ( rigidLid .AND. TOP_LAYER) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          af(i,j) = 0.  
         ENDDO  
        ENDDO  
       ELSE  
        IF (tauUpwV.EQ.0. _d 0) THEN  
 C       Centered scheme :  
         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  
 C       Upwind weighted scheme :  
         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  
      &     +tauUpwV*abs(rTrans(i,j))*  
      &               (salt(i,j,k,bi,bj)-salt(i,j,kM1,bi,bj))*0.5 _d 0  
          ENDDO  
         ENDDO  
        ENDIF  
        IF (.NOT.rigidLid ) THEN  
 C       free-surface correction for k > 1  
         DO j=jMin,jMax  
          DO i=iMin,iMax  
           af(i,j) = af(i,j)*maskC(i,j,kM1,bi,bj)  
      &     +rTrans(i,j)*(maskC(i,j,k,bi,bj)-maskC(i,j,kM1,bi,bj))*  
      &                salt(i,j,k,bi,bj)  
          ENDDO  
         ENDDO  
        ENDIF  
       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  
   
 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  
   
 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  
 #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  
94    
95  C--   External forcing term(s)  C--   External forcing term(s)
96        CALL EXTERNAL_FORCING_S(  c     CALL EXTERNAL_FORCING_S(
97       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
98       I     myCurrentTime,myThid)  c    I     myTime,myThid)
99    
100        IF ( saltAdvScheme.EQ.ENUM_CENTERED_2ND        IF ( saltAdvScheme.EQ.ENUM_CENTERED_2ND
101       & .OR.saltAdvScheme.EQ.ENUM_UPWIND_3RD       & .OR.saltAdvScheme.EQ.ENUM_UPWIND_3RD
# Line 480  C--   External forcing term(s) Line 106  C--   External forcing term(s)
106       I                        myIter, myThid )       I                        myIter, myThid )
107        ENDIF        ENDIF
108    
109    C--   External forcing term(s)
110          CALL EXTERNAL_FORCING_S(
111         I     iMin,iMax,jMin,jMax,bi,bj,k,
112         I     myTime,myThid)
113    
114  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
115        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
116          CALL FREESURF_RESCALE_G(          CALL FREESURF_RESCALE_G(

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

  ViewVC Help
Powered by ViewVC 1.1.22