/[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.2 by cnh, Fri Apr 24 02:05:40 1998 UTC revision 1.40 by jmc, Fri Apr 15 14:18:50 2005 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,wTrans,maskup,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
13       U           af,df,fZon,fMer, fVerS,       I           KappaRS,
14       I           myThid )       U           fVerS,
15  C     /==========================================================\       I           myTime,myIter,myThid )
16  C     | SUBROUTINE CALC_GS                                       |  C     !DESCRIPTION: \bv
17  C     | o Calculate the salinity tendency terms.                 |  C     *==========================================================*
18  C     |==========================================================|  C     | SUBROUTINE CALC_GS                                        
19  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     | o Calculate the salt tendency terms.                      
20  C     | here. These procedures can be used to add per problem    |  C     *==========================================================*
21  C     | fresh water flux source terms.                           |  C     | A procedure called EXTERNAL_FORCING_S is called from      
22  C     | Note: Although it is slightly counter-intuitive the      |  C     | here. These procedures can be used to add per problem    
23  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     | E-P  flux source terms.                                  
24  C     |       file I/O. Instead files that are required to       |  C     | Note: Although it is slightly counter-intuitive the      
25  C     |       calculate the external source terms are generally  |  C     |       EXTERNAL_FORCING routine is not the place to put    
26  C     |       read during the model main loop. This makes the    |  C     |       file I/O. Instead files that are required to        
27  C     |       logisitics of multi-processing simpler and also    |  C     |       calculate the external source terms are generally  
28  C     |       makes the adjoint generation simpler. It also      |  C     |       read during the model main loop. This makes the    
29  C     |       allows for I/O to overlap computation where that   |  C     |       logisitics of multi-processing simpler and also    
30  C     |       is supported by hardware.                          |  C     |       makes the adjoint generation simpler. It also      
31  C     | Aside from the problem specific term the code here       |  C     |       allows for I/O to overlap computation where that    
32  C     | forms the tendency terms due to advection and mixing     |  C     |       is supported by hardware.                          
33  C     | The baseline implementation here uses a centered         |  C     | Aside from the problem specific term the code here        
34  C     | difference form for the advection term and a tensorial   |  C     | forms the tendency terms due to advection and mixing      
35  C     | divergence of a flux form for the diffusive term. The    |  C     | The baseline implementation here uses a centered          
36  C     | diffusive term is formulated so that isopycnal mixing and|  C     | difference form for the advection term and a tensorial    
37  C     | GM-style subgrid-scale terms can be incorporated b simply|  C     | divergence of a flux form for the diffusive term. The    
38  C     | setting the diffusion tensor terms appropriately.        |  C     | diffusive term is formulated so that isopycnal mixing and
39  C     \==========================================================/  C     | GM-style subgrid-scale terms can be incorporated b simply
40        IMPLICIT NONE  C     | setting the diffusion tensor terms appropriately.        
41    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"  #include "PACKAGES_CONFIG.h"
52    #ifdef ALLOW_GENERIC_ADVDIFF
53    #include "GAD.h"
54    #endif
55    
56    C     !INPUT/OUTPUT PARAMETERS:
57  C     == Routine arguments ==  C     == Routine arguments ==
58  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 salinity (S) in the vertical  
59  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.
60  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  :: Land mask used to denote base of the domain.
61  C     xA      - Tracer cell face area normal to X  C     xA      :: Tracer cell face area normal to X
62  C     yA      - Tracer cell face area normal to X  C     yA      :: Tracer cell face area normal to X
63  C     uTrans  - Zonal volume transport through cell face  C     uTrans  :: Zonal volume transport through cell face
64  C     vTrans  - Meridional volume transport through cell face  C     vTrans  :: Meridional volume transport through cell face
65  C     wTrans  - Vertical volume transport through cell face  C     rTrans  ::   Vertical volume transport at interface k
66  C     af      - Advective flux component work array  C     rTransKp1 :: Vertical volume transport at inteface k+1
67  C     df      - Diffusive flux component work array  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  
68  C                                      results will be set.  C                                      results will be set.
69  C     myThid - Instance number for this innvocation of CALC_GS  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)  
70        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
71        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        INTEGER k,kUp,kDown,kM1
       INTEGER kUp,kDown,kM1  
