/[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.16 by cnh, Tue Nov 3 15:28:04 1998 UTC
# Line 5  C $Header$ Line 5  C $Header$
5  CStartOfInterFace  CStartOfInterFace
6        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
7       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
8       I           xA,yA,uTrans,vTrans,wTrans,maskup,       I           xA,yA,uTrans,vTrans,rTrans,maskup,maskC,
9       U           af,df,fZon,fMer, fVerS,       I           K13,K23,KappaRS,KapGM,
10       I           myThid )       U           af,df,fZon,fMer,fVerS,
11         I           myCurrentTime, myThid )
12  C     /==========================================================\  C     /==========================================================\
13  C     | SUBROUTINE CALC_GS                                       |  C     | SUBROUTINE CALC_GS                                       |
14  C     | o Calculate the salinity tendency terms.                 |  C     | o Calculate the salt tendency terms.                     |
15  C     |==========================================================|  C     |==========================================================|
16  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     | A procedure called EXTERNAL_FORCING_S is called from     |
17  C     | here. These procedures can be used to add per problem    |  C     | here. These procedures can be used to add per problem    |
18  C     | fresh water flux source terms.                           |  C     | E-P  flux source terms.                                  |
19  C     | Note: Although it is slightly counter-intuitive the      |  C     | Note: Although it is slightly counter-intuitive the      |
20  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     |       EXTERNAL_FORCING routine is not the place to put   |
21  C     |       file I/O. Instead files that are required to       |  C     |       file I/O. Instead files that are required to       |
# Line 41  C     == GLobal variables == Line 42  C     == GLobal variables ==
42  #include "EEPARAMS.h"  #include "EEPARAMS.h"
43  #include "PARAMS.h"  #include "PARAMS.h"
44  #include "GRID.h"  #include "GRID.h"
45    #include "FFIELDS.h"
46    
47  C     == Routine arguments ==  C     == Routine arguments ==
48  C     fZon    - Work array for flux of temperature in the east-west  C     fZon    - Work array for flux of temperature in the east-west
49  C               direction at the west face of a cell.  C               direction at the west face of a cell.
50  C     fMer    - Work array for flux of temperature in the north-south  C     fMer    - Work array for flux of temperature in the north-south
51  C               direction at the south face of a cell.  C               direction at the south face of a cell.
52  C     fVerS   - Flux of salinity (S) in the vertical  C     fVerS   - Flux of salt (S) in the vertical
53  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.
54  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
55    C     maskC   - Land mask for salt cells (used in TOP_LAYER only)
56  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
57  C     yA      - Tracer cell face area normal to X  C     yA      - Tracer cell face area normal to X
58  C     uTrans  - Zonal volume transport through cell face  C     uTrans  - Zonal volume transport through cell face
# Line 59  C     af      - Advective flux component Line 62  C     af      - Advective flux component
62  C     df      - Diffusive flux component work array  C     df      - Diffusive flux component work array
63  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
64  C                                      results will be set.  C                                      results will be set.
65  C     myThid - Instance number for this innvocation of CALC_GS  C     myThid - Instance number for this innvocation of CALC_GT
66        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 67  C     myThid - Instance number for this Line 70  C     myThid - Instance number for this
70        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75          _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76          _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
77          _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
78          _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
79          _RL KapGM (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82        INTEGER kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
83        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
84        INTEGER myThid        INTEGER myThid
85          _RL     myCurrentTime
86  CEndOfInterface  CEndOfInterface
87    
88  C     == Local variables ==  C     == Local variables ==
89  C     I, J, K - Loop counters  C     I, J, K - Loop counters
90        INTEGER i,j,k        INTEGER i,j
91        INTEGER afFacS, dfFacS        LOGICAL TOP_LAYER
92          _RL afFacS, dfFacS
93          _RL dSdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94          _RL dSdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95    
96        afFacS = 1. _d 0        afFacS = 1. _d 0
97        dfFacS = 1. _d 0        dfFacS = 1. _d 0
98          TOP_LAYER = K .EQ. 1
99    
 C---  
100  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
 C---  
101    
102  C--   Zonal flux (fZon is at west face of "salt" cell)  C--   Zonal flux (fZon is at west face of "salt" cell)
103  C     Advective component of zonal flux  C     Advective component of zonal flux
# Line 96  C     Advective component of zonal flux Line 107  C     Advective component of zonal flux
107       &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0       &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0
108         ENDDO         ENDDO
109        ENDDO        ENDDO
110    C     Zonal tracer gradient
111          DO j=jMin,jMax
112           DO i=iMin,iMax
113            dSdx(i,j) = _recip_dxC(i,j,bi,bj)*
114         &  (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))
115           ENDDO
116          ENDDO
117  C     Diffusive component of zonal flux  C     Diffusive component of zonal flux
118        DO j=jMin,jMax        DO j=jMin,jMax
119         DO i=iMin,iMax         DO i=iMin,iMax
120          df(i,j) =          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i-1,j)))*
121       &   -diffKhS*xA(i,j)*_rdxC(i,j,bi,bj)       &            xA(i,j)*dSdx(i,j)
      &   *(salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))  
