/[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.18 by cnh, Tue Nov 3 15:28:04 1998 UTC revision 1.19 by cnh, Fri Nov 6 22:44:44 1998 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    
3  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
4    
5  CStartOfInterFace  CStartOfInterFace
6        SUBROUTINE CALC_GT(        SUBROUTINE CALC_GT(
# Line 100  C     I, J, K - Loop counters Line 100  C     I, J, K - Loop counters
100  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
101    
102  C--   Zonal flux (fZon is at west face of "theta" cell)  C--   Zonal flux (fZon is at west face of "theta" cell)
103  C     Advective component of zonal flux  #ifdef INCLUDE_T_ADVECTION_CODE
104    C     o Advective component of zonal flux
105        DO j=jMin,jMax        DO j=jMin,jMax
106         DO i=iMin,iMax         DO i=iMin,iMax
107          af(i,j) =          af(i,j) =
108       &   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
109         ENDDO         ENDDO
110        ENDDO        ENDDO
111  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
112    #ifdef INCLUDE_T_DIFFUSION_CODE
113    C     o Zonal tracer gradient
114        DO j=jMin,jMax        DO j=jMin,jMax
115         DO i=iMin,iMax         DO i=iMin,iMax
116          dTdx(i,j) = _recip_dxC(i,j,bi,bj)*          dTdx(i,j) = _recip_dxC(i,j,bi,bj)*
117       &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))       &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))
118         ENDDO         ENDDO
119        ENDDO        ENDDO
120  C     Diffusive component of zonal flux  C     o Diffusive component of zonal flux
121        DO j=jMin,jMax        DO j=jMin,jMax
122         DO i=iMin,iMax         DO i=iMin,iMax
123          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i-1,j)))*          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i-1,j)))*
124       &            xA(i,j)*dTdx(i,j)       &            xA(i,j)*dTdx(i,j)
125         ENDDO         ENDDO
126        ENDDO        ENDDO
127  C     Net zonal flux  #endif /* INCLUDE_T_DIFFUSION_CODE */
128    C     o Net zonal flux
129        DO j=jMin,jMax        DO j=jMin,jMax
130         DO i=iMin,iMax         DO i=iMin,iMax
131          fZon(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          fZon(i,j) = 0.
132         _ADT(&            + afFacT*af(i,j) )
133         _LPT(&            + dfFacT*df(i,j) )
134         ENDDO         ENDDO
135        ENDDO        ENDDO
136    
137  C--   Meridional flux (fMer is at south face of "theta" cell)  C--   Meridional flux (fMer is at south face of "theta" cell)
138  C     Advective component of meridional flux  #ifdef INCLUDE_T_ADVECTION_CODE
139    C     o Advective component of meridional flux
140        DO j=jMin,jMax        DO j=jMin,jMax
141         DO i=iMin,iMax         DO i=iMin,iMax
 C       Advective component of meridional flux  
142          af(i,j) =          af(i,j) =
143       &   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
144         ENDDO         ENDDO
145        ENDDO        ENDDO
146  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
147    #ifdef INCLUDE_T_DIFFUSION_CODE
148    C     o Meridional tracer gradient
149        DO j=jMin,jMax        DO j=jMin,jMax
150         DO i=iMin,iMax         DO i=iMin,iMax
151          dTdy(i,j) = _recip_dyC(i,j,bi,bj)*          dTdy(i,j) = _recip_dyC(i,j,bi,bj)*
152       &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))       &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))
153         ENDDO         ENDDO
154        ENDDO        ENDDO
155  C     Diffusive component of meridional flux  C     o Diffusive component of meridional flux
156        DO j=jMin,jMax        DO j=jMin,jMax
157         DO i=iMin,iMax         DO i=iMin,iMax
158          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i,j-1)))*          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i,j-1)))*
159       &            yA(i,j)*dTdy(i,j)       &            yA(i,j)*dTdy(i,j)
160         ENDDO         ENDDO
161        ENDDO        ENDDO
162  C     Net meridional flux  #endif /* INCLUDE_T_DIFFUSION_CODE */
163    C     o Net meridional flux
164        DO j=jMin,jMax        DO j=jMin,jMax
165         DO i=iMin,iMax         DO i=iMin,iMax
166          fMer(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          fMer(i,j) = 0.
167         _ADT(&  + afFacT*af(i,j) )
168         _LPT(&  + dfFacT*df(i,j) )
169         ENDDO         ENDDO
170        ENDDO        ENDDO
171    
172  C--   Interpolate terms for Redi/GM scheme  #ifdef INCLUDE_T_DIFFUSION_CODE
173    C--   Terms that diffusion tensor projects onto z
174        DO j=jMin,jMax        DO j=jMin,jMax
175         DO i=iMin,iMax         DO i=iMin,iMax
176          dTdx(i,j) = 0.5*(          dTdx(i,j) = 0.5*(
# Line 195  C--   Interpolate terms for Redi/GM sche Line 207  C--   Interpolate terms for Redi/GM sche
207       &       )       &       )
208         ENDDO         ENDDO
209        ENDDO        ENDDO
210    #endif /* INCLUDE_T_DIFFUSION_CODE */
211    
212  C--   Vertical flux (fVerT) above  C--   Vertical flux ( fVerT(,,kUp) is at upper face of "theta" cell )
213  C     Advective component of vertical flux  #ifdef INCLUDE_T_ADVECTION_CODE
214    C     o Advective component of vertical flux
215  C     Note: For K=1 then KM1=1 this gives a barZ(T) = T  C     Note: For K=1 then KM1=1 this gives a barZ(T) = T
216  C     (this plays the role of the free-surface correction)  C     (this plays the role of the free-surface correction)
217        DO j=jMin,jMax        DO j=jMin,jMax
# Line 206  C     (this plays the role of the free-s Line 220  C     (this plays the role of the free-s
220       &   rTrans(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
221         ENDDO         ENDDO
222        ENDDO        ENDDO
223  C     Diffusive component of vertical flux  #endif /* INCLUDE_T_ADVECTION_CODE */
224  C     Note: For K=1 then KM1=1 this gives a dT/dr = 0 upper  #ifdef INCLUDE_T_DIFFUSION_CODE
225    C     o Diffusive component of vertical flux
226    C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
227  C           boundary condition.  C           boundary condition.
228        DO j=jMin,jMax        DO j=jMin,jMax
229         DO i=iMin,iMax         DO i=iMin,iMax
# Line 227  C           boundary condition. Line 243  C           boundary condition.
243          ENDDO          ENDDO
244         ENDDO         ENDDO
245        ENDIF        ENDIF
246  C     Net vertical flux  #endif /* INCLUDE_T_DIFFUSION_CODE */
247    C     o Net vertical flux
248        DO j=jMin,jMax        DO j=jMin,jMax
249         DO i=iMin,iMax         DO i=iMin,iMax
250          fVerT(i,j,kUp) = ( afFacT*af(i,j)+  dfFacT*df(i,j) )*maskUp(i,j)          fVerT(i,j,kUp) = 0.
251         _ADT(&  +afFacT*af(i,j)*maskUp(i,j) )
252         _LPT(&  +dfFacT*df(i,j)*maskUp(i,j) )
253         ENDDO         ENDDO
254        ENDDO        ENDDO
255    #ifdef INCLUDE_T_ADVECTION_CODE
256        IF ( TOP_LAYER ) THEN        IF ( TOP_LAYER ) THEN
257         DO j=jMin,jMax         DO j=jMin,jMax
258          DO i=iMin,iMax          DO i=iMin,iMax
# Line 240  C     Net vertical flux Line 260  C     Net vertical flux
260          ENDDO          ENDDO
261         ENDDO         ENDDO
262        ENDIF        ENDIF
263    #endif /* INCLUDE_T_ADVECTION_CODE */
264    
265  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
266  C     Note. Tendency terms will only be correct for range  C     Note. Tendency terms will only be correct for range
# Line 262  C           are not used. Line 283  C           are not used.
283         ENDDO         ENDDO
284        ENDDO        ENDDO
285    
286    #ifdef INCLUDE_T_FORCING_CODE
287  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
288  C     o Surface relaxation term        CALL EXTERNAL_FORCING_T(
289        IF ( TOP_LAYER ) THEN       I     iMin,iMax,jMin,jMax,bi,bj,k,
290         DO j=jMin,jMax       I     maskC,
291          DO i=iMin,iMax       I     myCurrentTime,myThid)
292           gT(i,j,k,bi,bj)=gT(i,j,k,bi,bj)  #endif /*  INCLUDE_T_FORCING_CODE */
293       &  +maskC(i,j)*(  
294       &   -lambdaThetaClimRelax*(theta(i,j,k,bi,bj)-SST(i,j,bi,bj))  #ifdef INCLUDE_LAT_CIRC_FFT_FILTER_CODE
295       &   -Qnet(i,j,bi,bj) )  C--   Zonal FFT filter of tendency
296          ENDDO        CALL FILTER_LATCIRCS_FFT_APPLY(
297         ENDDO       U     gT,
298        ENDIF       I     1, sNy, k, k, bi, bj, 1, myThid)
299    #endif /* INCLUDE_LAT_CIRC_FFT_FILTER_CODE */
300    
301    
302        RETURN        RETURN
303        END        END

Legend:
Removed from v.1.18  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.22