/[MITgcm]/MITgcm/model/src/calc_gt.F
ViewVC logotype

Diff of /MITgcm/model/src/calc_gt.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.16 by cnh, Sat Aug 22 17:51:07 1998 UTC
# Line 5  C $Header$ Line 5  C $Header$
5  CStartOfInterFace  CStartOfInterFace
6        SUBROUTINE CALC_GT(        SUBROUTINE CALC_GT(
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         I           K13,K23,KappaRT,KapGM,
10       U           af,df,fZon,fMer,fVerT,       U           af,df,fZon,fMer,fVerT,
11       I           myThid )       I           myThid )
12  C     /==========================================================\  C     /==========================================================\
# 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
# Line 50  C               direction at the south f Line 52  C               direction at the south f
52  C     fVerT   - Flux of temperature (T) in the vertical  C     fVerT   - Flux of temperature (T) 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 theta 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
59  C     vTrans  - Meridional volume transport through cell face  C     vTrans  - Meridional volume transport through cell face
60  C     wTrans  - Vertical volume transport through cell face  C     rTrans  - Vertical volume transport through cell face
61  C     af      - Advective flux component work array  C     af      - Advective flux component work array
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
# 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 KappaRT(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  CEndOfInterface  CEndOfInterface
86    
87  C     == Local variables ==  C     == Local variables ==
88  C     I, J, K - Loop counters  C     I, J, K - Loop counters
89        INTEGER i,j,k        INTEGER i,j
90        REAL afFacT, dfFacT        LOGICAL TOP_LAYER
91        REAL dutdxFac        _RL afFacT, dfFacT
92          _RL dTdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93          _RL dTdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94    
95        afFacT = 1. _d 0        afFacT = 1. _d 0
96        dfFacT = 1. _d 0        dfFacT = 1. _d 0
97        dutdxFac = afFacT        TOP_LAYER = K .EQ. 1
98    
 C---  
99  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
 C---  
100    
101  C--   Zonal flux (fZon is at west face of "theta" cell)  C--   Zonal flux (fZon is at west face of "theta" cell)
102  C     Advective component of zonal flux  C     Advective component of zonal flux
# Line 98  C     Advective component of zonal flux Line 106  C     Advective component of zonal flux
106       &   uTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i-1,j,k,bi,bj))*0.5 _d 0       &   uTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i-1,j,k,bi,bj))*0.5 _d 0
107         ENDDO         ENDDO
108        ENDDO        ENDDO
109    C     Zonal tracer gradient
110          DO j=jMin,jMax
111           DO i=iMin,iMax
112            dTdx(i,j) = _recip_dxC(i,j,bi,bj)*
113         &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))
114           ENDDO
115          ENDDO
116  C     Diffusive component of zonal flux  C     Diffusive component of zonal flux
117        DO j=jMin,jMax        DO j=jMin,jMax
118         DO i=iMin,iMax         DO i=iMin,iMax
119          df(i,j) =          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i-1,j)))*
120       &   -diffKhT*xA(i,j)*rdxC(i,j,bi,bj)       &            xA(i,j)*dTdx(i,j)
      &   *(theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))  
121         ENDDO         ENDDO
122        ENDDO        ENDDO
123  C     Net zonal flux  C     Net zonal flux
# Line 122  C       Advective component of meridiona Line 136  C       Advective component of meridiona
136       &   vTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j-1,k,bi,bj))*0.5 _d 0       &   vTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j-1,k,bi,bj))*0.5 _d 0
137         ENDDO         ENDDO
138        ENDDO        ENDDO
139    C     Zonal tracer gradient
140          DO j=jMin,jMax
141           DO i=iMin,iMax
142            dTdy(i,j) = _recip_dyC(i,j,bi,bj)*
143         &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))
144           ENDDO
145          ENDDO
146  C     Diffusive component of meridional flux  C     Diffusive component of meridional flux
147        DO j=jMin,jMax        DO j=jMin,jMax
148         DO i=iMin,iMax         DO i=iMin,iMax
149          df(i,j) =          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i,j-1)))*
150       &   -diffKhT*yA(i,j)*rdyC(i,j,bi,bj)       &            yA(i,j)*dTdy(i,j)
 C    &   -1.D3*rdyC(i,j,bi,bj)*dZF(K)*delX(1)*hFacC(i,j,k,bi,bj)*  
 C    &    hFacC(i,j-1,k,bi,bj)  
      &   *(theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))  
