/[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.31 by adcroft, Wed Sep 19 02:43:27 2001 UTC revision 1.41 by jmc, Sun Nov 6 22:19:08 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7    CBOP
8    C     !ROUTINE: CALC_GS
9    C     !INTERFACE:
10        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
11       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
13       I           KappaRS,       I           KappaRS,
14       U           fVerS,       U           fVerS,
15       I           myTime,myIter,myThid )       I           myTime,myIter,myThid )
16  C     /==========================================================\  C     !DESCRIPTION: \bv
17  C     | SUBROUTINE CALC_GS                                       |  C     *==========================================================*
18  C     | o Calculate the salt tendency terms.                     |  C     | SUBROUTINE CALC_GS                                        
19  C     |==========================================================|  C     | o Calculate the salt tendency terms.                      
20  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     *==========================================================*
21  C     | here. These procedures can be used to add per problem    |  C     | A procedure called EXTERNAL_FORCING_S is called from      
22  C     | E-P  flux source terms.                                  |  C     | here. These procedures can be used to add per problem    
23  C     | Note: Although it is slightly counter-intuitive the      |  C     | E-P  flux source terms.                                  
24  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     | Note: Although it is slightly counter-intuitive the      
25  C     |       file I/O. Instead files that are required to       |  C     |       EXTERNAL_FORCING routine is not the place to put    
26  C     |       calculate the external source terms are generally  |  C     |       file I/O. Instead files that are required to        
27  C     |       read during the model main loop. This makes the    |  C     |       calculate the external source terms are generally  
28  C     |       logisitics of multi-processing simpler and also    |  C     |       read during the model main loop. This makes the    
29  C     |       makes the adjoint generation simpler. It also      |  C     |       logisitics of multi-processing simpler and also    
30  C     |       allows for I/O to overlap computation where that   |  C     |       makes the adjoint generation simpler. It also      
31  C     |       is supported by hardware.                          |  C     |       allows for I/O to overlap computation where that    
32  C     | Aside from the problem specific term the code here       |  C     |       is supported by hardware.                          
33  C     | forms the tendency terms due to advection and mixing     |  C     | Aside from the problem specific term the code here        
34  C     | The baseline implementation here uses a centered         |  C     | forms the tendency terms due to advection and mixing      
35  C     | difference form for the advection term and a tensorial   |  C     | The baseline implementation here uses a centered          
36  C     | divergence of a flux form for the diffusive term. The    |  C     | difference form for the advection term and a tensorial    
37  C     | diffusive term is formulated so that isopycnal mixing and|  C     | divergence of a flux form for the diffusive term. The    
38  C     | GM-style subgrid-scale terms can be incorporated b simply|  C     | diffusive term is formulated so that isopycnal mixing and
39  C     | setting the diffusion tensor terms appropriately.        |  C     | GM-style subgrid-scale terms can be incorporated b simply
40  C     \==========================================================/  C     | setting the diffusion tensor terms appropriately.        
41        IMPLICIT NONE  C     *==========================================================*
42    C     \ev
43    
44    C     !USES:
45          IMPLICIT NONE
46  C     == GLobal variables ==  C     == GLobal variables ==
47  #include "SIZE.h"  #include "SIZE.h"
48  #include "DYNVARS.h"  #include "DYNVARS.h"
49  #include "EEPARAMS.h"  #include "EEPARAMS.h"
50  #include "PARAMS.h"  #include "PARAMS.h"
51    #ifdef ALLOW_GENERIC_ADVDIFF
52  #include "GAD.h"  #include "GAD.h"
53    #endif
54    
55    C     !INPUT/OUTPUT PARAMETERS:
56  C     == Routine arguments ==  C     == Routine arguments ==
57  C     fVerS   - Flux of salt (S) in the vertical  C     fVerS   :: Flux of salt (S) in the vertical
58  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.
59  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  :: Land mask used to denote base of the domain.
60  C     xA      - Tracer cell face area normal to X  C     xA      :: Tracer cell face area normal to X
61  C     yA      - Tracer cell face area normal to X  C     yA      :: Tracer cell face area normal to X
62  C     uTrans  - Zonal volume transport through cell face  C     uTrans  :: Zonal volume transport through cell face
63  C     vTrans  - Meridional volume transport through cell face  C     vTrans  :: Meridional volume transport through cell face
64  C     rTrans  - Vertical volume transport through cell face  C     rTrans  ::   Vertical volume transport at interface k
65  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     rTransKp1 :: Vertical volume transport at inteface k+1
66    C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation
67  C                                      results will be set.  C                                      results will be set.
68  C     myThid - Instance number for this innvocation of CALC_GT  C     myThid :: Instance number for this innvocation of CALC_GT
69        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
70        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
79        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
80        _RL     myTime        _RL     myTime
81        INTEGER myIter        INTEGER myIter
82        INTEGER myThid        INTEGER myThid
83    
84  C     == Local variables ==  CEOP
85    
86    #ifdef ALLOW_GENERIC_ADVDIFF
87    C     === Local variables ===
88          LOGICAL calcAdvection
89          INTEGER iterNb
90    #ifdef ALLOW_ADAMSBASHFORTH_3
91          INTEGER m1, m2
92    #endif
93    
94  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
95  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
# Line 77  C--   the kDown is still required Line 97  C--   the kDown is still required
97        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
98  #endif  #endif
99    
100        CALL GAD_CALC_RHS(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
101    
102          calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
103          iterNb = myIter
104          IF (staggerTimeStep) iterNb = myIter - 1
105    
106    #ifdef ALLOW_ADAMSBASHFORTH_3
107          IF ( AdamsBashforth_S ) THEN
108            m1 = 1 + MOD(iterNb+1,2)
109            m2 = 1 + MOD( iterNb ,2)
110            CALL GAD_CALC_RHS(
111       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
112       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
113       I           diffKhS, diffK4S, KappaRS, Salt,       I           uVel, vVel, wVel,
114       I           GAD_SALINITY, saltAdvScheme,       I           diffKhS, diffK4S, KappaRS,
115         I           gsNm(1-Olx,1-Oly,1,1,1,m2), salt,
116         I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
117         I           calcAdvection, saltImplVertAdv,
118       U           fVerS, gS,       U           fVerS, gS,
119       I           myThid )       I           myTime, myIter, myThid )
120          ELSE
121    #endif /* ALLOW_ADAMSBASHFORTH_3 */
122            CALL GAD_CALC_RHS(
123         I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
124         I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
125         I           uVel, vVel, wVel,
126         I           diffKhS, diffK4S, KappaRS, salt, salt,
127         I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
128         I           calcAdvection, saltImplVertAdv,
129         U           fVerS, gS,
130         I           myTime, myIter, myThid )
131    #ifdef ALLOW_ADAMSBASHFORTH_3
132          ENDIF
133    #endif
134    
135  C--   External forcing term(s)  C--   External salinity forcing term(s) inside Adams-Bashforth:
136        CALL EXTERNAL_FORCING_S(        IF ( saltForcing .AND. forcing_In_AB )
137         & CALL EXTERNAL_FORCING_S(
138       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
139       I     myTime,myThid)       I     myTime,myThid)
140    
141        IF ( saltAdvScheme.EQ.ENUM_CENTERED_2ND        IF ( AdamsBashforthGs ) THEN
142       & .OR.saltAdvScheme.EQ.ENUM_UPWIND_3RD  #ifdef ALLOW_ADAMSBASHFORTH_3
143       & .OR.saltAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN          CALL ADAMS_BASHFORTH3(
144         I                        bi, bj, k,
145         U                        gS, gsNm,
146         I                        saltStartAB, iterNb, myThid )
147    #else
148          CALL ADAMS_BASHFORTH2(          CALL ADAMS_BASHFORTH2(
149       I                        bi, bj, K,       I                        bi, bj, k,
150       U                        gS, gSnm1,       U                        gS, gsNm1,
151       I                        myIter, myThid )       I                        iterNb, myThid )
152    #endif
153        ENDIF        ENDIF
154    
155    C--   External salinity forcing term(s) outside Adams-Bashforth:
156          IF ( saltForcing .AND. .NOT.forcing_In_AB )
157         & CALL EXTERNAL_FORCING_S(
158         I     iMin,iMax,jMin,jMax,bi,bj,k,
159         I     myTime,myThid)
160    
161  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
162        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
163          CALL FREESURF_RESCALE_G(          CALL FREESURF_RESCALE_G(
164       I                          bi, bj, K,       I                          bi, bj, k,
165       U                          gS,       U                          gS,
166       I                          myThid )       I                          myThid )
167            IF ( AdamsBashforthGs ) THEN
168    #ifdef ALLOW_ADAMSBASHFORTH_3
169            CALL FREESURF_RESCALE_G(
170         I                          bi, bj, k,
171         U                          gsNm(1-OLx,1-OLy,1,1,1,1),
172         I                          myThid )
173            CALL FREESURF_RESCALE_G(
174         I                          bi, bj, k,
175         U                          gsNm(1-OLx,1-OLy,1,1,1,2),
176         I                          myThid )
177    #else
178            CALL FREESURF_RESCALE_G(
179         I                          bi, bj, k,
180         U                          gsNm1,
181         I                          myThid )
182    #endif
183            ENDIF
184        ENDIF        ENDIF
185  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
186    
187    #endif /* ALLOW_GENERIC_ADVDIFF */
188    
189        RETURN        RETURN
190        END        END

Legend:
Removed from v.1.31  
changed lines
  Added in v.1.41

  ViewVC Help
Powered by ViewVC 1.1.22