122         ENDDO         ENDDO
123        ENDDO        ENDDO
124  C     Net zonal flux  C     Net zonal flux
# Line 120  C       Advective component of meridiona Line 137  C       Advective component of meridiona
137       &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0       &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0
138         ENDDO         ENDDO
139        ENDDO        ENDDO
140    C     Zonal tracer gradient
141          DO j=jMin,jMax
142           DO i=iMin,iMax
143            dSdy(i,j) = _recip_dyC(i,j,bi,bj)*
144         &  (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))
145           ENDDO
146          ENDDO
147  C     Diffusive component of meridional flux  C     Diffusive component of meridional flux
148        DO j=jMin,jMax        DO j=jMin,jMax
149         DO i=iMin,iMax         DO i=iMin,iMax
150          df(i,j) =          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i,j-1)))*
151       &   -diffKhS*yA(i,j)*_rdyC(i,j,bi,bj)       &            yA(i,j)*dSdy(i,j)
      &   *(salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
152         ENDDO         ENDDO
153        ENDDO        ENDDO
154  C     Net meridional flux  C     Net meridional flux
# Line 135  C     Net meridional flux Line 158  C     Net meridional flux
158         ENDDO         ENDDO
159        ENDDO        ENDDO
160    
161    C--   Interpolate terms for Redi/GM scheme
162          DO j=jMin,jMax
163           DO i=iMin,iMax
164            dSdx(i,j) = 0.5*(
165         &   +0.5*(_maskW(i+1,j,k,bi,bj)
166         &         *_recip_dxC(i+1,j,bi,bj)*
167         &           (salt(i+1,j,k,bi,bj)-salt(i,j,k,bi,bj))
168         &        +_maskW(i,j,k,bi,bj)
169         &         *_recip_dxC(i,j,bi,bj)*
170         &           (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj)))
171         &   +0.5*(_maskW(i+1,j,km1,bi,bj)
172         &         *_recip_dxC(i+1,j,bi,bj)*
173         &           (salt(i+1,j,km1,bi,bj)-salt(i,j,km1,bi,bj))
174         &        +_maskW(i,j,km1,bi,bj)
175         &         *_recip_dxC(i,j,bi,bj)*
176         &           (salt(i,j,km1,bi,bj)-salt(i-1,j,km1,bi,bj)))
177         &       )
178           ENDDO
179          ENDDO
180          DO j=jMin,jMax
181           DO i=iMin,iMax
182            dSdy(i,j) = 0.5*(
183         &   +0.5*(_maskS(i,j,k,bi,bj)
184         &         *_recip_dyC(i,j,bi,bj)*
185         &           (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))
186         &        +_maskS(i,j+1,k,bi,bj)
187         &         *_recip_dyC(i,j+1,bi,bj)*
188         &           (salt(i,j+1,k,bi,bj)-salt(i,j,k,bi,bj)))
189         &   +0.5*(_maskS(i,j,km1,bi,bj)
190         &         *_recip_dyC(i,j,bi,bj)*
191         &           (salt(i,j,km1,bi,bj)-salt(i,j-1,km1,bi,bj))
192         &        +_maskS(i,j+1,km1,bi,bj)
193         &         *_recip_dyC(i,j+1,bi,bj)*
194         &           (salt(i,j+1,km1,bi,bj)-salt(i,j,km1,bi,bj)))
195         &       )
196           ENDDO
197          ENDDO
198    
199  C--   Vertical flux (fVerS) above  C--   Vertical flux (fVerS) above
 C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper  
 C           boundary condition.  