151         ENDDO         ENDDO
152        ENDDO        ENDDO
153  C     Net meridional flux  C     Net meridional flux
# Line 139  C     Net meridional flux Line 157  C     Net meridional flux
157         ENDDO         ENDDO
158        ENDDO        ENDDO
159    
160    C--   Interpolate terms for Redi/GM scheme
161          DO j=jMin,jMax
162           DO i=iMin,iMax
163            dTdx(i,j) = 0.5*(
164         &   +0.5*(_maskW(i+1,j,k,bi,bj)*_recip_dxC(i+1,j,bi,bj)*
165         &           (theta(i+1,j,k,bi,bj)-theta(i,j,k,bi,bj))
166         &        +_maskW(i,j,k,bi,bj)*_recip_dxC(i,j,bi,bj)*
167         &           (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj)))
168         &   +0.5*(_maskW(i+1,j,km1,bi,bj)*_recip_dxC(i+1,j,bi,bj)*
169         &           (theta(i+1,j,km1,bi,bj)-theta(i,j,km1,bi,bj))
170         &        +_maskW(i,j,km1,bi,bj)*_recip_dxC(i,j,bi,bj)*
171         &           (theta(i,j,km1,bi,bj)-theta(i-1,j,km1,bi,bj)))
172         &       )
173           ENDDO
174          ENDDO
175          DO j=jMin,jMax
176           DO i=iMin,iMax
177            dTdy(i,j) = 0.5*(
178         &   +0.5*(_maskS(i,j,k,bi,bj)*_recip_dyC(i,j,bi,bj)*
179         &           (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))
180         &        +_maskS(i,j+1,k,bi,bj)*_recip_dyC(i,j+1,bi,bj)*
181         &           (theta(i,j+1,k,bi,bj)-theta(i,j,k,bi,bj)))
182         &   +0.5*(_maskS(i,j,km1,bi,bj)*_recip_dyC(i,j,bi,bj)*
183         &           (theta(i,j,km1,bi,bj)-theta(i,j-1,km1,bi,bj))
184         &        +_maskS(i,j+1,km1,bi,bj)*_recip_dyC(i,j+1,bi,bj)*
185         &           (theta(i,j+1,km1,bi,bj)-theta(i,j,km1,bi,bj)))
186         &       )
187           ENDDO
188          ENDDO
189    
190  C--   Vertical flux (fVerT) above  C--   Vertical flux (fVerT) above
 C     Note: For K=1 then KM1=1 this gives a dT/dz = 0 upper  
 C           boundary condition.  
191  C     Advective component of vertical flux  C     Advective component of vertical flux
192    C     Note: For K=1 then KM1=1 this gives a barZ(T) = T
193    C     (this plays the role of the free-surface correction)
194        DO j=jMin,jMax        DO j=jMin,jMax
195         DO i=iMin,iMax         DO i=iMin,iMax
196          af(i,j) =          af(i,j) =
197       &   wTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j,kM1,bi,bj))*0.5 _d 0       &   rTrans(i,j)*(theta(i,j,k,bi,bj)+theta(i,j,kM1,bi,bj))*0.5 _d 0
198         ENDDO         ENDDO
199        ENDDO        ENDDO
200  C     Diffusive component of vertical flux  C     Diffusive component of vertical flux
201    C     Note: For K=1 then KM1=1 this gives a dT/dr = 0 upper
202    C           boundary condition.
203        DO j=jMin,jMax        DO j=jMin,jMax
204         DO i=iMin,iMax         DO i=iMin,iMax
205          df(i,j) =          df(i,j) = _rA(i,j,bi,bj)*(
206       &   -diffKzT*zA(i,j,bi,bj)*rdzC(k)       &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)
207       &   *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))       &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)
208         &   )
209         ENDDO         ENDDO
210        ENDDO        ENDDO
211          IF (.NOT.implicitDiffusion) THEN
212           DO j=jMin,jMax
213            DO i=iMin,iMax
214             df(i,j) = df(i,j) + _rA(i,j,bi,bj)*(
215         &    -KappaRT(i,j,k)*recip_drC(k)
216         &    *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))*rkFac
217         &    )
218            ENDDO
219           ENDDO
220          ENDIF
221  C     Net vertical flux  C     Net vertical flux
222        DO j=jMin,jMax        DO j=jMin,jMax
223         DO i=iMin,iMax         DO i=iMin,iMax
224          fVerT(i,j,kUp) = (afFacT*af(i,j) + dfFacT*df(i,j))*maskUp(i,j)          fVerT(i,j,kUp) = ( afFacT*af(i,j)+  dfFacT*df(i,j) )*maskUp(i,j)
225         ENDDO         ENDDO
226        ENDDO        ENDDO
227          IF ( TOP_LAYER ) THEN
228           DO j=jMin,jMax
229            DO i=iMin,iMax
230             fVerT(i,j,kUp) = afFacT*af(i,j)*freeSurfFac
231            ENDDO
232           ENDDO
233          ENDIF
234    
235  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
236  C     Note. Tendency terms will only be correct for range  C     Note. Tendency terms will only be correct for range
# Line 172  C           they are not algorithmically Line 240  C           they are not algorithmically
240  C           are not used.  C           are not used.
241        DO j=jMin,jMax        DO j=jMin,jMax
242         DO i=iMin,iMax         DO i=iMin,iMax
243    #define _recip_VolT(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)/_rA(i,j,bi,bj)
244          gT(i,j,k,bi,bj)=          gT(i,j,k,bi,bj)=
245       &   -rHFacC(i,j,k,bi,bj)*rdzF(k)*rDxF(i,j,bi,bj)*rDyF(i,j,bi,bj)       &   -_recip_VolT(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) )
249       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
250       &    )       &    )
251         ENDDO         ENDDO
252        ENDDO        ENDDO
253    
254  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
255    C     o Surface relaxation term
256          IF ( TOP_LAYER ) THEN
257           DO j=jMin,jMax
258            DO i=iMin,iMax
259             gT(i,j,k,bi,bj)=gT(i,j,k,bi,bj)
260         &  +maskC(i,j)*(
261         &   -lambdaThetaClimRelax*(theta(i,j,k,bi,bj)-SST(i,j,bi,bj))
262         &   -Qnet(i,j,bi,bj) )
263            ENDDO
264           ENDDO
265          ENDIF
266    
267        RETURN        RETURN
268        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22