/[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.11 by cnh, Mon Jun 15 05:13:55 1998 UTC revision 1.24 by heimbach, Fri Jun 9 02:45:04 2000 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(
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,KappaZT,KapGM,       I           K13,K23,KappaRT,KapGM,
10       U           af,df,fZon,fMer,fVerT,       U           af,df,fZon,fMer,fVerT,
11       I           myThid )       I           myCurrentTime, myThid )
12  C     /==========================================================\  C     /==========================================================\
13  C     | SUBROUTINE CALC_GT                                       |  C     | SUBROUTINE CALC_GT                                       |
14  C     | o Calculate the temperature tendency terms.              |  C     | o Calculate the temperature tendency terms.              |
# Line 43  C     == GLobal variables == Line 43  C     == GLobal variables ==
43  #include "PARAMS.h"  #include "PARAMS.h"
44  #include "GRID.h"  #include "GRID.h"
45  #include "FFIELDS.h"  #include "FFIELDS.h"
46    #ifdef ALLOW_KPP
47    #include "KPPMIX.h"
48    #endif
49    
50    
51  C     == Routine arguments ==  C     == Routine arguments ==
52  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 52  C               direction at the south f Line 56  C               direction at the south f
56  C     fVerT   - Flux of temperature (T) in the vertical  C     fVerT   - Flux of temperature (T) in the vertical
57  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.
58  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
59    C     maskC   - Land mask for theta cells (used in TOP_LAYER only)
60  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
61  C     yA      - Tracer cell face area normal to X  C     yA      - Tracer cell face area normal to X
62  C     uTrans  - Zonal volume transport through cell face  C     uTrans  - Zonal volume transport through cell face
63  C     vTrans  - Meridional volume transport through cell face  C     vTrans  - Meridional volume transport through cell face
64  C     wTrans  - Vertical volume transport through cell face  C     rTrans  - Vertical volume transport through cell face
65  C     af      - Advective flux component work array  C     af      - Advective flux component work array
66  C     df      - Diffusive flux component work array  C     df      - Diffusive flux component work array
67  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 69  C     myThid - Instance number for this Line 74  C     myThid - Instance number for this
74        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79        _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K13   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
81        _RL KappaZT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nz)        _RL K23   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
82          _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
83        _RL KapGM (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KapGM (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
87        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
88        INTEGER myThid        INTEGER myThid
89          _RL     myCurrentTime
90  CEndOfInterface  CEndOfInterface
91    
92  C     == Local variables ==  C     == Local variables ==
# Line 89  C     I, J, K - Loop counters Line 96  C     I, J, K - Loop counters
96        _RL afFacT, dfFacT        _RL afFacT, dfFacT
97        _RL dTdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dTdx(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98        _RL dTdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dTdy(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99          _RL df4   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100    #ifdef ALLOW_KPP
101          _RS hbl  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)    ! used by KPP mixing scheme
102          _RS frac (1-OLx:sNx+OLx,1-OLy:sNy+OLy)    ! used by KPP mixing scheme
103          _RS negone                                ! used as argument to SWFRAC
104          integer jwtype                            ! index for Jerlov water type
105    #endif
106    
107    #ifdef ALLOW_AUTODIFF_TAMC
108    C--   only the kUp part of fverT is set in this subroutine
109    C--   the kDown is still required
110    
111          fVerT(1,1,kDown) = fVerT(1,1,kDown)
112          DO j=1-OLy,sNy+OLy
113           DO i=1-OLx,sNx+OLx
114            fZon(i,j)      = 0.0
115            fMer(i,j)      = 0.0
116            fVerT(i,j,kUp) = 0.0
117           ENDDO
118          ENDDO
119    #endif
120    
121        afFacT = 1. _d 0        afFacT = 1. _d 0
122        dfFacT = 1. _d 0        dfFacT = 1. _d 0
# Line 96  C     I, J, K - Loop counters Line 124  C     I, J, K - Loop counters
124    
125  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
126    
127    #ifdef INCLUDE_T_DIFFUSION_CODE
128    C     o Zonal tracer gradient
129          DO j=1-Oly,sNy+Oly
130           DO i=1-Olx+1,sNx+Olx
131            dTdx(i,j) = _recip_dxC(i,j,bi,bj)*
132         &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))
133           ENDDO
134          ENDDO
135    C     o Meridional tracer gradient
136          DO j=1-Oly+1,sNy+Oly
137           DO i=1-Olx,sNx+Olx
138            dTdy(i,j) = _recip_dyC(i,j,bi,bj)*
139         &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))
140           ENDDO
141          ENDDO
142    
143    C--   del^2 of T, needed for bi-harmonic (del^4) term
144          IF (diffK4T .NE. 0.) THEN
145           DO j=1-Oly+1,sNy+Oly-1
146            DO i=1-Olx+1,sNx+Olx-1
147             df4(i,j)= _recip_hFacC(i,j,k,bi,bj)
148         &             *recip_drF(k)/_rA(i,j,bi,bj)
149         &            *(
150         &             +( xA(i+1,j)*dTdx(i+1,j)-xA(i,j)*dTdx(i,j) )
151         &             +( yA(i,j+1)*dTdy(i,j+1)-yA(i,j)*dTdy(i,j) )
152         &             )
153            ENDDO
154           ENDDO
155          ENDIF
156    #endif
157    
158  C--   Zonal flux (fZon is at west face of "theta" cell)  C--   Zonal flux (fZon is at west face of "theta" cell)
159  C     Advective component of zonal flux  #ifdef INCLUDE_T_ADVECTION_CODE
160    C     o Advective component of zonal flux
161        DO j=jMin,jMax        DO j=jMin,jMax
162         DO i=iMin,iMax         DO i=iMin,iMax
163          af(i,j) =          af(i,j) =
164       &   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
165         ENDDO         ENDDO
166        ENDDO        ENDDO
167  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
168        DO j=jMin,jMax  #ifdef INCLUDE_T_DIFFUSION_CODE
169         DO i=iMin,iMax  C     o Diffusive component of zonal flux
         dTdx(i,j) = _rdxC(i,j,bi,bj)*  
      &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Diffusive component of zonal flux  
