/[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.37 by jmc, Fri Sep 24 16:58:17 2004 UTC revision 1.50 by heimbach, Fri Feb 13 21:56:48 2009 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  CBOP
8  C     !ROUTINE: CALC_GS  C     !ROUTINE: CALC_GS
9  C     !INTERFACE:  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,rTransKp1,maskUp,       I           xA, yA, maskUp, uFld, vFld, wFld,
13         I           uTrans, vTrans, rTrans, rTransKp1,
14       I           KappaRS,       I           KappaRS,
15       U           fVerS,       U           fVerS,
16       I           myTime,myIter,myThid )       I           myTime,myIter,myThid )
17  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
18  C     *==========================================================*  C     *==========================================================*
19  C     | SUBROUTINE CALC_GS                                          C     | SUBROUTINE CALC_GS
20  C     | o Calculate the salt tendency terms.                        C     | o Calculate the salt tendency terms.
21  C     *==========================================================*  C     *==========================================================*
22  C     | A procedure called EXTERNAL_FORCING_S is called from        C     | A procedure called EXTERNAL_FORCING_S is called from
23  C     | here. These procedures can be used to add per problem      C     | here. These procedures can be used to add per problem
24  C     | E-P  flux source terms.                                    C     | E-P  flux source terms.
25  C     | Note: Although it is slightly counter-intuitive the        C     | Note: Although it is slightly counter-intuitive the
26  C     |       EXTERNAL_FORCING routine is not the place to put      C     |       EXTERNAL_FORCING routine is not the place to put
27  C     |       file I/O. Instead files that are required to          C     |       file I/O. Instead files that are required to
28  C     |       calculate the external source terms are generally    C     |       calculate the external source terms are generally
29  C     |       read during the model main loop. This makes the      C     |       read during the model main loop. This makes the
30  C     |       logisitics of multi-processing simpler and also      C     |       logisitics of multi-processing simpler and also
31  C     |       makes the adjoint generation simpler. It also        C     |       makes the adjoint generation simpler. It also
32  C     |       allows for I/O to overlap computation where that      C     |       allows for I/O to overlap computation where that
33  C     |       is supported by hardware.                            C     |       is supported by hardware.
34  C     | Aside from the problem specific term the code here          C     | Aside from the problem specific term the code here
35  C     | forms the tendency terms due to advection and mixing        C     | forms the tendency terms due to advection and mixing
36  C     | The baseline implementation here uses a centered            C     | The baseline implementation here uses a centered
37  C     | difference form for the advection term and a tensorial      C     | difference form for the advection term and a tensorial
38  C     | divergence of a flux form for the diffusive term. The      C     | divergence of a flux form for the diffusive term. The
39  C     | diffusive term is formulated so that isopycnal mixing and  C     | diffusive term is formulated so that isopycnal mixing and
40  C     | GM-style subgrid-scale terms can be incorporated b simply  C     | GM-style subgrid-scale terms can be incorporated b simply
41  C     | setting the diffusion tensor terms appropriately.          C     | setting the diffusion tensor terms appropriately.
42  C     *==========================================================*  C     *==========================================================*
43  C     \ev  C     \ev
44    
# Line 47  C     == GLobal variables == Line 49  C     == GLobal variables ==
49  #include "DYNVARS.h"  #include "DYNVARS.h"
50  #include "EEPARAMS.h"  #include "EEPARAMS.h"
51  #include "PARAMS.h"  #include "PARAMS.h"
52    #include "RESTART.h"
53    #ifdef ALLOW_GENERIC_ADVDIFF
54  #include "GAD.h"  #include "GAD.h"
55    #endif
56    #ifdef ALLOW_AUTODIFF_TAMC
57    # include "tamc.h"
58    # include "tamc_keys.h"
59    #endif
60    
61  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
62  C     == Routine arguments ==  C     == Routine arguments ==
63  C     fVerS   :: Flux of salt (S) in the vertical  C     bi, bj,   :: tile indices
64  C               direction at the upper(U) and lower(D) faces of a cell.  C     iMin,iMax, jMin,jMax :: Range of points for which calculation
65  C     maskUp  :: Land mask used to denote base of the domain.  C                                       results will be set.
66  C     xA      :: Tracer cell face area normal to X  C     k         :: vertical index
67  C     yA      :: Tracer cell face area normal to X  C     kM1       :: =k-1 for k>1, =1 for k=1
68  C     uTrans  :: Zonal volume transport through cell face  C     kUp       :: index into 2 1/2D array, toggles between 1|2
69  C     vTrans  :: Meridional volume transport through cell face  C     kDown     :: index into 2 1/2D array, toggles between 2|1
70  C     rTrans  ::   Vertical volume transport at interface k  C     xA        :: Tracer cell face area normal to X
71    C     yA        :: Tracer cell face area normal to X
72    C     maskUp    :: Land mask used to denote base of the domain.
73    C     uFld,vFld :: Local copy of horizontal velocity field
74    C     wFld      :: Local copy of vertical velocity field
75    C     uTrans    :: Zonal volume transport through cell face
76    C     vTrans    :: Meridional volume transport through cell face
77    C     rTrans    ::   Vertical volume transport at interface k
78  C     rTransKp1 :: Vertical volume transport at inteface k+1  C     rTransKp1 :: Vertical volume transport at inteface k+1
79  C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation  C     KappaRS   :: Vertical diffusion for Salinity
80  C                                      results will be set.  C     fVerS     :: Flux of salt (S) in the vertical direction
81  C     myThid :: Instance number for this innvocation of CALC_GT  C                  at the upper(U) and lower(D) faces of a cell.
82        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  C     myTime    :: current time
83        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C     myIter    :: current iteration number
84        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  C     myThid    :: my Thread Id. number
85        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       INTEGER k,kUp,kDown,kM1  
86        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
87          INTEGER k,kUp,kDown,kM1
88          _RS xA     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89          _RS yA     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90          _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91          _RL uFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92          _RL vFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93          _RL wFld   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94          _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95          _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96          _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98          _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99          _RL fVerS  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
100        _RL     myTime        _RL     myTime
101        INTEGER myIter        INTEGER myIter
102        INTEGER myThid        INTEGER myThid
   