80        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
81          _RL     myTime
82          INTEGER myIter
83        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
84    
85  C     == Local variables ==  CEOP
86  C     I, J, K - Loop counters  
87        INTEGER i,j,k  #ifdef ALLOW_GENERIC_ADVDIFF
88        INTEGER afFacS, dfFacS  C     === Local variables ===
89          LOGICAL calcAdvection
90        afFacS = 1. _d 0        INTEGER iterNb
91        dfFacS = 1. _d 0  
92    #ifdef ALLOW_AUTODIFF_TAMC
93  C---  C--   only the kUp part of fverS is set in this subroutine
94  C---  Calculate advective and diffusive fluxes between cells.  C--   the kDown is still required
95  C---        fVerS(1,1,kDown) = fVerS(1,1,kDown)
96    #endif
97  C--   Zonal flux (fZon is at west face of "salt" cell)  
98  C     Advective component of zonal flux        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
99        DO j=jMin,jMax        CALL GAD_CALC_RHS(
100         DO i=iMin,iMax       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
101          af(i,j) =       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
102       &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0       I           uVel, vVel, wVel,
103         ENDDO       I           diffKhS, diffK4S, KappaRS, Salt,
104        ENDDO       I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
105  C     Diffusive component of zonal flux       I           calcAdvection, saltImplVertAdv,
106        DO j=jMin,jMax       U           fVerS, gS,
107         DO i=iMin,iMax       I           myTime, myIter, myThid )
108          df(i,j) =  
109       &   -diffKhS*xA(i,j)*rdxC(i,j,bi,bj)  C--   External salinity forcing term(s) inside Adams-Bashforth:
110       &   *(salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))        IF ( saltForcing .AND. forcing_In_AB )
111         ENDDO       & CALL EXTERNAL_FORCING_S(
112        ENDDO       I     iMin,iMax,jMin,jMax,bi,bj,k,
113  C     Net zonal flux       I     myTime,myThid)
114        DO j=jMin,jMax  
115         DO i=iMin,iMax        IF ( saltAdamsBashforth ) THEN
116          fZon(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)          iterNb = myIter
117         ENDDO          IF (staggerTimeStep) iterNb = myIter - 1
118        ENDDO  #ifdef ALLOW_ADAMSBASHFORTH_3
119            CALL ADAMS_BASHFORTH3(
120  C--   Meridional flux (fMer is at south face of "salt" cell)       I                        bi, bj, k,
121  C     Advective component of meridional flux       U                        gS, gsNm,
122        DO j=jMin,jMax       I                        iterNb, myThid )
123         DO i=iMin,iMax  #else
124  C       Advective component of meridional flux          CALL ADAMS_BASHFORTH2(
125          af(i,j) =       I                        bi, bj, k,
126       &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0       U                        gS, gsNm1,
127         ENDDO       I                        iterNb, myThid )
128        ENDDO  #endif
129  C     Diffusive component of meridional flux        ENDIF
130        DO j=jMin,jMax  
131         DO i=iMin,iMax  C--   External salinity forcing term(s) outside Adams-Bashforth:
132          df(i,j) =        IF ( saltForcing .AND. .NOT.forcing_In_AB )
133       &   -diffKhS*yA(i,j)*rdyC(i,j,bi,bj)       & CALL EXTERNAL_FORCING_S(
134       &   *(salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))       I     iMin,iMax,jMin,jMax,bi,bj,k,
135         ENDDO       I     myTime,myThid)
136        ENDDO  
137  C     Net meridional flux  #ifdef NONLIN_FRSURF
138        DO j=jMin,jMax        IF (nonlinFreeSurf.GT.0) THEN
139         DO i=iMin,iMax          CALL FREESURF_RESCALE_G(
140          fMer(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)       I                          bi, bj, k,
141         ENDDO       U                          gS,
142        ENDDO       I                          myThid )
143            IF ( saltAdamsBashforth ) THEN
144  C--   Vertical flux (fVerS) above  #ifdef ALLOW_ADAMSBASHFORTH_3
145  C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper          CALL FREESURF_RESCALE_G(
146  C           boundary condition.       I                          bi, bj, k,
147  C     Advective component of vertical flux       U                          gsNm(1-OLx,1-OLy,1,1,1,1),
148        DO j=jMin,jMax       I                          myThid )
149         DO i=iMin,iMax          CALL FREESURF_RESCALE_G(
150          af(i,j) =       I                          bi, bj, k,
151       &   wTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0       U                          gsNm(1-OLx,1-OLy,1,1,1,2),
152         ENDDO       I                          myThid )
153        ENDDO  #else
154  C     Diffusive component of vertical flux          CALL FREESURF_RESCALE_G(
155        DO j=jMin,jMax       I                          bi, bj, k,
156         DO i=iMin,iMax       U                          gsNm1,
157          df(i,j) =       I                          myThid )
158       &   -diffKzS*zA(i,j,bi,bj)*rdzC(k)  #endif
159       &   *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))          ENDIF
160         ENDDO        ENDIF
161        ENDDO  #endif /* NONLIN_FRSURF */
 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  
         gS(i,j,k,bi,bj)=  
      &   -rHFacC(i,j,k,bi,bj)*rdzF(k)*rDxF(i,j,bi,bj)*rDyF(i,j,bi,bj)  
      &   *(  
      &    +( fZon(i+1,j)-fZon(i,j) )  
      &    +( fMer(i,j+1)-fMer(i,j) )  
      &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )  
      &    )  
        ENDDO  
       ENDDO  
162    
163  C--   External haline forcing term(s)  #endif /* ALLOW_GENERIC_ADVDIFF */
164    
165        RETURN        RETURN
166        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22