170        DO j=jMin,jMax        DO j=jMin,jMax
171         DO i=iMin,iMax         DO i=iMin,iMax
172          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)))*
173       &            xA(i,j)*dTdx(i,j)       &            xA(i,j)*dTdx(i,j)
174         ENDDO         ENDDO
175        ENDDO        ENDDO
176  C     Net zonal flux  C     o Add the bi-harmonic contribution
177          IF (diffK4T .NE. 0.) THEN
178           DO j=jMin,jMax
179            DO i=iMin,iMax
180             df(i,j) = df(i,j) + xA(i,j)*
181         &    diffK4T*(df4(i,j)-df4(i-1,j))*_recip_dxC(i,j,bi,bj)
182            ENDDO
183           ENDDO
184          ENDIF
185    #endif /* INCLUDE_T_DIFFUSION_CODE */
186    C     o Net zonal flux
187        DO j=jMin,jMax        DO j=jMin,jMax
188         DO i=iMin,iMax         DO i=iMin,iMax
189          fZon(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          fZon(i,j) = 0.
190         & _ADT( + afFacT*af(i,j) )
191         & _LPT( + dfFacT*df(i,j) )
192         ENDDO         ENDDO
193        ENDDO        ENDDO
194    
195  C--   Meridional flux (fMer is at south face of "theta" cell)  C--   Meridional flux (fMer is at south face of "theta" cell)
196  C     Advective component of meridional flux  #ifdef INCLUDE_T_ADVECTION_CODE
197    C     o Advective component of meridional flux
198        DO j=jMin,jMax        DO j=jMin,jMax
199         DO i=iMin,iMax         DO i=iMin,iMax
 C       Advective component of meridional flux  
200          af(i,j) =          af(i,j) =
201       &   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
202         ENDDO         ENDDO
203        ENDDO        ENDDO
204  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
205        DO j=jMin,jMax  #ifdef INCLUDE_T_DIFFUSION_CODE
206         DO i=iMin,iMax  C     o Diffusive component of meridional flux
         dTdy(i,j) = _rdyC(i,j,bi,bj)*  
      &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Diffusive component of meridional flux  
207        DO j=jMin,jMax        DO j=jMin,jMax
208         DO i=iMin,iMax         DO i=iMin,iMax
209          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)))*
210       &            yA(i,j)*dTdy(i,j)       &            yA(i,j)*dTdy(i,j)
211         ENDDO         ENDDO
212        ENDDO        ENDDO
213  C     Net meridional flux  C     o Add the bi-harmonic contribution
214          IF (diffK4T .NE. 0.) THEN
215           DO j=jMin,jMax
216            DO i=iMin,iMax
217             df(i,j) = df(i,j) + yA(i,j)*
218         &    diffK4T*(df4(i,j)-df4(i,j-1))*_recip_dyC(i,j,bi,bj)
219            ENDDO
220           ENDDO
221          ENDIF
222    #endif /* INCLUDE_T_DIFFUSION_CODE */
223    C     o Net meridional flux
224        DO j=jMin,jMax        DO j=jMin,jMax
225         DO i=iMin,iMax         DO i=iMin,iMax
226          fMer(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          fMer(i,j) = 0.
227         & _ADT( + afFacT*af(i,j) )
228         & _LPT( + dfFacT*df(i,j) )
229         ENDDO         ENDDO
230        ENDDO        ENDDO
231    
232  C--   Interpolate terms for Redi/GM scheme  #ifdef INCLUDE_T_DIFFUSION_CODE
233    C--   Terms that diffusion tensor projects onto z
234        DO j=jMin,jMax        DO j=jMin,jMax
235         DO i=iMin,iMax         DO i=iMin,iMax
236          dTdx(i,j) = 0.5*(          dTdx(i,j) = 0.5*(
237       &   +0.5*(_maskW(i+1,j,k,bi,bj)*_rdxC(i+1,j,bi,bj)*       &   +0.5*(_maskW(i+1,j,k,bi,bj)
238         &         *_recip_dxC(i+1,j,bi,bj)*
239       &           (theta(i+1,j,k,bi,bj)-theta(i,j,k,bi,bj))       &           (theta(i+1,j,k,bi,bj)-theta(i,j,k,bi,bj))
240       &        +_maskW(i,j,k,bi,bj)*_rdxC(i,j,bi,bj)*       &        +_maskW(i,j,k,bi,bj)
241         &         *_recip_dxC(i,j,bi,bj)*
242       &           (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)))
243       &   +0.5*(_maskW(i+1,j,km1,bi,bj)*_rdxC(i+1,j,bi,bj)*       &   +0.5*(_maskW(i+1,j,km1,bi,bj)
244         &         *_recip_dxC(i+1,j,bi,bj)*
245       &           (theta(i+1,j,km1,bi,bj)-theta(i,j,km1,bi,bj))       &           (theta(i+1,j,km1,bi,bj)-theta(i,j,km1,bi,bj))
246       &        +_maskW(i,j,km1,bi,bj)*_rdxC(i,j,bi,bj)*       &        +_maskW(i,j,km1,bi,bj)
247         &         *_recip_dxC(i,j,bi,bj)*
248       &           (theta(i,j,km1,bi,bj)-theta(i-1,j,km1,bi,bj)))       &           (theta(i,j,km1,bi,bj)-theta(i-1,j,km1,bi,bj)))
249       &       )       &       )
250         ENDDO         ENDDO
# Line 173  C--   Interpolate terms for Redi/GM sche Line 252  C--   Interpolate terms for Redi/GM sche
252        DO j=jMin,jMax        DO j=jMin,jMax
253         DO i=iMin,iMax         DO i=iMin,iMax
254          dTdy(i,j) = 0.5*(          dTdy(i,j) = 0.5*(
255       &   +0.5*(_maskS(i,j,k,bi,bj)*_rdyC(i,j,bi,bj)*       &   +0.5*(_maskS(i,j,k,bi,bj)
256         &         *_recip_dyC(i,j,bi,bj)*
257       &           (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))
258       &        +_maskS(i,j+1,k,bi,bj)*_rdyC(i,j+1,bi,bj)*       &        +_maskS(i,j+1,k,bi,bj)
259         &         *_recip_dyC(i,j+1,bi,bj)*
260       &           (theta(i,j+1,k,bi,bj)-theta(i,j,k,bi,bj)))       &           (theta(i,j+1,k,bi,bj)-theta(i,j,k,bi,bj)))
261       &   +0.5*(_maskS(i,j,km1,bi,bj)*_rdyC(i,j,bi,bj)*       &   +0.5*(_maskS(i,j,km1,bi,bj)
262         &         *_recip_dyC(i,j,bi,bj)*
263       &           (theta(i,j,km1,bi,bj)-theta(i,j-1,km1,bi,bj))       &           (theta(i,j,km1,bi,bj)-theta(i,j-1,km1,bi,bj))
264       &        +_maskS(i,j+1,km1,bi,bj)*_rdyC(i,j+1,bi,bj)*       &        +_maskS(i,j+1,km1,bi,bj)
265         &         *_recip_dyC(i,j+1,bi,bj)*
266       &           (theta(i,j+1,km1,bi,bj)-theta(i,j,km1,bi,bj)))       &           (theta(i,j+1,km1,bi,bj)-theta(i,j,km1,bi,bj)))
267       &       )       &       )
268         ENDDO         ENDDO
269        ENDDO        ENDDO
270    #endif /* INCLUDE_T_DIFFUSION_CODE */
271    
272  C--   Vertical flux (fVerT) above  C--   Vertical flux ( fVerT(,,kUp) is at upper face of "theta" cell )
273  C     Advective component of vertical flux  #ifdef INCLUDE_T_ADVECTION_CODE
274    C     o Advective component of vertical flux
275  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
276  C     (this plays the role of the free-surface correction)  C     (this plays the role of the free-surface correction)
277        DO j=jMin,jMax        DO j=jMin,jMax
278         DO i=iMin,iMax         DO i=iMin,iMax
279          af(i,j) =          af(i,j) =
280       &   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
281         ENDDO         ENDDO
282        ENDDO        ENDDO
283  C     Diffusive component of vertical flux  #endif /* INCLUDE_T_ADVECTION_CODE */
284  C     Note: For K=1 then KM1=1 this gives a dT/dz = 0 upper  #ifdef INCLUDE_T_DIFFUSION_CODE
285    C     o Diffusive component of vertical flux
286    C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
287  C           boundary condition.  C           boundary condition.
288        DO j=jMin,jMax        DO j=jMin,jMax
289         DO i=iMin,iMax         DO i=iMin,iMax
290          df(i,j) = _zA(i,j,bi,bj)*(          df(i,j) = _rA(i,j,bi,bj)*(
291       &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)       &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)
292       &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)       &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)
293       &   )       &   )
# Line 209  C           boundary condition. Line 296  C           boundary condition.
296        IF (.NOT.implicitDiffusion) THEN        IF (.NOT.implicitDiffusion) THEN
297         DO j=jMin,jMax         DO j=jMin,jMax
298          DO i=iMin,iMax          DO i=iMin,iMax
299           df(i,j) = df(i,j) + _zA(i,j,bi,bj)*(           df(i,j) = df(i,j) + _rA(i,j,bi,bj)*(
300       &    -KappaZT(i,j,k)*rdzC(k)       &    -KappaRT(i,j,k)*recip_drC(k)
301       &    *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))       &    *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))*rkFac
302       &    )       &    )
303          ENDDO          ENDDO
304         ENDDO         ENDDO
305        ENDIF        ENDIF
306  C     Net vertical flux  #endif /* INCLUDE_T_DIFFUSION_CODE */
307    
308    #ifdef ALLOW_KPP
309          IF (usingKPPmixing) THEN
310    C--   Compute fraction of solar short-wave flux penetrating to
311    C     the bottom of the mixing layer
312           DO j=jMin,jMax
313            DO i=iMin,iMax
314             hbl(i,j) = KPPhbl(i,j,bi,bj)
315            ENDDO
316           ENDDO
317           j=(sNx+2*OLx)*(sNy+2*OLy)
318           jwtype = 3
319           negone = -1.
320           CALL SWFRAC(
321         I     j, negone, hbl, jwtype,
322         O     frac )
323    
324    C     Add non local transport coefficient (ghat term) to right-hand-side
325    C     The nonlocal transport term is noNrero only for scalars in unstable
326    C     (convective) forcing conditions.
327    C     Note: -[Qnet * delZ(1) + Qsw * (1-frac) / KPPhbl] * 4000 * rho
328    C     is the total heat flux
329    C     penetrating the mixed layer from the surface in (deg C / s)
330           IF ( TOP_LAYER ) THEN
331            DO j=jMin,jMax
332             DO i=iMin,iMax
333              df(i,j) = df(i,j) + _rA(i,j,bi,bj) *
334         &           ( Qnet(i,j,bi,bj) * delZ(1) +
335         &           Qsw(i,j,bi,bj) * (1.-frac(i,j))
336         &           / KPPhbl(i,j,bi,bj) ) *
337         &           ( KappaRT(i,j,k) * KPPghat(i,j,k,  bi,bj) )
338             ENDDO
339            ENDDO
340           ELSE
341            DO j=jMin,jMax
342             DO i=iMin,iMax
343              df(i,j) = df(i,j) + _rA(i,j,bi,bj) *
344         &           ( Qnet(i,j,bi,bj) * delZ(1) +
345         &           Qsw(i,j,bi,bj)  * (1.-frac(i,j))
346         &           / KPPhbl(i,j,bi,bj) ) *
347         &           ( KappaRT(i,j,k)   * KPPghat(i,j,k,  bi,bj)
348         &           - KappaRT(i,j,k-1) * KPPghat(i,j,k-1,bi,bj) )
349             ENDDO
350            ENDDO
351           ENDIF
352          ENDIF
353    #endif /* ALLOW_KPP */
354    
355    C     o Net vertical flux
356        DO j=jMin,jMax        DO j=jMin,jMax
357         DO i=iMin,iMax         DO i=iMin,iMax
358          fVerT(i,j,kUp) = ( afFacT*af(i,j)+  dfFacT*df(i,j) )*maskUp(i,j)          fVerT(i,j,kUp) = 0.
359         & _ADT( +afFacT*af(i,j)*maskUp(i,j) )
360         & _LPT( +dfFacT*df(i,j)*maskUp(i,j) )
361         ENDDO         ENDDO
362        ENDDO        ENDDO
363    #ifdef INCLUDE_T_ADVECTION_CODE
364        IF ( TOP_LAYER ) THEN        IF ( TOP_LAYER ) THEN
365         DO j=jMin,jMax         DO j=jMin,jMax
366          DO i=iMin,iMax          DO i=iMin,iMax
# Line 229  C     Net vertical flux Line 368  C     Net vertical flux
368          ENDDO          ENDDO
369         ENDDO         ENDDO
370        ENDIF        ENDIF
371    #endif /* INCLUDE_T_ADVECTION_CODE */
372    
373  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
374  C     Note. Tendency terms will only be correct for range  C     Note. Tendency terms will only be correct for range
# Line 238  C           they are not algorithmically Line 378  C           they are not algorithmically
378  C           are not used.  C           are not used.
379        DO j=jMin,jMax        DO j=jMin,jMax
380         DO i=iMin,iMax         DO i=iMin,iMax
381  C    &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)  #define _recip_VolT1(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
382  C    &   -_rhFacC(i,j,k,bi,bj)*rdzF(k)/_zA(i,j,bi,bj)  #define _recip_VolT2(i,j,k,bi,bj) /_rA(i,j,bi,bj)
 C #define _rVolT(i,j,k,bi,bj) _rhFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)  
 #define _rVolT(i,j,k,bi,bj) _rhFacC(i,j,k,bi,bj)*rdzF(k)/_zA(i,j,bi,bj)  
