/[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.6 by cnh, Thu May 28 03:34:52 1998 UTC revision 1.23 by adcroft, Fri Mar 24 16:03:03 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,K33,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 42  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    #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 51  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 68  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 K33   (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 ==
93  C     I, J, K - Loop counters  C     I, J, K - Loop counters
94        INTEGER i,j        INTEGER i,j
95          LOGICAL TOP_LAYER
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        afFacT = 1. _d 0        afFacT = 1. _d 0
108        dfFacT = 1. _d 0        dfFacT = 1. _d 0
109          TOP_LAYER = K .EQ. 1
110    
111  C---  Calculate advective and diffusive fluxes between cells.  C---  Calculate advective and diffusive fluxes between cells.
112    
113    #ifdef INCLUDE_T_DIFFUSION_CODE
114    C     o Zonal tracer gradient
115          DO j=1-Oly,sNy+Oly
116           DO i=1-Olx+1,sNx+Olx
117            dTdx(i,j) = _recip_dxC(i,j,bi,bj)*
118         &  (theta(i,j,k,bi,bj)-theta(i-1,j,k,bi,bj))
119           ENDDO
120          ENDDO
121    C     o Meridional tracer gradient
122          DO j=1-Oly+1,sNy+Oly
123           DO i=1-Olx,sNx+Olx
124            dTdy(i,j) = _recip_dyC(i,j,bi,bj)*
125         &  (theta(i,j,k,bi,bj)-theta(i,j-1,k,bi,bj))
126           ENDDO
127          ENDDO
128    
129    C--   del^2 of T, needed for bi-harmonic (del^4) term
130          IF (diffK4T .NE. 0.) THEN
131           DO j=1-Oly+1,sNy+Oly-1
132            DO i=1-Olx+1,sNx+Olx-1
133             df4(i,j)= _recip_hFacC(i,j,k,bi,bj)
134         &             *recip_drF(k)/_rA(i,j,bi,bj)
135         &            *(
136         &             +( xA(i+1,j)*dTdx(i+1,j)-xA(i,j)*dTdx(i,j) )
137         &             +( yA(i,j+1)*dTdy(i,j+1)-yA(i,j)*dTdy(i,j) )
138         &             )
139            ENDDO
140           ENDDO
141          ENDIF
142    #endif
143    
144  C--   Zonal flux (fZon is at west face of "theta" cell)  C--   Zonal flux (fZon is at west face of "theta" cell)
145  C     Advective component of zonal flux  #ifdef INCLUDE_T_ADVECTION_CODE
146    C     o Advective component of zonal flux
147        DO j=jMin,jMax        DO j=jMin,jMax
148         DO i=iMin,iMax         DO i=iMin,iMax
149          af(i,j) =          af(i,j) =
150       &   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
151         ENDDO         ENDDO
152        ENDDO        ENDDO
153  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
154        DO j=jMin,jMax  #ifdef INCLUDE_T_DIFFUSION_CODE
155         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  
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-1,j)))*          df(i,j) = -(diffKhT+0.5*(KapGM(i,j)+KapGM(i-1,j)))*
159       &            xA(i,j)*dTdx(i,j)       &            xA(i,j)*dTdx(i,j)
160         ENDDO         ENDDO
161        ENDDO        ENDDO
162  C     Net zonal flux  C     o Add the bi-harmonic contribution
163        DO j=jMin,jMax        IF (diffK4T .NE. 0.) THEN
164         DO i=iMin,iMax         DO j=jMin,jMax
165          fZon(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          DO i=iMin,iMax
166             df(i,j) = df(i,j) + xA(i,j)*
167         &    diffK4T*(df4(i,j)-df4(i-1,j))*_recip_dxC(i,j,bi,bj)
168            ENDDO
169           ENDDO
170          ENDIF
171    #endif /* INCLUDE_T_DIFFUSION_CODE */
172    C     o Net zonal flux
173          DO j=jMin,jMax
174           DO i=iMin,iMax
175            fZon(i,j) = 0.
176         & _ADT( + afFacT*af(i,j) )
177         & _LPT( + dfFacT*df(i,j) )
178         ENDDO         ENDDO
179        ENDDO        ENDDO
180    
181  C--   Meridional flux (fMer is at south face of "theta" cell)  C--   Meridional flux (fMer is at south face of "theta" cell)
182  C     Advective component of meridional flux  #ifdef INCLUDE_T_ADVECTION_CODE
183    C     o Advective component of meridional flux
184        DO j=jMin,jMax        DO j=jMin,jMax
185         DO i=iMin,iMax         DO i=iMin,iMax
 C       Advective component of meridional flux  
186          af(i,j) =          af(i,j) =
187       &   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
188         ENDDO         ENDDO
189        ENDDO        ENDDO
190  C     Zonal tracer gradient  #endif /* INCLUDE_T_ADVECTION_CODE */
191        DO j=jMin,jMax  #ifdef INCLUDE_T_DIFFUSION_CODE
192         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  
193        DO j=jMin,jMax        DO j=jMin,jMax
194         DO i=iMin,iMax         DO i=iMin,iMax
195          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)))*
196       &            yA(i,j)*dTdy(i,j)       &            yA(i,j)*dTdy(i,j)
197         ENDDO         ENDDO
198        ENDDO        ENDDO
199  C     Net meridional flux  C     o Add the bi-harmonic contribution
200          IF (diffK4T .NE. 0.) THEN
201           DO j=jMin,jMax
202            DO i=iMin,iMax
203             df(i,j) = df(i,j) + yA(i,j)*
204         &    diffK4T*(df4(i,j)-df4(i,j-1))*_recip_dyC(i,j,bi,bj)
205            ENDDO
206           ENDDO
207          ENDIF
208    #endif /* INCLUDE_T_DIFFUSION_CODE */
209    C     o Net meridional flux
210        DO j=jMin,jMax        DO j=jMin,jMax
211         DO i=iMin,iMax         DO i=iMin,iMax
212          fMer(i,j) = afFacT*af(i,j) + dfFacT*df(i,j)          fMer(i,j) = 0.
213         & _ADT( + afFacT*af(i,j) )
214         & _LPT( + dfFacT*df(i,j) )
215         ENDDO         ENDDO
216        ENDDO        ENDDO
217    
218  C--   Interpolate terms for Redi/GM scheme  #ifdef INCLUDE_T_DIFFUSION_CODE
219    C--   Terms that diffusion tensor projects onto z
220        DO j=jMin,jMax        DO j=jMin,jMax
221         DO i=iMin,iMax         DO i=iMin,iMax
222          dTdx(i,j) = 0.5*(          dTdx(i,j) = 0.5*(
223       &   +0.5*(maskW(i+1,j,k,bi,bj)*_rdxC(i+1,j,bi,bj)*       &   +0.5*(_maskW(i+1,j,k,bi,bj)
224         &         *_recip_dxC(i+1,j,bi,bj)*
225       &           (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))
226       &        +maskW(i,j,k,bi,bj)*_rdxC(i,j,bi,bj)*       &        +_maskW(i,j,k,bi,bj)
227         &         *_recip_dxC(i,j,bi,bj)*
228       &           (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)))
229       &   +0.5*(maskW(i+1,j,km1,bi,bj)*_rdxC(i+1,j,bi,bj)*       &   +0.5*(_maskW(i+1,j,km1,bi,bj)
230         &         *_recip_dxC(i+1,j,bi,bj)*
231       &           (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))
232       &        +maskW(i,j,km1,bi,bj)*_rdxC(i,j,bi,bj)*       &        +_maskW(i,j,km1,bi,bj)
233         &         *_recip_dxC(i,j,bi,bj)*
234       &           (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)))
235       &       )       &       )
236         ENDDO         ENDDO
# Line 170  C--   Interpolate terms for Redi/GM sche Line 238  C--   Interpolate terms for Redi/GM sche
238        DO j=jMin,jMax        DO j=jMin,jMax
239         DO i=iMin,iMax         DO i=iMin,iMax
240          dTdy(i,j) = 0.5*(          dTdy(i,j) = 0.5*(
241       &   +0.5*(maskS(i,j,k,bi,bj)*_rdyC(i,j,bi,bj)*       &   +0.5*(_maskS(i,j,k,bi,bj)
242         &         *_recip_dyC(i,j,bi,bj)*
243       &           (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))
244       &        +maskS(i,j+1,k,bi,bj)*_rdyC(i,j+1,bi,bj)*       &        +_maskS(i,j+1,k,bi,bj)
245         &         *_recip_dyC(i,j+1,bi,bj)*
246       &           (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)))
247       &   +0.5*(maskS(i,j,km1,bi,bj)*_rdyC(i,j,bi,bj)*       &   +0.5*(_maskS(i,j,km1,bi,bj)
248         &         *_recip_dyC(i,j,bi,bj)*
249       &           (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))
250       &        +maskS(i,j+1,km1,bi,bj)*_rdyC(i,j+1,bi,bj)*       &        +_maskS(i,j+1,km1,bi,bj)
251         &         *_recip_dyC(i,j+1,bi,bj)*
252       &           (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)))
253       &       )       &       )
254         ENDDO         ENDDO
255        ENDDO        ENDDO
256    #endif /* INCLUDE_T_DIFFUSION_CODE */
257    
258  C--   Vertical flux (fVerT) above  C--   Vertical flux ( fVerT(,,kUp) is at upper face of "theta" cell )
259  C     Advective component of vertical flux  #ifdef INCLUDE_T_ADVECTION_CODE
260    C     o Advective component of vertical flux
261  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
262  C     (this plays the role of the free-surface correction)  C     (this plays the role of the free-surface correction)
263        DO j=jMin,jMax        DO j=jMin,jMax
264         DO i=iMin,iMax         DO i=iMin,iMax
265          af(i,j) =          af(i,j) =
266       &   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
267         ENDDO         ENDDO
268        ENDDO        ENDDO
269  C     Diffusive component of vertical flux  #endif /* INCLUDE_T_ADVECTION_CODE */
270  C     Note: For K=1 then KM1=1 this gives a dT/dz = 0 upper  #ifdef INCLUDE_T_DIFFUSION_CODE
271    C     o Diffusive component of vertical flux
272    C     Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
273  C           boundary condition.  C           boundary condition.
274        DO j=jMin,jMax        DO j=jMin,jMax
275         DO i=iMin,iMax         DO i=iMin,iMax
276          df(i,j) = zA(i,j,bi,bj)*(          df(i,j) = _rA(i,j,bi,bj)*(
      &   -(diffKzT+KapGM(i,j)*K33(i,j,k))*rdzC(k)  
      &   *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))  
