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

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.48

  ViewVC Help
Powered by ViewVC 1.1.22