/[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.6 by cnh, Sat May 30 02:10:16 1998 UTC revision 1.7 by adcroft, Wed Jun 10 16:05:39 1998 UTC
# Line 6  CStartOfInterFace Line 6  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,wTrans,maskup,
9       U           af,df,fZon,fMer, fVerS,       I           K13,K23,KappaZS,KapGM,
10         U           af,df,fZon,fMer,fVerS,
11       I           myThid )       I           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 47  C     fZon    - Work array for flux of t Line 48  C     fZon    - Work array for flux of t
48  C               direction at the west face of a cell.  C               direction at the west face of a cell.
49  C     fMer    - Work array for flux of temperature in the north-south  C     fMer    - Work array for flux of temperature in the north-south
50  C               direction at the south face of a cell.  C               direction at the south face of a cell.
51  C     fVerS   - Flux of salinity (S) in the vertical  C     fVerS   - Flux of salt (S) in the vertical
52  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.
53  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
54  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
# Line 59  C     af      - Advective flux component Line 60  C     af      - Advective flux component
60  C     df      - Diffusive flux component work array  C     df      - Diffusive flux component work array
61  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
62  C                                      results will be set.  C                                      results will be set.
63  C     myThid - Instance number for this innvocation of CALC_GS  C     myThid - Instance number for this innvocation of CALC_GT
64        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 69  C     myThid - Instance number for this Line 70  C     myThid - Instance number for this
70        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73          _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
74          _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
75          _RL KappaZS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)
76          _RL KapGM (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79        INTEGER kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
80        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
81        INTEGER myThid        INTEGER myThid
82  CEndOfInterface  CEndOfInterface
83    
84  C     == Local variables ==  C     == Local variables ==
85  C     I, J, K - Loop counters  C     I, J, K - Loop counters
86        INTEGER i,j,k        INTEGER i,j
87        INTEGER afFacS, dfFacS        LOGICAL TOP_LAYER
88          _RL afFacS, dfFacS
89          _RL dSdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90          _RL dSdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91    
92        afFacS = 1. _d 0        afFacS = 1. _d 0
93        dfFacS = 1. _d 0        dfFacS = 1. _d 0
94          TOP_LAYER = K .EQ. 1
95    
 C---  
96  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
 C---  
97    
98  C--   Zonal flux (fZon is at west face of "salt" cell)  C--   Zonal flux (fZon is at west face of "salt" cell)
99  C     Advective component of zonal flux  C     Advective component of zonal flux
# Line 96  C     Advective component of zonal flux Line 103  C     Advective component of zonal flux
103       &   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
104         ENDDO         ENDDO
105        ENDDO        ENDDO
106    C     Zonal tracer gradient
107          DO j=jMin,jMax
108           DO i=iMin,iMax
109            dSdx(i,j) = _rdxC(i,j,bi,bj)*
110         &  (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))
111           ENDDO
112          ENDDO
113  C     Diffusive component of zonal flux  C     Diffusive component of zonal flux
114        DO j=jMin,jMax        DO j=jMin,jMax
115         DO i=iMin,iMax         DO i=iMin,iMax
116          df(i,j) =          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i-1,j)))*
117       &   -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))  
118         ENDDO         ENDDO
119        ENDDO        ENDDO
120  C     Net zonal flux  C     Net zonal flux
# Line 120  C       Advective component of meridiona Line 133  C       Advective component of meridiona
133       &   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
134         ENDDO         ENDDO
135        ENDDO        ENDDO
136    C     Zonal tracer gradient
137          DO j=jMin,jMax
138           DO i=iMin,iMax
139            dSdy(i,j) = _rdyC(i,j,bi,bj)*
140         &  (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))
141           ENDDO
142          ENDDO
143  C     Diffusive component of meridional flux  C     Diffusive component of meridional flux
144        DO j=jMin,jMax        DO j=jMin,jMax
145         DO i=iMin,iMax         DO i=iMin,iMax
146          df(i,j) =          df(i,j) = -(diffKhS+0.5*(KapGM(i,j)+KapGM(i,j-1)))*
147       &   -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))  
148         ENDDO         ENDDO
149        ENDDO        ENDDO
150  C     Net meridional flux  C     Net meridional flux
# Line 135  C     Net meridional flux Line 154  C     Net meridional flux
154         ENDDO         ENDDO
155        ENDDO        ENDDO
156    
157    C--   Interpolate terms for Redi/GM scheme
158          DO j=jMin,jMax
159           DO i=iMin,iMax
160            dSdx(i,j) = 0.5*(
161         &   +0.5*(_maskW(i+1,j,k,bi,bj)*_rdxC(i+1,j,bi,bj)*
162         &           (salt(i+1,j,k,bi,bj)-salt(i,j,k,bi,bj))
163         &        +_maskW(i,j,k,bi,bj)*_rdxC(i,j,bi,bj)*
164         &           (salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj)))
165         &   +0.5*(_maskW(i+1,j,km1,bi,bj)*_rdxC(i+1,j,bi,bj)*
166         &           (salt(i+1,j,km1,bi,bj)-salt(i,j,km1,bi,bj))
167         &        +_maskW(i,j,km1,bi,bj)*_rdxC(i,j,bi,bj)*
168         &           (salt(i,j,km1,bi,bj)-salt(i-1,j,km1,bi,bj)))
169         &       )
170           ENDDO
171          ENDDO
172          DO j=jMin,jMax
173           DO i=iMin,iMax
174            dSdy(i,j) = 0.5*(
175         &   +0.5*(_maskS(i,j,k,bi,bj)*_rdyC(i,j,bi,bj)*
176         &           (salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))
177         &        +_maskS(i,j+1,k,bi,bj)*_rdyC(i,j+1,bi,bj)*
178         &           (salt(i,j+1,k,bi,bj)-salt(i,j,k,bi,bj)))
179         &   +0.5*(_maskS(i,j,km1,bi,bj)*_rdyC(i,j,bi,bj)*
180         &           (salt(i,j,km1,bi,bj)-salt(i,j-1,km1,bi,bj))
181         &        +_maskS(i,j+1,km1,bi,bj)*_rdyC(i,j+1,bi,bj)*
182         &           (salt(i,j+1,km1,bi,bj)-salt(i,j,km1,bi,bj)))
183         &       )
184           ENDDO
185          ENDDO
186    
187  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.  
188  C     Advective component of vertical flux  C     Advective component of vertical flux
189    C     Note: For K=1 then KM1=1 this gives a barZ(T) = T
190    C     (this plays the role of the free-surface correction)
191        DO j=jMin,jMax        DO j=jMin,jMax
192         DO i=iMin,iMax         DO i=iMin,iMax
193          af(i,j) =          af(i,j) =
# Line 146  C     Advective component of vertical fl Line 195  C     Advective component of vertical fl
195         ENDDO         ENDDO
196        ENDDO        ENDDO
197  C     Diffusive component of vertical flux  C     Diffusive component of vertical flux
198    C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper
199    C           boundary condition.
200        DO j=jMin,jMax        DO j=jMin,jMax
201         DO i=iMin,iMax         DO i=iMin,iMax
202          df(i,j) =          df(i,j) = _zA(i,j,bi,bj)*(
203       &   -diffKzS*_zA(i,j,bi,bj)*rdzC(k)       &   -KapGM(i,j)*K13(i,j,k)*dSdx(i,j)
204       &   *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))       &   -KapGM(i,j)*K23(i,j,k)*dSdy(i,j)
205         &   )
206         ENDDO         ENDDO
207        ENDDO        ENDDO
208          IF (.NOT.implicitDiffusion) THEN
209           DO j=jMin,jMax
210            DO i=iMin,iMax
211             df(i,j) = df(i,j) + _zA(i,j,bi,bj)*(
212         &    -KappaZS(i,j,k)*rdzC(k)
213         &    *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))
214         &    )
215            ENDDO
216           ENDDO
217          ENDIF
218  C     Net vertical flux  C     Net vertical flux
219        DO j=jMin,jMax        DO j=jMin,jMax
220         DO i=iMin,iMax         DO i=iMin,iMax
221          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)
222         ENDDO         ENDDO
223        ENDDO        ENDDO
224          IF ( TOP_LAYER ) THEN
225           DO j=jMin,jMax
226            DO i=iMin,iMax
227             fVerS(i,j,kUp) = afFacS*af(i,j)*freeSurfFac
228            ENDDO
229           ENDDO
230          ENDIF
231    
232  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
233  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 237  C           they are not algorithmically
237  C           are not used.  C           are not used.
238        DO j=jMin,jMax        DO j=jMin,jMax
239         DO i=iMin,iMax         DO i=iMin,iMax
240    C    &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)
241    C    &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)/_zA(i,j,bi,bj)
242    C #define _rVolS(i,j,k,bi,bj) _rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)
243    #define _rVolS(i,j,k,bi,bj) _rhFacC(i,j,k,bi,bj)*rdzF(k)/_zA(i,j,bi,bj)
244          gS(i,j,k,bi,bj)=          gS(i,j,k,bi,bj)=
245       &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)       &   -_rVolS(i,j,k,bi,bj)
246       &   *(       &   *(
247       &    +( fZon(i+1,j)-fZon(i,j) )       &    +( fZon(i+1,j)-fZon(i,j) )
248       &    +( fMer(i,j+1)-fMer(i,j) )       &    +( fMer(i,j+1)-fMer(i,j) )
# Line 178  C           are not used. Line 251  C           are not used.
251         ENDDO         ENDDO
252        ENDDO        ENDDO
253    
254  C--   External haline forcing term(s)  C--   External P-E forcing term(s)
255    
256        RETURN        RETURN
257        END        END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.7

  ViewVC Help
Powered by ViewVC 1.1.22