277       &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)       &   -KapGM(i,j)*K13(i,j,k)*dTdx(i,j)
278       &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)       &   -KapGM(i,j)*K23(i,j,k)*dTdy(i,j)
279       &   )       &   )
280         ENDDO         ENDDO
281        ENDDO        ENDDO
282  C     Net vertical flux        IF (.NOT.implicitDiffusion) THEN
283        DO j=jMin,jMax         DO j=jMin,jMax
284         DO i=iMin,iMax          DO i=iMin,iMax
285          fVerT(i,j,kUp) = (afFacT*af(i,j) + dfFacT*df(i,j))*maskUp(i,j)           df(i,j) = df(i,j) + _rA(i,j,bi,bj)*(
286         &    -KappaRT(i,j,k)*recip_drC(k)
287         &    *(theta(i,j,kM1,bi,bj)-theta(i,j,k,bi,bj))*rkFac
288         &    )
289            ENDDO
290         ENDDO         ENDDO
291        ENDDO        ENDIF
292    #endif /* INCLUDE_T_DIFFUSION_CODE */
293    
294    #ifdef ALLOW_KPP
295          IF (usingKPPmixing) THEN
296    C--   Compute fraction of solar short-wave flux penetrating to
297    C     the bottom of the mixing layer
298           DO j=jMin,jMax
299            DO i=iMin,iMax
300             hbl(i,j) = KPPhbl(i,j,bi,bj)
301            ENDDO
302           ENDDO
303           j=(sNx+2*OLx)*(sNy+2*OLy)
304           jwtype = 3
305           negone = -1.
306           CALL SWFRAC(
307         I     j, negone, hbl, jwtype,
308         O     frac )
309    
310    C     Add non local transport coefficient (ghat term) to right-hand-side
311    C     The nonlocal transport term is noNrero only for scalars in unstable
312    C     (convective) forcing conditions.
313    C     Note: -[Qnet * delZ(1) + Qsw * (1-frac) / KPPhbl] * 4000 * rho
314    C     is the total heat flux
315    C     penetrating the mixed layer from the surface in (deg C / s)
316           IF ( TOP_LAYER ) THEN
317            DO j=jMin,jMax
318             DO i=iMin,iMax
319              df(i,j) = df(i,j) + _rA(i,j,bi,bj) *
320         &           ( Qnet(i,j,bi,bj) * delZ(1) +
321         &           Qsw(i,j,bi,bj) * (1.-frac(i,j))
322         &           / KPPhbl(i,j,bi,bj) ) *
323         &           ( KappaRT(i,j,k) * KPPghat(i,j,k,  bi,bj) )
324             ENDDO
325            ENDDO
326           ELSE
327            DO j=jMin,jMax
328             DO i=iMin,iMax
329              df(i,j) = df(i,j) + _rA(i,j,bi,bj) *
330         &           ( Qnet(i,j,bi,bj) * delZ(1) +
331         &           Qsw(i,j,bi,bj)  * (1.-frac(i,j))
332         &           / KPPhbl(i,j,bi,bj) ) *
333         &           ( KappaRT(i,j,k)   * KPPghat(i,j,k,  bi,bj)
334         &           - KappaRT(i,j,k-1) * KPPghat(i,j,k-1,bi,bj) )
335             ENDDO
336            ENDDO
337           ENDIF
338          ENDIF
339    #endif /* ALLOW_KPP */
340    
341    C     o Net vertical flux
342          DO j=jMin,jMax
343           DO i=iMin,iMax
344            fVerT(i,j,kUp) = 0.
345         & _ADT( +afFacT*af(i,j)*maskUp(i,j) )
346         & _LPT( +dfFacT*df(i,j)*maskUp(i,j) )
347           ENDDO
348          ENDDO
349    #ifdef INCLUDE_T_ADVECTION_CODE
350          IF ( TOP_LAYER ) THEN
351           DO j=jMin,jMax
352            DO i=iMin,iMax
353             fVerT(i,j,kUp) = afFacT*af(i,j)*freeSurfFac
354            ENDDO
355           ENDDO
356          ENDIF
357    #endif /* INCLUDE_T_ADVECTION_CODE */
358    
359  C--   Tendency is minus divergence of the fluxes.  C--   Tendency is minus divergence of the fluxes.
360  C     Note. Tendency terms will only be correct for range  C     Note. Tendency terms will only be correct for range
# Line 220  C           they are not algorithmically Line 364  C           they are not algorithmically
364  C           are not used.  C           are not used.
365        DO j=jMin,jMax        DO j=jMin,jMax
366         DO i=iMin,iMax         DO i=iMin,iMax
367    #define _recip_VolT1(i,j,k,bi,bj) _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
368    #define _recip_VolT2(i,j,k,bi,bj) /_rA(i,j,bi,bj)
369          gT(i,j,k,bi,bj)=          gT(i,j,k,bi,bj)=
370       &   -rHFacC(i,j,k,bi,bj)*rdzF(k)*_rdxF(i,j,bi,bj)*_rdyF(i,j,bi,bj)       &   -_recip_VolT1(i,j,k,bi,bj)
371         &    _recip_VolT2(i,j,k,bi,bj)
372       &   *(       &   *(
373       &    +( fZon(i+1,j)-fZon(i,j) )       &    +( fZon(i+1,j)-fZon(i,j) )
374       &    +( fMer(i,j+1)-fMer(i,j) )       &    +( fMer(i,j+1)-fMer(i,j) )
375       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )       &    +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
376       &    )       &    )
377         ENDDO         ENDDO
378        ENDDO        ENDDO
379    
380    #ifdef INCLUDE_T_FORCING_CODE
381  C--   External thermal forcing term(s)  C--   External thermal forcing term(s)
382          CALL EXTERNAL_FORCING_T(
383         I     iMin,iMax,jMin,jMax,bi,bj,k,
384         I     maskC,
385         I     myCurrentTime,myThid)
386    #endif /*  INCLUDE_T_FORCING_CODE */
387    
388    #ifdef INCLUDE_LAT_CIRC_FFT_FILTER_CODE
389    C--   Zonal FFT filter of tendency
390          CALL FILTER_LATCIRCS_FFT_APPLY(
391         U     gT,
392         I     1, sNy, k, k, bi, bj, 1, myThid)
393    #endif /* INCLUDE_LAT_CIRC_FFT_FILTER_CODE */
394    
395    
396        RETURN        RETURN
397        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22