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

Contents of /MITgcm/model/src/thermodynamics.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.157 - (show annotations) (download)
Thu Jan 22 18:21:45 2015 UTC (9 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65j, checkpoint65k, checkpoint65i, checkpoint65l
Changes since 1.156: +23 -4 lines
- with synchronous time-stepping: move resetting to zero of frictionHeating
  field from load_fields_driver.F to thermodynamics.F ;
- add diagnostics for frictional heating.

1 C $Header: /u/gcmpack/MITgcm/model/src/thermodynamics.F,v 1.156 2014/08/18 14:26:15 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_AUTODIFF
7 # include "AUTODIFF_OPTIONS.h"
8 #endif
9 #if (defined ALLOW_PTRACERS) && (!defined ALLOW_LONGSTEP)
10 # define DO_PTRACERS_HERE
11 #endif
12
13 #ifdef ALLOW_AUTODIFF
14 # ifdef ALLOW_GMREDI
15 # include "GMREDI_OPTIONS.h"
16 # endif
17 # ifdef ALLOW_KPP
18 # include "KPP_OPTIONS.h"
19 # endif
20 #endif /* ALLOW_AUTODIFF */
21
22 CBOP
23 C !ROUTINE: THERMODYNAMICS
24 C !INTERFACE:
25 SUBROUTINE THERMODYNAMICS(myTime, myIter, myThid)
26 C !DESCRIPTION: \bv
27 C *==========================================================*
28 C | SUBROUTINE THERMODYNAMICS
29 C | o Controlling routine for the prognostic part of the
30 C | thermo-dynamics.
31 C *===========================================================
32 C \ev
33
34 C !USES:
35 IMPLICIT NONE
36 C == Global variables ===
37 #include "SIZE.h"
38 #include "EEPARAMS.h"
39 #include "PARAMS.h"
40 #include "RESTART.h"
41 #include "DYNVARS.h"
42 #include "GRID.h"
43 #include "SURFACE.h"
44 #include "FFIELDS.h"
45 #ifdef ALLOW_GENERIC_ADVDIFF
46 # include "GAD.h"
47 #endif
48 #ifdef DO_PTRACERS_HERE
49 # include "PTRACERS_SIZE.h"
50 # include "PTRACERS_PARAMS.h"
51 # include "PTRACERS_FIELDS.h"
52 #endif
53
54 #ifdef ALLOW_AUTODIFF
55 # include "tamc.h"
56 # include "tamc_keys.h"
57 # include "EOS.h"
58 # ifdef ALLOW_KPP
59 # include "KPP.h"
60 # endif
61 # ifdef ALLOW_GMREDI
62 # include "GMREDI.h"
63 # endif
64 # ifdef ALLOW_EBM
65 # include "EBM.h"
66 # endif
67 # ifdef ALLOW_SALT_PLUME
68 # include "SALT_PLUME.h"
69 # endif
70 #endif /* ALLOW_AUTODIFF */
71
72 C !INPUT/OUTPUT PARAMETERS:
73 C == Routine arguments ==
74 C myTime :: Current time in simulation
75 C myIter :: Current iteration number in simulation
76 C myThid :: Thread number for this instance of the routine.
77 _RL myTime
78 INTEGER myIter
79 INTEGER myThid
80
81 #ifdef ALLOW_GENERIC_ADVDIFF
82 C !LOCAL VARIABLES:
83 C == Local variables
84 C uFld,vFld,wFld :: Local copy of velocity field (3 components)
85 C kappaRk :: Total diffusion in vertical, all levels, 1 tracer
86 C recip_hFacNew :: reciprocal of futur time-step hFacC
87 C bi, bj :: Tile indices
88 C i, j, k :: loop indices
89 C iterNb :: iteration number when this time-step started
90 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
91 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
92 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
93 _RL kappaRk (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
94 _RS recip_hFacNew(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
95 INTEGER bi, bj
96 INTEGER i, j, k
97 INTEGER iterNb
98 CEOP
99
100 #ifdef ALLOW_DEBUG
101 IF (debugMode) CALL DEBUG_ENTER('THERMODYNAMICS',myThid)
102 #endif
103
104 iterNb = myIter
105 IF (staggerTimeStep) iterNb = myIter - 1
106
107 #ifdef ALLOW_AUTODIFF_TAMC
108 C-- dummy statement to end declaration part
109 ikey = 1
110 itdkey = 1
111 #endif /* ALLOW_AUTODIFF_TAMC */
112
113 #ifdef ALLOW_AUTODIFF_TAMC
114 C-- HPF directive to help TAMC
115 CHPF$ INDEPENDENT
116 #endif /* ALLOW_AUTODIFF_TAMC */
117
118 C-- Compute correction at the surface for Lin Free Surf.
119 #ifdef ALLOW_AUTODIFF
120 TsurfCor = 0. _d 0
121 SsurfCor = 0. _d 0
122 #endif
123 IF ( linFSConserveTr ) THEN
124 #ifdef ALLOW_AUTODIFF_TAMC
125 CADJ STORE theta,salt,wvel = comlev1, key = ikey_dynamics, byte=isbyte
126 #endif
127 CALL CALC_WSURF_TR( theta, salt, wVel,
128 & myTime, myIter, myThid )
129 ENDIF
130
131 #ifdef DO_PTRACERS_HERE
132 IF ( PTRACERS_calcSurfCor ) THEN
133 CALL PTRACERS_CALC_WSURF_TR(wVel,myTime,myIter,myThid)
134 ENDIF
135 #endif
136
137 DO bj=myByLo(myThid),myByHi(myThid)
138 DO bi=myBxLo(myThid),myBxHi(myThid)
139
140 #ifdef ALLOW_AUTODIFF_TAMC
141 act1 = bi - myBxLo(myThid)
142 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
143 act2 = bj - myByLo(myThid)
144 max2 = myByHi(myThid) - myByLo(myThid) + 1
145 act3 = myThid - 1
146 max3 = nTx*nTy
147 act4 = ikey_dynamics - 1
148 itdkey = (act1 + 1) + act2*max1
149 & + act3*max1*max2
150 & + act4*max1*max2*max3
151 #endif /* ALLOW_AUTODIFF_TAMC */
152
153 C-- Set up work arrays with valid (i.e. not NaN) values
154 C These inital values do not alter the numerical results. They
155 C just ensure that all memory references are to valid floating
156 C point numbers. This prevents spurious hardware signals due to
157 C uninitialised but inert locations.
158
159 DO k=1,Nr
160 DO j=1-OLy,sNy+OLy
161 DO i=1-OLx,sNx+OLx
162 recip_hFacNew(i,j,k) = 0. _d 0
163 C This is currently also used by IVDC and Diagnostics
164 kappaRk(i,j,k) = 0. _d 0
165 ENDDO
166 ENDDO
167 ENDDO
168
169 C-- Compute new reciprocal hFac for implicit calculation
170 #ifdef NONLIN_FRSURF
171 IF ( nonlinFreeSurf.GT.0 ) THEN
172 IF ( select_rStar.GT.0 ) THEN
173 # ifndef DISABLE_RSTAR_CODE
174 DO k=1,Nr
175 DO j=1-OLy,sNy+OLy
176 DO i=1-OLx,sNx+OLx
177 recip_hFacNew(i,j,k) = recip_hFacC(i,j,k,bi,bj)
178 & / rStarExpC(i,j,bi,bj)
179 ENDDO
180 ENDDO
181 ENDDO
182 # endif /* DISABLE_RSTAR_CODE */
183 ELSEIF ( selectSigmaCoord.NE.0 ) THEN
184 # ifndef DISABLE_SIGMA_CODE
185 DO k=1,Nr
186 DO j=1-OLy,sNy+OLy
187 DO i=1-OLx,sNx+OLx
188 recip_hFacNew(i,j,k) = recip_hFacC(i,j,k,bi,bj)
189 & /( 1. _d 0 + dEtaHdt(i,j,bi,bj)*deltaTFreeSurf
190 & *dBHybSigF(k)*recip_drF(k)
191 & *recip_hFacC(i,j,k,bi,bj)
192 & )
193 ENDDO
194 ENDDO
195 ENDDO
196 # endif /* DISABLE_RSTAR_CODE */
197 ELSE
198 DO k=1,Nr
199 DO j=1-OLy,sNy+OLy
200 DO i=1-OLx,sNx+OLx
201 IF ( k.EQ.kSurfC(i,j,bi,bj) ) THEN
202 recip_hFacNew(i,j,k) = 1. _d 0 / hFac_surfC(i,j,bi,bj)
203 ELSE
204 recip_hFacNew(i,j,k) = recip_hFacC(i,j,k,bi,bj)
205 ENDIF
206 ENDDO
207 ENDDO
208 ENDDO
209 ENDIF
210 ELSE
211 #endif /* NONLIN_FRSURF */
212 DO k=1,Nr
213 DO j=1-OLy,sNy+OLy
214 DO i=1-OLx,sNx+OLx
215 recip_hFacNew(i,j,k) = _recip_hFacC(i,j,k,bi,bj)
216 ENDDO
217 ENDDO
218 ENDDO
219 #ifdef NONLIN_FRSURF
220 ENDIF
221 #endif /* NONLIN_FRSURF */
222
223 C-- Set up 3-D velocity field that we use to advect tracers:
224 C- just do a local copy:
225 DO k=1,Nr
226 DO j=1-OLy,sNy+OLy
227 DO i=1-OLx,sNx+OLx
228 uFld(i,j,k) = uVel(i,j,k,bi,bj)
229 vFld(i,j,k) = vVel(i,j,k,bi,bj)
230 wFld(i,j,k) = wVel(i,j,k,bi,bj)
231 ENDDO
232 ENDDO
233 ENDDO
234 #ifdef ALLOW_GMREDI
235 C- add Bolus velocity to Eulerian-mean velocity:
236 IF (useGMRedi) THEN
237 CALL GMREDI_RESIDUAL_FLOW(
238 U uFld, vFld, wFld,
239 I bi, bj, myIter, myThid )
240 ENDIF
241 #endif /* ALLOW_GMREDI */
242
243 C- Apply AB on T,S : moved inside TEMP/SALT_INTEGRATE
244
245 #ifdef ALLOW_AUTODIFF_TAMC
246 CADJ STORE recip_hFacNew(:,:,:) = comlev1_bibj , key=itdkey, byte=isbyte
247 CADJ STORE uFld (:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
248 CADJ STORE vFld (:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
249 CADJ STORE wFld (:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
250 CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
251 CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
252 # ifdef ALLOW_SALT_PLUME
253 CADJ STORE saltPlumeFlux(:,:,bi,bj) =
254 CADJ & comlev1_bibj, key=itdkey,kind = isbyte
255 CADJ STORE saltPlumeDepth(:,:,bi,bj) =
256 CADJ & comlev1_bibj, key=itdkey,kind = isbyte
257 # endif
258 # if ((defined NONLIN_FRSURF) || (defined ALLOW_DEPTH_CONTROL)) && (defined ALLOW_GMREDI)
259 # ifdef GM_NON_UNITY_DIAGONAL
260 CADJ STORE kux(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
261 CADJ STORE kvy(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
262 # endif
263 # ifdef GM_EXTRA_DIAGONAL
264 CADJ STORE kuz(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
265 CADJ STORE kvz(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
266 # endif
267 # endif
268 #endif /* ALLOW_AUTODIFF_TAMC */
269
270 C-- Calculate active tracer tendencies and step forward in time.
271 C Active tracer arrays are updated while adjustments (filters,
272 C conv.adjustment) are applied later in TRACERS_CORRECTION_STEP.
273
274 IF ( tempStepping ) THEN
275 #ifdef ALLOW_DEBUG
276 IF (debugMode) CALL DEBUG_CALL('TEMP_INTEGRATE',myThid)
277 #endif
278 CALL TEMP_INTEGRATE(
279 I bi, bj, recip_hFacNew,
280 I uFld, vFld, wFld,
281 U kappaRk,
282 I myTime, myIter, myThid )
283 ENDIF
284
285 IF ( saltStepping ) THEN
286 #ifdef ALLOW_DEBUG
287 IF (debugMode) CALL DEBUG_CALL('SALT_INTEGRATE',myThid)
288 #endif
289 CALL SALT_INTEGRATE(
290 I bi, bj, recip_hFacNew,
291 I uFld, vFld, wFld,
292 U kappaRk,
293 I myTime, myIter, myThid )
294 ENDIF
295
296 #ifdef DO_PTRACERS_HERE
297 C-- Calculate passive tracer tendencies and step forward in time.
298 C Passive tracer arrays are updated while adjustments (filters,
299 C conv.adjustment) are applied later in TRACERS_CORRECTION_STEP.
300 C Also apply open boundary conditions for each passive tracer
301 IF ( usePTRACERS ) THEN
302 #ifdef ALLOW_DEBUG
303 IF (debugMode) CALL DEBUG_CALL('PTRACERS_INTEGRATE',myThid)
304 #endif
305 CALL PTRACERS_INTEGRATE(
306 I bi, bj, recip_hFacNew,
307 I uFld, vFld, wFld,
308 U kappaRk,
309 I myTime, myIter, myThid )
310 ENDIF
311 #endif /* DO_PTRACERS_HERE */
312
313 #ifdef ALLOW_OBCS
314 C-- Apply open boundary conditions
315 IF ( useOBCS ) THEN
316 CALL OBCS_APPLY_TS( bi, bj, 0, theta, salt, myThid )
317 ENDIF
318 #endif /* ALLOW_OBCS */
319
320 #ifdef ALLOW_FRICTION_HEATING
321 #ifdef ALLOW_DIAGNOSTICS
322 IF ( addFrictionHeating .AND. useDiagnostics ) THEN
323 CALL DIAGNOSTICS_FILL_RS( frictionHeating, 'HeatDiss',
324 & 0, Nr, 1, bi, bj, myThid )
325 ENDIF
326 #endif /* ALLOW_DIAGNOSTICS */
327 C- Reset frictionHeating to zero
328 IF ( addFrictionHeating .AND. .NOT.staggerTimeStep ) THEN
329 DO k=1,Nr
330 DO j=1-OLy,sNy+OLy
331 DO i=1-OLx,sNx+OLx
332 frictionHeating(i,j,k,bi,bj) = 0. _d 0
333 ENDDO
334 ENDDO
335 ENDDO
336 ENDIF
337 #endif /* ALLOW_FRICTION_HEATING */
338
339 C-- end bi,bj loops.
340 ENDDO
341 ENDDO
342
343 #ifdef ALLOW_DEBUG
344 IF ( debugLevel.GE.debLevD ) THEN
345 CALL DEBUG_STATS_RL(Nr,uVel,'Uvel (THERMODYNAMICS)',myThid)
346 CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (THERMODYNAMICS)',myThid)
347 CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (THERMODYNAMICS)',myThid)
348 CALL DEBUG_STATS_RL(Nr,theta,'Theta (THERMODYNAMICS)',myThid)
349 CALL DEBUG_STATS_RL(Nr,salt,'Salt (THERMODYNAMICS)',myThid)
350 #ifndef ALLOW_ADAMSBASHFORTH_3
351 CALL DEBUG_STATS_RL(Nr,gtNm1,'GtNm1 (THERMODYNAMICS)',myThid)
352 CALL DEBUG_STATS_RL(Nr,gsNm1,'GsNm1 (THERMODYNAMICS)',myThid)
353 #endif
354 #ifdef DO_PTRACERS_HERE
355 IF ( usePTRACERS ) THEN
356 CALL PTRACERS_DEBUG(myThid)
357 ENDIF
358 #endif /* DO_PTRACERS_HERE */
359 ENDIF
360 #endif /* ALLOW_DEBUG */
361
362 #ifdef ALLOW_DEBUG
363 IF (debugMode) CALL DEBUG_LEAVE('THERMODYNAMICS',myThid)
364 #endif
365
366 #endif /* ALLOW_GENERIC_ADVDIFF */
367
368 RETURN
369 END

  ViewVC Help
Powered by ViewVC 1.1.22