200  C     Advective component of vertical flux  C     Advective component of vertical flux
201    C     Note: For K=1 then KM1=1 this gives a barZ(T) = T
202    C     (this plays the role of the free-surface correction)
203        DO j=jMin,jMax        DO j=jMin,jMax
204         DO i=iMin,iMax         DO i=iMin,iMax
205          af(i,j) =          af(i,j) =
206       &   wTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0       &   rTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0
207         ENDDO         ENDDO
208        ENDDO        ENDDO
209  C     Diffusive component of vertical flux  C     Diffusive component of vertical flux
210    C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper
211    C           boundary condition.
212        DO j=jMin,jMax        DO j=jMin,jMax
213         DO i=iMin,iMax         DO i=iMin,iMax
214          df(i,j) =          df(i,j) = _rA(i,j,bi,bj)*(
215       &   -diffKzS*zA(i,j,bi,bj)*rdzC(k)       &   -KapGM(i,j)*K13(i,j,k)*dSdx(i,j)
216       &   *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))       &   -KapGM(i,j)*K23(i,j,k)*dSdy(i,j)
217         &   )
218         ENDDO         ENDDO
219        ENDDO        ENDDO
220          IF (.NOT.implicitDiffusion) THEN
221           DO j=jMin,jMax
222            DO i=iMin,iMax
223             df(i,j) = df(i,j) + _rA(i,j,bi,bj)*(
224         &    -KappaRS(i,j,k)*recip_drC(k)
225         &    *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))*rkFac
226         &    )
227            ENDDO
228           ENDDO
229          ENDIF
230  C     Net vertical flux  C     Net vertical flux
231        DO j=jMin,jMax        DO j=jMin,jMax
232         DO i=iMin,iMax         DO i=iMin,iMax
233          fVerS(i,j,kUp) = (afFacS*af(i,j) + dfFacS*df(i,j))*maskUp(i,j)          fVerS(i,j,kUp) = ( afFacS*af(i,j)+  dfFacS*df(i,j) )*maskUp(i,j)
234         ENDDO         ENDDO
235        ENDDO        ENDDO
236          IF ( TOP_LAYER ) THEN
237           DO j=jMin,jMax
238            DO i=iMin,iMax
239             fVerS(i,j,kUp) = afFacS*af(i,j)*freeSurfFac
240            ENDDO
241           ENDDO
242          ENDIF
243    
244  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
245  C     Note. Tendency terms will only be correct for range  C     Note. Tendency terms will only be correct for range
# Line 168  C           they are not algorithmically Line 249  C           they are not algorithmically
249  C           are not used.  C           are not used.
250        DO j=jMin,jMax        DO j=jMin,jMax
251         DO i=iMin,iMax         DO i=iMin,iMax
252    #define _recip_VolS1(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
253    #define _recip_VolS2(i,j,k,bi,bj) /_rA(i,j,bi,bj)
254          gS(i,j,k,bi,bj)=          gS(i,j,k,bi,bj)=
255       &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)       &   -_recip_VolS1(i,j,k,bi,bj)
256         &    _recip_VolS2(i,j,k,bi,bj)
257       &   *(       &   *(
258       &    +( fZon(i+1,j)-fZon(i,j) )       &    +( fZon(i+1,j)-fZon(i,j) )
259       &    +( fMer(i,j+1)-fMer(i,j) )       &    +( fMer(i,j+1)-fMer(i,j) )
260       &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )       &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )*rkFac
261       &    )       &    )
262         ENDDO         ENDDO
263        ENDDO        ENDDO
264    
265  C--   External haline forcing term(s)  C--   External forcing term(s)
266          CALL EXTERNAL_FORCING_S(
267         I     iMin,iMax,jMin,jMax,bi,bj,k,
268         I     myCurrentTime,myThid)
269    C     o Surface relaxation term
270    C     IF ( TOP_LAYER ) THEN
271    C      DO j=jMin,jMax
272    C       DO i=iMin,iMax
273    C        gS(i,j,k,bi,bj)=gS(i,j,k,bi,bj)
274    C    &   +maskC(i,j)*(
275    C    &   -lambdaSaltClimRelax*(salt(i,j,k,bi,bj)-SSS(i,j,bi,bj))
276    C    &   +EmPmR(i,j,bi,bj) )
277    C       ENDDO
278    C      ENDDO
279    C     ENDIF
280    
281    #ifdef ALLOW_LATITUDE_CIRCLE_FFT_FILTER
282    C--
283          CALL FILTER_LATCIRCS_FFT_APPLY( gS, 1, sNy, k, k, bi, bj, 1, myThid)
284    #endif
285    
286        RETURN        RETURN
287        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22