103  CEOP  CEOP
104    
105    #ifdef ALLOW_GENERIC_ADVDIFF
106  C     === Local variables ===  C     === Local variables ===
107        LOGICAL calcAdvection        LOGICAL calcAdvection
108          INTEGER iterNb
109    #ifdef ALLOW_ADAMSBASHFORTH_3
110          INTEGER m1, m2
111    #endif
112    
113    #ifdef ALLOW_AUTODIFF_TAMC
114              act1 = bi - myBxLo(myThid)
115              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
116              act2 = bj - myByLo(myThid)
117              max2 = myByHi(myThid) - myByLo(myThid) + 1
118              act3 = myThid - 1
119              max3 = nTx*nTy
120              act4 = ikey_dynamics - 1
121              itdkey = (act1 + 1) + act2*max1
122         &                      + act3*max1*max2
123         &                      + act4*max1*max2*max3
124              kkey = (itdkey-1)*Nr + k
125    #endif /* ALLOW_AUTODIFF_TAMC */
126    
127  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
128  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
129  C--   the kDown is still required  C--   the kDown is still required
130        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
131    # ifdef NONLIN_FRSURF
132    CADJ STORE fVerS(:,:,:) =
133    CADJ &     comlev1_bibj_k, key=kkey, byte=isbyte,
134    CADJ &     kind = isbyte
135    CADJ STORE gsNm1(:,:,k,bi,bj) =
136    CADJ &     comlev1_bibj_k, key=kkey, byte=isbyte,
137    CADJ &     kind = isbyte
138    # endif
139  #endif  #endif
140    
141    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142    
143        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
144        CALL GAD_CALC_RHS(        iterNb = myIter
145          IF (staggerTimeStep) iterNb = myIter - 1
146    
147    #ifdef ALLOW_ADAMSBASHFORTH_3
148            m1 = 1 + MOD(iterNb+1,2)
149            m2 = 1 + MOD( iterNb ,2)
150            CALL GAD_CALC_RHS(
151       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
152       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,       I           xA, yA, maskUp, uFld, vFld, wFld,
153       I           uVel, vVel, wVel,       I           uTrans, vTrans, rTrans, rTransKp1,
154       I           diffKhS, diffK4S, KappaRS, Salt,       I           diffKhS, diffK4S, KappaRS,
155         I           gsNm(1-Olx,1-Oly,1,1,1,m2), salt,
156       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
157       I           calcAdvection, saltImplVertAdv,       I           calcAdvection, saltImplVertAdv, AdamsBashforth_S,
158         I           useGMRedi, useKPP,
159       U           fVerS, gS,       U           fVerS, gS,
160       I           myTime, myIter, myThid )       I           myTime, myIter, myThid )
161    #else /* ALLOW_ADAMSBASHFORTH_3 */
162            CALL GAD_CALC_RHS(
163         I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
164         I           xA, yA, maskUp, uFld, vFld, wFld,
165         I           uTrans, vTrans, rTrans, rTransKp1,
166         I           diffKhS, diffK4S, KappaRS, gsNm1, salt,
167         I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
168         I           calcAdvection, saltImplVertAdv, AdamsBashforth_S,
169         I           useGMRedi, useKPP,
170         U           fVerS, gS,
171         I           myTime, myIter, myThid )
172    #endif /* ALLOW_ADAMSBASHFORTH_3 */
173    
174  C--   External salinity forcing term(s) inside Adams-Bashforth:  C--   External salinity forcing term(s) inside Adams-Bashforth:
175        IF ( saltForcing .AND. forcing_In_AB )        IF ( saltForcing .AND. tracForcingOutAB.NE.1 )
176       & CALL EXTERNAL_FORCING_S(       & CALL EXTERNAL_FORCING_S(
177       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
178       I     myTime,myThid)       I     myTime,myThid)
179    
180        IF ( saltAdamsBashforth ) THEN        IF ( AdamsBashforthGs ) THEN
181    #ifdef ALLOW_ADAMSBASHFORTH_3
182            CALL ADAMS_BASHFORTH3(
183         I                        bi, bj, k,
184         U                        gS, gsNm,
185         I                        saltStartAB, iterNb, myThid )
186    #else
187          CALL ADAMS_BASHFORTH2(          CALL ADAMS_BASHFORTH2(
188       I                        bi, bj, K,       I                        bi, bj, k,
189       U                        gS, gSnm1,       U                        gS, gsNm1,
190       I                        myIter, myThid )       I                        saltStartAB, iterNb, myThid )
191    #endif
192        ENDIF        ENDIF
193    
194  C--   External salinity forcing term(s) outside Adams-Bashforth:  C--   External salinity forcing term(s) outside Adams-Bashforth:
195        IF ( saltForcing .AND. .NOT.forcing_In_AB )        IF ( saltForcing .AND. tracForcingOutAB.EQ.1 )
196       & CALL EXTERNAL_FORCING_S(       & CALL EXTERNAL_FORCING_S(
197       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
198       I     myTime,myThid)       I     myTime,myThid)
# Line 122  C--   External salinity forcing term(s) Line 200  C--   External salinity forcing term(s)
200  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
201        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
202          CALL FREESURF_RESCALE_G(          CALL FREESURF_RESCALE_G(
203       I                          bi, bj, K,       I                          bi, bj, k,
204       U                          gS,       U                          gS,
205       I                          myThid )       I                          myThid )
206          IF ( saltAdamsBashforth )          IF ( AdamsBashforthGs ) THEN
207       &  CALL FREESURF_RESCALE_G(  #ifdef ALLOW_ADAMSBASHFORTH_3
208       I                          bi, bj, K,          CALL FREESURF_RESCALE_G(
209       U                          gSnm1,       I                          bi, bj, k,
210         U                          gsNm(1-OLx,1-OLy,1,1,1,1),
211       I                          myThid )       I                          myThid )
212            CALL FREESURF_RESCALE_G(
213         I                          bi, bj, k,
214         U                          gsNm(1-OLx,1-OLy,1,1,1,2),
215         I                          myThid )
216    #else
217            CALL FREESURF_RESCALE_G(
218         I                          bi, bj, k,
219         U                          gsNm1,
220         I                          myThid )
221    #endif
222            ENDIF
223        ENDIF        ENDIF
224  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
225    
226    #endif /* ALLOW_GENERIC_ADVDIFF */
227    
228        RETURN        RETURN
229        END        END

Legend:
Removed from v.1.37  
changed lines
  Added in v.1.50

  ViewVC Help
Powered by ViewVC 1.1.22