383          gT(i,j,k,bi,bj)=          gT(i,j,k,bi,bj)=
384       &   -_rVolT(i,j,k,bi,bj)       &   -_recip_VolT1(i,j,k,bi,bj)
385         &    _recip_VolT2(i,j,k,bi,bj)
386       &   *(       &   *(
387       &    +( fZon(i+1,j)-fZon(i,j) )       &    +( fZon(i+1,j)-fZon(i,j) )
388       &    +( fMer(i,j+1)-fMer(i,j) )       &    +( fMer(i,j+1)-fMer(i,j) )
389       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
390       &    )       &    )
391         ENDDO         ENDDO
392        ENDDO        ENDDO
393    
394    #ifdef INCLUDE_T_FORCING_CODE
395  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
396  C     o Surface relaxation term        CALL EXTERNAL_FORCING_T(
397        IF ( TOP_LAYER ) THEN       I     iMin,iMax,jMin,jMax,bi,bj,k,
398         DO j=jMin,jMax       I     maskC,
399          DO i=iMin,iMax       I     myCurrentTime,myThid)
400           gT(i,j,k,bi,bj)=gT(i,j,k,bi,bj)  #endif /*  INCLUDE_T_FORCING_CODE */
401       &   -lambdaThetaClimRelax*(theta(i,j,k,bi,bj)-thetaClim(i,j,k,bi,bj))  
402          ENDDO  #ifdef INCLUDE_LAT_CIRC_FFT_FILTER_CODE
403         ENDDO  C--   Zonal FFT filter of tendency
404        ENDIF        CALL FILTER_LATCIRCS_FFT_APPLY(
405         U     gT,
406         I     1, sNy, k, k, bi, bj, 1, myThid)
407    #endif /* INCLUDE_LAT_CIRC_FFT_FILTER_CODE */
408    
409    
410        RETURN        RETURN
411        END        END

Legend:
Removed from v.1.11  
changed lines
  Added in v.1.24

  ViewVC Help
Powered by ViewVC 1.1.22