/[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.32 by cnh, Wed Sep 26 18:09:14 2001 UTC revision 1.35 by jmc, Wed Jan 7 21:18:01 2004 UTC
# Line 8  C     !ROUTINE: CALC_GS Line 8  C     !ROUTINE: CALC_GS
8  C     !INTERFACE:  C     !INTERFACE:
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,rTransKp1,maskUp,
12       I           KappaRS,       I           KappaRS,
13       U           fVerS,       U           fVerS,
14       I           myTime,myIter,myThid )       I           myTime,myIter,myThid )
# Line 58  C     xA      :: Tracer cell face area n Line 58  C     xA      :: Tracer cell face area n
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 at interface k
62    C     rTransKp1 :: Vertical volume transport at inteface k+1
63  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
64  C                                      results will be set.  C                                      results will be set.
65  C     myThid :: Instance number for this innvocation of CALC_GT  C     myThid :: Instance number for this innvocation of CALC_GT
# Line 68  C     myThid :: Instance number for this Line 69  C     myThid :: Instance number for this
69        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
75        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
# Line 78  C     myThid :: Instance number for this Line 80  C     myThid :: Instance number for this
80    
81  CEOP  CEOP
82    
83    C     === Local variables ===
84          LOGICAL calcAdvection
85    
86  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
87  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
88  C--   the kDown is still required  C--   the kDown is still required
89        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
90  #endif  #endif
91    
92          calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
93        CALL GAD_CALC_RHS(        CALL GAD_CALC_RHS(
94       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
95       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
96         I           uVel, vVel, wVel,
97       I           diffKhS, diffK4S, KappaRS, Salt,       I           diffKhS, diffK4S, KappaRS, Salt,
98       I           GAD_SALINITY, saltAdvScheme,       I           GAD_SALINITY, saltAdvScheme,
99         I           calcAdvection, saltImplVertAdv,
100       U           fVerS, gS,       U           fVerS, gS,
101       I           myThid )       I           myThid )
102    
103  C--   External forcing term(s)  C--   External salinity forcing term(s) inside Adams-Bashforth:
104        CALL EXTERNAL_FORCING_S(        IF ( saltForcing .AND. forcing_In_AB )
105         & CALL EXTERNAL_FORCING_S(
106       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
107       I     myTime,myThid)       I     myTime,myThid)
108    
109        IF ( saltAdvScheme.EQ.ENUM_CENTERED_2ND        IF ( saltAdamsBashforth ) THEN
      & .OR.saltAdvScheme.EQ.ENUM_UPWIND_3RD  
      & .OR.saltAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN  
110          CALL ADAMS_BASHFORTH2(          CALL ADAMS_BASHFORTH2(
111       I                        bi, bj, K,       I                        bi, bj, K,
112       U                        gS, gSnm1,       U                        gS, gSnm1,
113       I                        myIter, myThid )       I                        myIter, myThid )
114        ENDIF        ENDIF
115    
116    C--   External salinity forcing term(s) outside Adams-Bashforth:
117          IF ( saltForcing .AND. .NOT.forcing_In_AB )
118         & CALL EXTERNAL_FORCING_S(
119         I     iMin,iMax,jMin,jMax,bi,bj,k,
120         I     myTime,myThid)
121    
122  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
123        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
124          CALL FREESURF_RESCALE_G(          CALL FREESURF_RESCALE_G(
125       I                          bi, bj, K,       I                          bi, bj, K,
126       U                          gS,       U                          gS,
127       I                          myThid )       I                          myThid )
128            IF ( saltAdamsBashforth )
129         &  CALL FREESURF_RESCALE_G(
130         I                          bi, bj, K,
131         U                          gSnm1,
132         I                          myThid )
133        ENDIF        ENDIF
134  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
135    

Legend:
Removed from v.1.32  
changed lines
  Added in v.1.35

  ViewVC Help
Powered by ViewVC 1.1.22