/[MITgcm]/MITgcm/pkg/longstep/longstep_thermodynamics.F
ViewVC logotype

Contents of /MITgcm/pkg/longstep/longstep_thermodynamics.F

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


Revision 1.5 - (show annotations) (download)
Tue Jun 7 22:21:25 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62z
Changes since 1.4: +2 -2 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/pkg/longstep/longstep_thermodynamics.F,v 1.4 2010/11/18 00:38:55 jmc Exp $
2 C $Name: $
3
4 #include "LONGSTEP_OPTIONS.h"
5
6 #ifdef ALLOW_AUTODIFF_TAMC
7 # ifdef ALLOW_GMREDI
8 # include "GMREDI_OPTIONS.h"
9 # endif
10 #endif /* ALLOW_AUTODIFF_TAMC */
11
12 CBOP
13 C !ROUTINE: LONGSTEP_THERMODYNAMICS
14 C !INTERFACE:
15 SUBROUTINE LONGSTEP_THERMODYNAMICS(myTime, myIter, myThid)
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | SUBROUTINE LONGSTEP_THERMODYNAMICS
19 C | o Controlling routine for the prognostics of passive tracers
20 C | with longer time step.
21 C *===========================================================
22 C | This is a copy of THERMODYNAMICS, but only with the
23 C | parts relevant to ptracers, and dynamics fields replaced
24 C | by their longstep averages.
25 C | When THERMODYNAMICS is changed, this routine probably has
26 C | to be changed too :(
27 C *==========================================================*
28 C \ev
29
30 C !USES:
31 IMPLICIT NONE
32 C == Global variables ===
33 #include "SIZE.h"
34 #include "EEPARAMS.h"
35 #include "PARAMS.h"
36 #include "RESTART.h"
37 #include "DYNVARS.h"
38 #include "GRID.h"
39 #ifdef ALLOW_GENERIC_ADVDIFF
40 # include "GAD.h"
41 #endif
42 #include "LONGSTEP_PARAMS.h"
43 #include "LONGSTEP.h"
44 #ifdef ALLOW_PTRACERS
45 # include "PTRACERS_SIZE.h"
46 # include "PTRACERS_PARAMS.h"
47 # include "PTRACERS_FIELDS.h"
48 #endif
49 #ifdef ALLOW_TIMEAVE
50 # include "TIMEAVE_STATV.h"
51 #endif
52
53 #ifdef ALLOW_AUTODIFF_TAMC
54 # include "tamc.h"
55 # include "tamc_keys.h"
56 # include "FFIELDS.h"
57 # include "SURFACE.h"
58 # include "EOS.h"
59 # ifdef ALLOW_GMREDI
60 # include "GMREDI.h"
61 # endif
62 # ifdef ALLOW_EBM
63 # include "EBM.h"
64 # endif
65 #endif /* ALLOW_AUTODIFF_TAMC */
66
67 C !INPUT/OUTPUT PARAMETERS:
68 C == Routine arguments ==
69 C myTime - Current time in simulation
70 C myIter - Current iteration number in simulation
71 C myThid - Thread number for this instance of the routine.
72 _RL myTime
73 INTEGER myIter
74 INTEGER myThid
75
76 #ifdef ALLOW_LONGSTEP
77 C !LOCAL VARIABLES:
78 C == Local variables
79 C xA, yA - Per block temporaries holding face areas
80 C uFld, vFld, wFld - Local copy of velocity field (3 components)
81 C uTrans, vTrans, rTrans - Per block temporaries holding flow transport
82 C o uTrans: Zonal transport
83 C o vTrans: Meridional transport
84 C o rTrans: Vertical transport
85 C rTransKp1 o vertical volume transp. at interface k+1
86 C maskUp o maskUp: land/water mask for W points
87 C fVer[STUV] o fVer: Vertical flux term - note fVer
88 C is "pipelined" in the vertical
89 C so we need an fVer for each
90 C variable.
91 C kappaRTr - Total diffusion in vertical at level k,
92 C for each passive Tracer
93 C kappaRk - Total diffusion in vertical, all levels, 1 tracer
94 C iMin, iMax - Ranges and sub-block indices on which calculations
95 C jMin, jMax are applied.
96 C bi, bj
97 C k, kup, - Index for layer above and below. kup and kDown
98 C kDown, km1 are switched with layer to be the appropriate
99 C index into fVerTerm.
100 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110 #ifdef ALLOW_PTRACERS
111 _RL fVerP (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2,PTRACERS_num)
112 _RL kappaRTr(1-Olx:sNx+Olx,1-Oly:sNy+Oly,PTRACERS_num)
113 #endif
114 _RL kappaRk (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
115 INTEGER iMin, iMax
116 INTEGER jMin, jMax
117 INTEGER bi, bj
118 INTEGER i, j
119 INTEGER k, km1, kup, kDown
120 #ifdef ALLOW_ADAMSBASHFORTH_3
121 INTEGER iterNb, m1, m2
122 #endif
123 #ifdef ALLOW_PTRACERS
124 INTEGER iTracer, ip
125 #endif
126 CEOP
127
128 #ifdef ALLOW_DEBUG
129 IF (debugMode) CALL DEBUG_ENTER('LONGSTEP_THERMODYNAMICS',myThid)
130 #endif
131
132 C time for a ptracer time step?
133 IF ( LS_doTimeStep ) THEN
134
135 #ifdef ALLOW_AUTODIFF_TAMC
136 C-- dummy statement to end declaration part
137 ikey = 1
138 itdkey = 1
139 #endif /* ALLOW_AUTODIFF_TAMC */
140
141 #ifdef ALLOW_AUTODIFF_TAMC
142 C-- HPF directive to help TAMC
143 CHPF$ INDEPENDENT
144 #endif /* ALLOW_AUTODIFF_TAMC */
145
146 DO bj=myByLo(myThid),myByHi(myThid)
147
148 #ifdef ALLOW_AUTODIFF_TAMC
149 C-- HPF directive to help TAMC
150 CHPF$ INDEPENDENT, NEW (rTrans
151 CHPF$& ,utrans,vtrans,xA,yA
152 CHPF$& )
153 # ifdef ALLOW_PTRACERS
154 CHPF$ INDEPENDENT, NEW (fVerP,kappaRTr)
155 # endif
156 #endif /* ALLOW_AUTODIFF_TAMC */
157
158 DO bi=myBxLo(myThid),myBxHi(myThid)
159
160 #ifdef ALLOW_AUTODIFF_TAMC
161 act1 = bi - myBxLo(myThid)
162 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
163 act2 = bj - myByLo(myThid)
164 max2 = myByHi(myThid) - myByLo(myThid) + 1
165 act3 = myThid - 1
166 max3 = nTx*nTy
167 act4 = ikey_dynamics - 1
168 itdkey = (act1 + 1) + act2*max1
169 & + act3*max1*max2
170 & + act4*max1*max2*max3
171 #endif /* ALLOW_AUTODIFF_TAMC */
172
173 C-- Set up work arrays with valid (i.e. not NaN) values
174 C These inital values do not alter the numerical results. They
175 C just ensure that all memory references are to valid floating
176 C point numbers. This prevents spurious hardware signals due to
177 C uninitialised but inert locations.
178
179 DO j=1-OLy,sNy+OLy
180 DO i=1-OLx,sNx+OLx
181 xA(i,j) = 0. _d 0
182 yA(i,j) = 0. _d 0
183 uTrans(i,j) = 0. _d 0
184 vTrans(i,j) = 0. _d 0
185 rTrans (i,j) = 0. _d 0
186 rTransKp1(i,j) = 0. _d 0
187 ENDDO
188 ENDDO
189
190 DO k=1,Nr
191 DO j=1-OLy,sNy+OLy
192 DO i=1-OLx,sNx+OLx
193 C This is currently also used by IVDC and Diagnostics
194 kappaRk(i,j,k) = 0. _d 0
195 ENDDO
196 ENDDO
197 ENDDO
198
199 #ifdef ALLOW_PTRACERS
200 IF ( usePTRACERS ) THEN
201 DO ip=1,PTRACERS_num
202 DO j=1-OLy,sNy+OLy
203 DO i=1-OLx,sNx+OLx
204 fVerP (i,j,1,ip) = 0. _d 0
205 fVerP (i,j,2,ip) = 0. _d 0
206 kappaRTr(i,j,ip) = 0. _d 0
207 ENDDO
208 ENDDO
209 ENDDO
210 C- set tracer tendency to zero:
211 DO iTracer=1,PTRACERS_num
212 DO k=1,Nr
213 DO j=1-OLy,sNy+OLy
214 DO i=1-OLx,sNx+OLx
215 gPTr(i,j,k,bi,bj,itracer) = 0. _d 0
216 ENDDO
217 ENDDO
218 ENDDO
219 ENDDO
220 ENDIF
221 #endif
222
223 iMin = 1-OLx
224 iMax = sNx+OLx
225 jMin = 1-OLy
226 jMax = sNy+OLy
227
228 C need to recompute surfaceForcingPtr using LS_fwFlux
229 CALL LONGSTEP_FORCING_SURF(
230 I bi, bj, iMin, iMax, jMin, jMax,
231 I myTime,myIter,myThid )
232
233 #ifdef ALLOW_AUTODIFF_TAMC
234 cph avoids recomputation of integrate_for_w
235 CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
236 #endif /* ALLOW_AUTODIFF_TAMC */
237
238 C-- Attention: by defining "SINGLE_LAYER_MODE" in CPP_OPTIONS.h
239 C-- MOST of THERMODYNAMICS will be disabled
240 #ifndef SINGLE_LAYER_MODE
241
242 #ifdef ALLOW_AUTODIFF_TAMC
243 CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
244 CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
245 CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
246 CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
247 # if ((defined ALLOW_DEPTH_CONTROL) || (defined NONLIN_FRSURF))
248 CADJ STORE gtnm1(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
249 CADJ STORE gsnm1(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
250 # endif
251 #endif /* ALLOW_AUTODIFF_TAMC */
252
253 #ifndef DISABLE_MULTIDIM_ADVECTION
254 C-- Some advection schemes are better calculated using a multi-dimensional
255 C method in the absence of any other terms and, if used, is done here.
256 C
257 C The CPP flag DISABLE_MULTIDIM_ADVECTION is currently unset in GAD_OPTIONS.h
258 C The default is to use multi-dimensinal advection for non-linear advection
259 C schemes. However, for the sake of efficiency of the adjoint it is necessary
260 C to be able to exclude this scheme to avoid excessive storage and
261 C recomputation. It *is* differentiable, if you need it.
262 C Edit GAD_OPTIONS.h and #define DISABLE_MULTIDIM_ADVECTION to
263 C disable this section of code.
264
265 C Since passive tracers are configurable separately from T,S we
266 C call the multi-dimensional method for PTRACERS regardless
267 C of whether multiDimAdvection is set or not.
268 #ifdef ALLOW_PTRACERS
269 IF ( usePTRACERS ) THEN
270 #ifdef ALLOW_DEBUG
271 IF (debugMode) CALL DEBUG_CALL('PTRACERS_ADVECTION',myThid)
272 #endif
273 CALL PTRACERS_ADVECTION(
274 I bi,bj,myTime,myIter,myThid )
275 ENDIF
276 #endif /* ALLOW_PTRACERS */
277 #endif /* DISABLE_MULTIDIM_ADVECTION */
278
279 #ifdef ALLOW_DEBUG
280 IF (debugMode) CALL DEBUG_MSG(
281 & 'ENTERING DOWNWARD K LOOP IN LONGSTEP', myThid)
282 #endif
283
284 C-- Start of thermodynamics loop
285 DO k=Nr,1,-1
286 #ifdef ALLOW_AUTODIFF_TAMC
287 C? Patrick Is this formula correct?
288 cph Yes, but I rewrote it.
289 cph Also, the kappaR? need the index and subscript k!
290 kkey = (itdkey-1)*Nr + k
291 #endif /* ALLOW_AUTODIFF_TAMC */
292
293 C-- km1 Points to level above k (=k-1)
294 C-- kup Cycles through 1,2 to point to layer above
295 C-- kDown Cycles through 2,1 to point to current layer
296
297 km1 = MAX(1,k-1)
298 kup = 1+MOD(k+1,2)
299 kDown= 1+MOD(k,2)
300
301 iMin = 1-OLx
302 iMax = sNx+OLx
303 jMin = 1-OLy
304 jMax = sNy+OLy
305
306 IF (k.EQ.Nr) THEN
307 DO j=1-Oly,sNy+Oly
308 DO i=1-Olx,sNx+Olx
309 rTransKp1(i,j) = 0. _d 0
310 ENDDO
311 ENDDO
312 ELSE
313 DO j=1-Oly,sNy+Oly
314 DO i=1-Olx,sNx+Olx
315 rTransKp1(i,j) = rTrans(i,j)
316 ENDDO
317 ENDDO
318 ENDIF
319 #ifdef ALLOW_AUTODIFF_TAMC
320 CADJ STORE rTransKp1(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
321 #endif
322
323 C-- Get temporary terms used by tendency routines :
324 C- Calculate horizontal "volume transport" through tracer cell face
325 C anelastic: uTrans,vTrans are scaled by rhoFacC (~ mass transport)
326 CALL CALC_COMMON_FACTORS (
327 I LS_uVel, LS_vVel,
328 O uFld, vFld, uTrans, vTrans, xA, yA,
329 I k,bi,bj, myThid )
330
331 C- Calculate vertical "volume transport" through tracer cell face
332 IF (k.EQ.1) THEN
333 C- Surface interface :
334 DO j=1-Oly,sNy+Oly
335 DO i=1-Olx,sNx+Olx
336 wFld(i,j) = 0. _d 0
337 maskUp(i,j) = 0. _d 0
338 rTrans(i,j) = 0. _d 0
339 ENDDO
340 ENDDO
341 ELSE
342 C- Interior interface :
343 C anelastic: rTrans is scaled by rhoFacF (~ mass transport)
344 DO j=1-Oly,sNy+Oly
345 DO i=1-Olx,sNx+Olx
346 wFld(i,j) = LS_wVel(i,j,k,bi,bj)
347 maskUp(i,j) = maskC(i,j,k-1,bi,bj)*maskC(i,j,k,bi,bj)
348 rTrans(i,j) = wFld(i,j)*rA(i,j,bi,bj)*maskUp(i,j)
349 & *deepFac2F(k)*rhoFacF(k)
350 ENDDO
351 ENDDO
352 ENDIF
353
354 #ifdef ALLOW_GMREDI
355 C-- Residual transp = Bolus transp + Eulerian transp
356 IF (useGMRedi) THEN
357 CALL GMREDI_CALC_UVFLOW(
358 U uFld, vFld, uTrans, vTrans,
359 I k, bi, bj, myThid )
360 IF (K.GE.2) THEN
361 CALL GMREDI_CALC_WFLOW(
362 U wFld, rTrans,
363 I k, bi, bj, myThid )
364 ENDIF
365 ENDIF
366 # ifdef ALLOW_AUTODIFF_TAMC
367 CADJ STORE rTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
368 CADJ STORE wfld(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
369 # ifdef GM_BOLUS_ADVEC
370 CADJ STORE ufld(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
371 CADJ STORE vfld(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
372 CADJ STORE uTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
373 CADJ STORE vTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
374 # endif
375 # endif /* ALLOW_AUTODIFF_TAMC */
376 #endif /* ALLOW_GMREDI */
377
378 iMin = 1-OLx+2
379 iMax = sNx+OLx-1
380 jMin = 1-OLy+2
381 jMax = sNy+OLy-1
382
383 C-- Calculate active tracer tendencies (gT,gS,...)
384 C and step forward storing result in gT, gS, etc.
385 C--
386 # ifdef ALLOW_AUTODIFF_TAMC
387 # if ((defined NONLIN_FRSURF) || (defined ALLOW_DEPTH_CONTROL)) && (defined ALLOW_GMREDI)
388 # ifdef GM_NON_UNITY_DIAGONAL
389 CADJ STORE kux(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
390 CADJ STORE kvy(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
391 # endif
392 # ifdef GM_EXTRA_DIAGONAL
393 CADJ STORE kuz(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
394 CADJ STORE kvz(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
395 # endif
396 # endif
397 # endif /* ALLOW_AUTODIFF_TAMC */
398 C
399 #ifdef ALLOW_AUTODIFF_TAMC
400 # if (defined NONLIN_FRSURF) || (defined ALLOW_DEPTH_CONTROL)
401 cph-test
402 CADJ STORE uFld(:,:), vFld(:,:), wFld(:,:)
403 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
404 CADJ STORE uTrans(:,:), vTrans(:,:)
405 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
406 CADJ STORE xA(:,:), yA(:,:)
407 CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
408 # endif
409 #endif /* ALLOW_AUTODIFF_TAMC */
410 C
411 #ifdef ALLOW_PTRACERS
412 IF ( usePTRACERS ) THEN
413 IF ( .NOT.implicitDiffusion ) THEN
414 CALL PTRACERS_CALC_DIFF(
415 I bi,bj,iMin,iMax,jMin,jMax,k,
416 I maskUp,
417 O kappaRTr,
418 I myThid)
419 ENDIF
420 # ifdef ALLOW_AUTODIFF_TAMC
421 CADJ STORE kappaRTr(:,:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
422 # endif /* ALLOW_AUTODIFF_TAMC */
423 CALL PTRACERS_INTEGRATE(
424 I bi,bj,k,
425 I xA, yA, maskUp, uFld, vFld, wFld,
426 I uTrans, vTrans, rTrans, rTransKp1,
427 I kappaRTr,
428 U fVerP,
429 I myTime,myIter,myThid)
430 ENDIF
431 #endif /* ALLOW_PTRACERS */
432
433 C-- end of thermodynamic k loop (Nr:1)
434 ENDDO
435
436 #ifdef ALLOW_DOWN_SLOPE
437 #ifdef ALLOW_PTRACERS
438 IF ( usePTRACERS .AND. useDOWN_SLOPE ) THEN
439 CALL PTRACERS_DWNSLP_APPLY(
440 I bi, bj, myTime, myIter, myThid )
441 ENDIF
442 #endif /* ALLOW_PTRACERS */
443 #endif /* ALLOW_DOWN_SLOPE */
444
445 C All explicit advection/diffusion/sources should now be
446 C done. The updated tracer field is in gPtr. Accumalate
447 C explicit tendency and also reset gPtr to initial tracer
448 C field for implicit matrix calculation
449
450 #ifdef ALLOW_MATRIX
451 IF (useMATRIX)
452 & CALL MATRIX_STORE_TENDENCY_EXP(bi,bj, myTime,myIter,myThid)
453 #endif
454
455 iMin = 1
456 iMax = sNx
457 jMin = 1
458 jMax = sNy
459
460 #ifdef ALLOW_PTRACERS
461 IF ( usePTRACERS ) THEN
462 C-- Vertical advection/diffusion (implicit) for passive tracers
463 CALL PTRACERS_IMPLICIT(
464 U kappaRk,
465 I bi, bj, myTime, myIter, myThid )
466 ENDIF
467 #endif /* ALLOW_PTRACERS */
468
469 #endif /* SINGLE_LAYER_MODE */
470
471 C-- end bi,bj loops.
472 ENDDO
473 ENDDO
474
475 #ifdef ALLOW_DEBUG
476 IF ( debugLevel.GE.debLevD ) THEN
477 CALL DEBUG_STATS_RL(Nr,LS_uVel,'LS_Uvel (THERMODYNAMICS)',myThid)
478 CALL DEBUG_STATS_RL(Nr,LS_vVel,'LS_Vvel (THERMODYNAMICS)',myThid)
479 CALL DEBUG_STATS_RL(Nr,LS_wVel,'LS_Wvel (THERMODYNAMICS)',myThid)
480 CALL DEBUG_STATS_RL(Nr,LS_theta,'LS_Theta (THERMODYNAMICS)',
481 & myThid)
482 CALL DEBUG_STATS_RL(Nr,LS_salt,'LS_Salt (THERMODYNAMICS)',myThid)
483 #ifdef ALLOW_PTRACERS
484 IF ( usePTRACERS ) THEN
485 CALL PTRACERS_DEBUG(myThid)
486 ENDIF
487 #endif /* ALLOW_PTRACERS */
488 ENDIF
489 #endif /* ALLOW_DEBUG */
490
491 C LS_doTimeStep
492 ENDIF
493
494 #ifdef ALLOW_DEBUG
495 IF (debugMode) CALL DEBUG_LEAVE('LONGSTEP_THERMODYNAMICS',myThid)
496 #endif
497
498 #endif /* ALLOW_LONGSTEP */
499
500 RETURN
501 END

  ViewVC Help
Powered by ViewVC 1.1.22