/[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.14 by cnh, Sat Aug 22 17:51:07 1998 UTC revision 1.43 by jmc, Sun Feb 26 01:57:24 2006 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "PACKAGES_CONFIG.h"
5    #include "CPP_OPTIONS.h"
6    
7  CStartOfInterFace  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,maskC,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
13       I           K13,K23,KappaRS,KapGM,       I           KappaRS,
14       U           af,df,fZon,fMer,fVerS,       U           fVerS,
15       I           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  #include "GRID.h"  #ifdef ALLOW_GENERIC_ADVDIFF
52  #include "FFIELDS.h"  #include "GAD.h"
53    #endif
54    #ifdef ALLOW_AUTODIFF_TAMC
55    # include "tamc.h"
56    # include "tamc_keys.h"
57    #endif
58    
59    C     !INPUT/OUTPUT PARAMETERS:
60  C     == Routine arguments ==  C     == Routine arguments ==
61  C     fZon    - Work array for flux of temperature in the east-west  C     fVerS   :: Flux of salt (S) in the vertical
 C               direction at the west face of a cell.  
 C     fMer    - Work array for flux of temperature in the north-south  
 C               direction at the south face of a cell.  
 C     fVerS   - Flux of salt (S) in the vertical  
62  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.
63  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  :: Land mask used to denote base of the domain.
64  C     maskC   - Land mask for salt cells (used in TOP_LAYER only)  C     xA      :: Tracer cell face area normal to X
65  C     xA      - Tracer cell face area normal to X  C     yA      :: Tracer cell face area normal to X
66  C     yA      - Tracer cell face area normal to X  C     uTrans  :: Zonal volume transport through cell face
67  C     uTrans  - Zonal volume transport through cell face  C     vTrans  :: Meridional volume transport through cell face
68  C     vTrans  - Meridional volume transport through cell face  C     rTrans  ::   Vertical volume transport at interface k
69  C     wTrans  - Vertical volume transport through cell face  C     rTransKp1 :: Vertical volume transport at inteface k+1
70  C     af      - Advective flux component work array  C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation
 C     df      - Diffusive flux component work array  
 C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  
71  C                                      results will be set.  C                                      results will be set.
72  C     myThid - Instance number for this innvocation of CALC_GT  C     myThid :: Instance number for this innvocation of CALC_GT
       _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
73        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
74        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL KapGM (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)  
82        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
83        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
84          _RL     myTime
85          INTEGER myIter
86        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
87    
88  C     == Local variables ==  CEOP
89  C     I, J, K - Loop counters  
90        INTEGER i,j  #ifdef ALLOW_GENERIC_ADVDIFF
91        LOGICAL TOP_LAYER  C     === Local variables ===
92        _RL afFacS, dfFacS        LOGICAL calcAdvection
93        _RL dSdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        INTEGER iterNb
94        _RL dSdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  #ifdef ALLOW_ADAMSBASHFORTH_3
95          INTEGER m1, m2
96        afFacS = 1. _d 0  #endif
97        dfFacS = 1. _d 0  
98        TOP_LAYER = K .EQ. 1  #ifdef ALLOW_AUTODIFF_TAMC
99              act1 = bi - myBxLo(myThid)
100  C---  Calculate advective and diffusive fluxes between cells.            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
101              act2 = bj - myByLo(myThid)
102  C--   Zonal flux (fZon is at west face of "salt" cell)            max2 = myByHi(myThid) - myByLo(myThid) + 1
103  C     Advective component of zonal flux            act3 = myThid - 1
104        DO j=jMin,jMax            max3 = nTx*nTy
105         DO i=iMin,iMax            act4 = ikey_dynamics - 1
106          af(i,j) =            itdkey = (act1 + 1) + act2*max1
107       &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0       &                      + act3*max1*max2
108         ENDDO       &                      + act4*max1*max2*max3
109        ENDDO            kkey = (itdkey-1)*Nr + k
110  C     Zonal tracer gradient  #endif /* ALLOW_AUTODIFF_TAMC */
111        DO j=jMin,jMax  
112         DO i=iMin,iMax  #ifdef ALLOW_AUTODIFF_TAMC
113          dSdx(i,j) = _recip_dxC(i,j,bi,bj)*  C--   only the kUp part of fverS is set in this subroutine
114       &  (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))  C--   the kDown is still required
115         ENDDO        fVerS(1,1,kDown) = fVerS(1,1,kDown)
116        ENDDO  # ifdef NONLIN_FRSURF
117  C     Diffusive component of zonal flux  CADJ STORE fVerS(:,:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
118        DO j=jMin,jMax  # endif
119         DO i=iMin,iMax  #endif
120          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i-1,j)))*  
121       &            xA(i,j)*dSdx(i,j)  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122         ENDDO  
123        ENDDO        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
124  C     Net zonal flux        iterNb = myIter
125        DO j=jMin,jMax        IF (staggerTimeStep) iterNb = myIter - 1
126         DO i=iMin,iMax  
127          fZon(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  #ifdef ALLOW_ADAMSBASHFORTH_3
128         ENDDO        IF ( AdamsBashforth_S ) THEN
129        ENDDO          m1 = 1 + MOD(iterNb+1,2)
130            m2 = 1 + MOD( iterNb ,2)
131  C--   Meridional flux (fMer is at south face of "salt" cell)          CALL GAD_CALC_RHS(
132  C     Advective component of meridional flux       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
133        DO j=jMin,jMax       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
134         DO i=iMin,iMax       I           uVel, vVel, wVel,
135  C       Advective component of meridional flux       I           diffKhS, diffK4S, KappaRS,
136          af(i,j) =       I           gsNm(1-Olx,1-Oly,1,1,1,m2), salt,
137       &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
138         ENDDO       I           calcAdvection, saltImplVertAdv,
139        ENDDO       U           fVerS, gS,
140  C     Zonal tracer gradient       I           myTime, myIter, myThid )
141        DO j=jMin,jMax        ELSE
142         DO i=iMin,iMax          CALL GAD_CALC_RHS(
143          dSdy(i,j) = _recip_dyC(i,j,bi,bj)*       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
144       &  (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
145         ENDDO       I           uVel, vVel, wVel,
146        ENDDO       I           diffKhS, diffK4S, KappaRS, salt, salt,
147  C     Diffusive component of meridional flux       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
148        DO j=jMin,jMax       I           calcAdvection, saltImplVertAdv,
149         DO i=iMin,iMax       U           fVerS, gS,
150          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i,j-1)))*       I           myTime, myIter, myThid )
      &            yA(i,j)*dSdy(i,j)  
        ENDDO  
       ENDDO  
 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--   Interpolate terms for Redi/GM scheme  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dSdx(i,j) = 0.5*(  
      &   +0.5*(_maskW(i+1,j,k,bi,bj)*_recip_dxC(i+1,j,bi,bj)*  
      &           (salt(i+1,j,k,bi,bj)-salt(i,j,k,bi,bj))  
      &        +_maskW(i,j,k,bi,bj)*_recip_dxC(i,j,bi,bj)*  
      &           (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj)))  
      &   +0.5*(_maskW(i+1,j,km1,bi,bj)*_recip_dxC(i+1,j,bi,bj)*  
      &           (salt(i+1,j,km1,bi,bj)-salt(i,j,km1,bi,bj))  
      &        +_maskW(i,j,km1,bi,bj)*_recip_dxC(i,j,bi,bj)*  
      &           (salt(i,j,km1,bi,bj)-salt(i-1,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         dSdy(i,j) = 0.5*(  
      &   +0.5*(_maskS(i,j,k,bi,bj)*_recip_dyC(i,j,bi,bj)*  
      &           (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
      &        +_maskS(i,j+1,k,bi,bj)*_recip_dyC(i,j+1,bi,bj)*  
      &           (salt(i,j+1,k,bi,bj)-salt(i,j,k,bi,bj)))  
      &   +0.5*(_maskS(i,j,km1,bi,bj)*_recip_dyC(i,j,bi,bj)*  
      &           (salt(i,j,km1,bi,bj)-salt(i,j-1,km1,bi,bj))  
      &        +_maskS(i,j+1,km1,bi,bj)*_recip_dyC(i,j+1,bi,bj)*  
      &           (salt(i,j+1,km1,bi,bj)-salt(i,j,km1,bi,bj)))  
      &       )  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux (fVerS) above  
 C     Advective component of vertical flux  
 C     Note: For K=1 then KM1=1 this gives a barZ(T) = T  
 C     (this plays the role of the free-surface correction)  
       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  
 C     Diffusive component of vertical flux  
 C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper  
 C           boundary condition.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) = _rA(i,j,bi,bj)*(  
      &   -KapGM(i,j)*K13(i,j,k)*dSdx(i,j)  
      &   -KapGM(i,j)*K23(i,j,k)*dSdy(i,j)  
      &   )  
        ENDDO  
       ENDDO  
       IF (.NOT.implicitDiffusion) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          df(i,j) = 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  
151        ENDIF        ENDIF
152  C     Net vertical flux  #else /* ALLOW_ADAMSBASHFORTH_3 */
153        DO j=jMin,jMax          CALL GAD_CALC_RHS(
154         DO i=iMin,iMax       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
155          fVerS(i,j,kUp) = ( afFacS*af(i,j)+  dfFacS*df(i,j) )*maskUp(i,j)       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
156         ENDDO       I           uVel, vVel, wVel,
157        ENDDO       I           diffKhS, diffK4S, KappaRS, gsNm1, salt,
158        IF ( TOP_LAYER ) THEN       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
159         DO j=jMin,jMax       I           calcAdvection, saltImplVertAdv,
160          DO i=iMin,iMax       U           fVerS, gS,
161           fVerS(i,j,kUp) = afFacS*af(i,j)*freeSurfFac       I           myTime, myIter, myThid )
162          ENDDO  #endif /* ALLOW_ADAMSBASHFORTH_3 */
163         ENDDO  
164    C--   External salinity forcing term(s) inside Adams-Bashforth:
165          IF ( saltForcing .AND. forcing_In_AB )
166         & CALL EXTERNAL_FORCING_S(
167         I     iMin,iMax,jMin,jMax,bi,bj,k,
168         I     myTime,myThid)
169    
170          IF ( AdamsBashforthGs ) THEN
171    #ifdef ALLOW_ADAMSBASHFORTH_3
172            CALL ADAMS_BASHFORTH3(
173         I                        bi, bj, k,
174         U                        gS, gsNm,
175         I                        saltStartAB, iterNb, myThid )
176    #else
177            CALL ADAMS_BASHFORTH2(
178         I                        bi, bj, k,
179         U                        gS, gsNm1,
180         I                        iterNb, myThid )
181    #endif
182        ENDIF        ENDIF
183    
184  C--   Tendency is minus divergence of the fluxes.  C--   External salinity forcing term(s) outside Adams-Bashforth:
185  C     Note. Tendency terms will only be correct for range        IF ( saltForcing .AND. .NOT.forcing_In_AB )
186  C           i=iMin+1:iMax-1, j=jMin+1:jMax-1. Edge points       & CALL EXTERNAL_FORCING_S(
187  C           will contain valid floating point numbers but       I     iMin,iMax,jMin,jMax,bi,bj,k,
188  C           they are not algorithmically correct. These points       I     myTime,myThid)
189  C           are not used.  
190        DO j=jMin,jMax  #ifdef NONLIN_FRSURF
191         DO i=iMin,iMax        IF (nonlinFreeSurf.GT.0) THEN
192  #define _recip_VolS(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)/_rA(i,j,bi,bj)          CALL FREESURF_RESCALE_G(
193          gS(i,j,k,bi,bj)=       I                          bi, bj, k,
194       &   -_recip_VolS(i,j,k,bi,bj)       U                          gS,
195       &   *(       I                          myThid )
196       &    +( fZon(i+1,j)-fZon(i,j) )          IF ( AdamsBashforthGs ) THEN
197       &    +( fMer(i,j+1)-fMer(i,j) )  #ifdef ALLOW_ADAMSBASHFORTH_3
198       &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )*rkFac          CALL FREESURF_RESCALE_G(
199       &    )       I                          bi, bj, k,
200         ENDDO       U                          gsNm(1-OLx,1-OLy,1,1,1,1),
201        ENDDO       I                          myThid )
202            CALL FREESURF_RESCALE_G(
203  C--   External P-E forcing term(s)       I                          bi, bj, k,
204  C     o Surface relaxation term       U                          gsNm(1-OLx,1-OLy,1,1,1,2),
205        IF ( TOP_LAYER ) THEN       I                          myThid )
206         DO j=jMin,jMax  #else
207          DO i=iMin,iMax          CALL FREESURF_RESCALE_G(
208           gS(i,j,k,bi,bj)=gS(i,j,k,bi,bj)       I                          bi, bj, k,
209       &   +maskC(i,j)*(       U                          gsNm1,
210       &   -lambdaSaltClimRelax*(salt(i,j,k,bi,bj)-SSS(i,j,bi,bj))       I                          myThid )
211       &   +EmPmR(i,j,bi,bj) )  #endif
212          ENDDO          ENDIF
        ENDDO  
213        ENDIF        ENDIF
214    #endif /* NONLIN_FRSURF */
215    
216    #endif /* ALLOW_GENERIC_ADVDIFF */
217    
218        RETURN        RETURN
219        END        END

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.43

  ViewVC Help
Powered by ViewVC 1.1.22