/[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.49 - (show annotations) (download)
Thu Oct 2 21:33:54 2003 UTC (20 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51h_pre, checkpoint51g_post
Changes since 1.48: +2 -8 lines
Bringing code up to date for AD
o remove some IF-statements which cause excessive dependencies
o provide interface for ADM*TLM

1 C $Header: /u/gcmpack/MITgcm/model/src/thermodynamics.F,v 1.48 2003/09/25 03:01:59 dimitri Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF_TAMC
6 # ifdef ALLOW_GMREDI
7 # include "GMREDI_OPTIONS.h"
8 # endif
9 # ifdef ALLOW_KPP
10 # include "KPP_OPTIONS.h"
11 # endif
12 #ifdef ALLOW_PTRACERS
13 # include "PTRACERS_OPTIONS.h"
14 #endif
15 #endif /* ALLOW_AUTODIFF_TAMC */
16
17 CBOP
18 C !ROUTINE: THERMODYNAMICS
19 C !INTERFACE:
20 SUBROUTINE THERMODYNAMICS(myTime, myIter, myThid)
21 C !DESCRIPTION: \bv
22 C *==========================================================*
23 C | SUBROUTINE THERMODYNAMICS
24 C | o Controlling routine for the prognostic part of the
25 C | thermo-dynamics.
26 C *===========================================================
27 C | The algorithm...
28 C |
29 C | "Correction Step"
30 C | =================
31 C | Here we update the horizontal velocities with the surface
32 C | pressure such that the resulting flow is either consistent
33 C | with the free-surface evolution or the rigid-lid:
34 C | U[n] = U* + dt x d/dx P
35 C | V[n] = V* + dt x d/dy P
36 C |
37 C | "Calculation of Gs"
38 C | ===================
39 C | This is where all the accelerations and tendencies (ie.
40 C | physics, parameterizations etc...) are calculated
41 C | rho = rho ( theta[n], salt[n] )
42 C | b = b(rho, theta)
43 C | K31 = K31 ( rho )
44 C | Gu[n] = Gu( u[n], v[n], wVel, b, ... )
45 C | Gv[n] = Gv( u[n], v[n], wVel, b, ... )
46 C | Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
47 C | Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
48 C |
49 C | "Time-stepping" or "Prediction"
50 C | ================================
51 C | The models variables are stepped forward with the appropriate
52 C | time-stepping scheme (currently we use Adams-Bashforth II)
53 C | - For momentum, the result is always *only* a "prediction"
54 C | in that the flow may be divergent and will be "corrected"
55 C | later with a surface pressure gradient.
56 C | - Normally for tracers the result is the new field at time
57 C | level [n+1} *BUT* in the case of implicit diffusion the result
58 C | is also *only* a prediction.
59 C | - We denote "predictors" with an asterisk (*).
60 C | U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )
61 C | V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )
62 C | theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
63 C | salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
64 C | With implicit diffusion:
65 C | theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
66 C | salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
67 C | (1 + dt * K * d_zz) theta[n] = theta*
68 C | (1 + dt * K * d_zz) salt[n] = salt*
69 C |
70 C *==========================================================*
71 C \ev
72
73 C !USES:
74 IMPLICIT NONE
75 C == Global variables ===
76 #include "SIZE.h"
77 #include "EEPARAMS.h"
78 #include "PARAMS.h"
79 #include "DYNVARS.h"
80 #include "GRID.h"
81 #include "GAD.h"
82 #ifdef ALLOW_PASSIVE_TRACER
83 #include "TR1.h"
84 #endif
85 #ifdef ALLOW_PTRACERS
86 #include "PTRACERS.h"
87 #endif
88 #ifdef ALLOW_TIMEAVE
89 #include "TIMEAVE_STATV.h"
90 #endif
91
92 #ifdef ALLOW_AUTODIFF_TAMC
93 # include "tamc.h"
94 # include "tamc_keys.h"
95 # include "FFIELDS.h"
96 # include "EOS.h"
97 # ifdef ALLOW_KPP
98 # include "KPP.h"
99 # endif
100 # ifdef ALLOW_GMREDI
101 # include "GMREDI.h"
102 # endif
103 #endif /* ALLOW_AUTODIFF_TAMC */
104
105 C !INPUT/OUTPUT PARAMETERS:
106 C == Routine arguments ==
107 C myTime - Current time in simulation
108 C myIter - Current iteration number in simulation
109 C myThid - Thread number for this instance of the routine.
110 _RL myTime
111 INTEGER myIter
112 INTEGER myThid
113
114 C !LOCAL VARIABLES:
115 C == Local variables
116 C xA, yA - Per block temporaries holding face areas
117 C uTrans, vTrans, rTrans - Per block temporaries holding flow
118 C transport
119 C o uTrans: Zonal transport
120 C o vTrans: Meridional transport
121 C o rTrans: Vertical transport
122 C maskUp o maskUp: land/water mask for W points
123 C fVer[STUV] o fVer: Vertical flux term - note fVer
124 C is "pipelined" in the vertical
125 C so we need an fVer for each
126 C variable.
127 C rhoK, rhoKM1 - Density at current level, and level above
128 C phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)
129 C phiSurfY or geopotentiel (atmos) in X and Y direction
130 C KappaRT, - Total diffusion in vertical for T and S.
131 C KappaRS (background + spatially varying, isopycnal term).
132 C useVariableK = T when vertical diffusion is not constant
133 C iMin, iMax - Ranges and sub-block indices on which calculations
134 C jMin, jMax are applied.
135 C bi, bj
136 C k, kup, - Index for layer above and below. kup and kDown
137 C kDown, km1 are switched with layer to be the appropriate
138 C index into fVerTerm.
139 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
140 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
141 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
142 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
143 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
144 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
145 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
146 _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
147 _RL fVerTr1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
148 _RL rhokm1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
149 _RL rhok (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
150 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
151 _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
152 _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
153 _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
154 _RL sigmaX (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
155 _RL sigmaY (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
156 _RL sigmaR (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
157 C This is currently used by IVDC and Diagnostics
158 _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
159 LOGICAL useVariableK
160 INTEGER iMin, iMax
161 INTEGER jMin, jMax
162 INTEGER bi, bj
163 INTEGER i, j
164 INTEGER k, km1, kup, kDown
165 INTEGER iTracer
166
167 CEOP
168
169 #ifndef DISABLE_DEBUGMODE
170 IF ( debugLevel .GE. debLevB )
171 & CALL DEBUG_ENTER('FORWARD_STEP',myThid)
172 #endif
173
174 #ifdef ALLOW_AUTODIFF_TAMC
175 C-- dummy statement to end declaration part
176 ikey = 1
177 itdkey = 1
178 #endif /* ALLOW_AUTODIFF_TAMC */
179
180 #ifdef ALLOW_AUTODIFF_TAMC
181 C-- HPF directive to help TAMC
182 CHPF$ INDEPENDENT
183 #endif /* ALLOW_AUTODIFF_TAMC */
184
185 DO bj=myByLo(myThid),myByHi(myThid)
186
187 #ifdef ALLOW_AUTODIFF_TAMC
188 C-- HPF directive to help TAMC
189 CHPF$ INDEPENDENT, NEW (rTrans,fVerT,fVerS
190 CHPF$& ,utrans,vtrans,xA,yA
191 CHPF$& ,KappaRT,KappaRS
192 CHPF$& )
193 #endif /* ALLOW_AUTODIFF_TAMC */
194
195 DO bi=myBxLo(myThid),myBxHi(myThid)
196
197 #ifdef ALLOW_AUTODIFF_TAMC
198 act1 = bi - myBxLo(myThid)
199 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
200 act2 = bj - myByLo(myThid)
201 max2 = myByHi(myThid) - myByLo(myThid) + 1
202 act3 = myThid - 1
203 max3 = nTx*nTy
204 act4 = ikey_dynamics - 1
205 itdkey = (act1 + 1) + act2*max1
206 & + act3*max1*max2
207 & + act4*max1*max2*max3
208 #endif /* ALLOW_AUTODIFF_TAMC */
209
210 C-- Set up work arrays with valid (i.e. not NaN) values
211 C These inital values do not alter the numerical results. They
212 C just ensure that all memory references are to valid floating
213 C point numbers. This prevents spurious hardware signals due to
214 C uninitialised but inert locations.
215
216 DO j=1-OLy,sNy+OLy
217 DO i=1-OLx,sNx+OLx
218 xA(i,j) = 0. _d 0
219 yA(i,j) = 0. _d 0
220 uTrans(i,j) = 0. _d 0
221 vTrans(i,j) = 0. _d 0
222 rhok (i,j) = 0. _d 0
223 rhoKM1 (i,j) = 0. _d 0
224 phiSurfX(i,j) = 0. _d 0
225 phiSurfY(i,j) = 0. _d 0
226 rTrans (i,j) = 0. _d 0
227 fVerT (i,j,1) = 0. _d 0
228 fVerT (i,j,2) = 0. _d 0
229 fVerS (i,j,1) = 0. _d 0
230 fVerS (i,j,2) = 0. _d 0
231 fVerTr1(i,j,1) = 0. _d 0
232 fVerTr1(i,j,2) = 0. _d 0
233 ENDDO
234 ENDDO
235
236 DO k=1,Nr
237 DO j=1-OLy,sNy+OLy
238 DO i=1-OLx,sNx+OLx
239 C This is currently also used by IVDC and Diagnostics
240 sigmaX(i,j,k) = 0. _d 0
241 sigmaY(i,j,k) = 0. _d 0
242 sigmaR(i,j,k) = 0. _d 0
243 ConvectCount(i,j,k) = 0.
244 KappaRT(i,j,k) = 0. _d 0
245 KappaRS(i,j,k) = 0. _d 0
246 C- tracer tendency needs to be set to zero (moved here from gad_calc_rhs):
247 gT(i,j,k,bi,bj) = 0. _d 0
248 gS(i,j,k,bi,bj) = 0. _d 0
249 # ifdef ALLOW_PASSIVE_TRACER
250 gTr1(i,j,k,bi,bj) = 0. _d 0
251 # endif
252 # ifdef ALLOW_PTRACERS
253 DO iTracer=1,PTRACERS_numInUse
254 gPTr(i,j,k,bi,bj,itracer) = 0. _d 0
255 ENDDO
256 # endif
257 #ifdef ALLOW_AUTODIFF_TAMC
258 cph all the following init. are necessary for TAF
259 cph although some of these are re-initialised later.
260 # ifdef ALLOW_GMREDI
261 Kwx(i,j,k,bi,bj) = 0. _d 0
262 Kwy(i,j,k,bi,bj) = 0. _d 0
263 Kwz(i,j,k,bi,bj) = 0. _d 0
264 # ifdef GM_NON_UNITY_DIAGONAL
265 Kux(i,j,k,bi,bj) = 0. _d 0
266 Kvy(i,j,k,bi,bj) = 0. _d 0
267 # endif
268 # ifdef GM_EXTRA_DIAGONAL
269 Kuz(i,j,k,bi,bj) = 0. _d 0
270 Kvz(i,j,k,bi,bj) = 0. _d 0
271 # endif
272 # ifdef GM_BOLUS_ADVEC
273 GM_PsiX(i,j,k,bi,bj) = 0. _d 0
274 GM_PsiY(i,j,k,bi,bj) = 0. _d 0
275 # endif
276 # ifdef GM_VISBECK_VARIABLE_K
277 VisbeckK(i,j,bi,bj) = 0. _d 0
278 # endif
279 # endif /* ALLOW_GMREDI */
280 #endif /* ALLOW_AUTODIFF_TAMC */
281 ENDDO
282 ENDDO
283 ENDDO
284
285 iMin = 1-OLx
286 iMax = sNx+OLx
287 jMin = 1-OLy
288 jMax = sNy+OLy
289
290 #ifdef ALLOW_AUTODIFF_TAMC
291 CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
292 CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
293 CADJ STORE totphihyd
294 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
295 #ifdef ALLOW_KPP
296 CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
297 CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
298 #endif
299 #endif /* ALLOW_AUTODIFF_TAMC */
300
301 #ifndef DISABLE_DEBUGMODE
302 IF ( debugLevel .GE. debLevB )
303 & CALL DEBUG_MSG('ENTERING UPWARD K LOOP',myThid)
304 #endif
305
306 C-- Start of diagnostic loop
307 DO k=Nr,1,-1
308
309 #ifdef ALLOW_AUTODIFF_TAMC
310 C? Patrick, is this formula correct now that we change the loop range?
311 C? Do we still need this?
312 cph kkey formula corrected.
313 cph Needed for rhok, rhokm1, in the case useGMREDI.
314 kkey = (itdkey-1)*Nr + k
315 #endif /* ALLOW_AUTODIFF_TAMC */
316
317 C-- Integrate continuity vertically for vertical velocity
318 c CALL INTEGRATE_FOR_W(
319 c I bi, bj, k, uVel, vVel,
320 c O wVel,
321 c I myThid )
322
323 #ifdef ALLOW_OBCS
324 #ifdef ALLOW_NONHYDROSTATIC
325 C-- Apply OBC to W if in N-H mode
326 c IF (useOBCS.AND.nonHydrostatic) THEN
327 c CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
328 c ENDIF
329 #endif /* ALLOW_NONHYDROSTATIC */
330 #endif /* ALLOW_OBCS */
331
332 C-- Attention: by defining "SINGLE_LAYER_MODE" in CPP_OPTIONS.h
333 C-- MOST of THERMODYNAMICS will be disabled
334 #ifndef SINGLE_LAYER_MODE
335
336 C-- Calculate gradients of potential density for isoneutral
337 C slope terms (e.g. GM/Redi tensor or IVDC diffusivity)
338 c IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN
339 IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN
340 #ifndef DISABLE_DEBUGMODE
341 IF ( debugLevel .GE. debLevB )
342 & CALL DEBUG_CALL('FIND_RHO',myThid)
343 #endif
344 #ifdef ALLOW_AUTODIFF_TAMC
345 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
346 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
347 #endif /* ALLOW_AUTODIFF_TAMC */
348 CALL FIND_RHO(
349 I bi, bj, iMin, iMax, jMin, jMax, k, k,
350 I theta, salt,
351 O rhoK,
352 I myThid )
353
354 IF (k.GT.1) THEN
355 #ifdef ALLOW_AUTODIFF_TAMC
356 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
357 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
358 #endif /* ALLOW_AUTODIFF_TAMC */
359 CALL FIND_RHO(
360 I bi, bj, iMin, iMax, jMin, jMax, k-1, k,
361 I theta, salt,
362 O rhoKm1,
363 I myThid )
364 ENDIF
365 #ifndef DISABLE_DEBUGMODE
366 IF ( debugLevel .GE. debLevB )
367 & CALL DEBUG_CALL('GRAD_SIGMA',myThid)
368 #endif
369 CALL GRAD_SIGMA(
370 I bi, bj, iMin, iMax, jMin, jMax, k,
371 I rhoK, rhoKm1, rhoK,
372 O sigmaX, sigmaY, sigmaR,
373 I myThid )
374 ENDIF
375
376 #ifdef ALLOW_AUTODIFF_TAMC
377 CADJ STORE rhok (:,:) = comlev1_bibj_k , key=kkey, byte=isbyte
378 CADJ STORE rhokm1 (:,:) = comlev1_bibj_k , key=kkey, byte=isbyte
379 #endif /* ALLOW_AUTODIFF_TAMC */
380 C-- Implicit Vertical Diffusion for Convection
381 c ==> should use sigmaR !!!
382 IF (k.GT.1 .AND. ivdc_kappa.NE.0.) THEN
383 #ifndef DISABLE_DEBUGMODE
384 IF ( debugLevel .GE. debLevB )
385 & CALL DEBUG_CALL('CALC_IVDC',myThid)
386 #endif
387 CALL CALC_IVDC(
388 I bi, bj, iMin, iMax, jMin, jMax, k,
389 I rhoKm1, rhoK,
390 U ConvectCount, KappaRT, KappaRS,
391 I myTime, myIter, myThid)
392 ENDIF
393
394 #endif /* SINGLE_LAYER_MODE */
395
396 C-- end of diagnostic k loop (Nr:1)
397 ENDDO
398
399 #ifdef ALLOW_AUTODIFF_TAMC
400 cph avoids recomputation of integrate_for_w
401 CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
402 #endif /* ALLOW_AUTODIFF_TAMC */
403
404 #ifdef ALLOW_OBCS
405 C-- Calculate future values on open boundaries
406 IF (useOBCS) THEN
407 #ifndef DISABLE_DEBUGMODE
408 IF ( debugLevel .GE. debLevB )
409 & CALL DEBUG_CALL('OBCS_CALC',myThid)
410 #endif
411 CALL OBCS_CALC( bi, bj, myTime+deltaT, myIter+1,
412 I uVel, vVel, wVel, theta, salt,
413 I myThid )
414 ENDIF
415 #endif /* ALLOW_OBCS */
416
417
418 #ifdef ALLOW_THERM_SEAICE
419 IF (useThermSeaIce) THEN
420 #ifndef DISABLE_DEBUGMODE
421 IF ( debugLevel .GE. debLevB )
422 & CALL DEBUG_CALL('ICE_FORCING',myThid)
423 #endif
424 C-- Determines forcing terms based on external fields
425 C including effects from ice
426 CALL ICE_FORCING(
427 I bi, bj, iMin, iMax, jMin, jMax,
428 I myThid )
429 END IF
430 #endif /* ALLOW_THERM_SEAICE */
431
432 C-- Determines forcing terms based on external fields
433 C relaxation terms, etc.
434 #ifndef DISABLE_DEBUGMODE
435 IF ( debugLevel .GE. debLevB )
436 & CALL DEBUG_CALL('EXTERNAL_FORCING_SURF',myThid)
437 #endif
438 CALL EXTERNAL_FORCING_SURF(
439 I bi, bj, iMin, iMax, jMin, jMax,
440 I myTime, myIter, myThid )
441
442 #ifdef ALLOW_AUTODIFF_TAMC
443 cph needed for KPP
444 CADJ STORE surfacetendencyU(:,:,bi,bj)
445 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
446 CADJ STORE surfacetendencyV(:,:,bi,bj)
447 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
448 CADJ STORE surfacetendencyS(:,:,bi,bj)
449 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
450 CADJ STORE surfacetendencyT(:,:,bi,bj)
451 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
452 #endif /* ALLOW_AUTODIFF_TAMC */
453
454 C-- Attention: by defining "SINGLE_LAYER_MODE" in CPP_OPTIONS.h
455 C-- MOST of THERMODYNAMICS will be disabled
456 #ifndef SINGLE_LAYER_MODE
457
458 #ifdef ALLOW_GMREDI
459
460 #ifdef ALLOW_AUTODIFF_TAMC
461 cph storing here is needed only for one GMREDI_OPTIONS:
462 cph define GM_BOLUS_ADVEC
463 cph but I've avoided the #ifdef for now, in case more things change
464 CADJ STORE sigmaX(:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
465 CADJ STORE sigmaY(:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
466 CADJ STORE sigmaR(:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
467 #endif /* ALLOW_AUTODIFF_TAMC */
468
469 C-- Calculate iso-neutral slopes for the GM/Redi parameterisation
470 IF (useGMRedi) THEN
471 #ifndef DISABLE_DEBUGMODE
472 IF ( debugLevel .GE. debLevB )
473 & CALL DEBUG_CALL('GMREDI_CALC_TENSOR',myThid)
474 #endif
475 CALL GMREDI_CALC_TENSOR(
476 I bi, bj, iMin, iMax, jMin, jMax,
477 I sigmaX, sigmaY, sigmaR,
478 I myThid )
479 #ifdef ALLOW_AUTODIFF_TAMC
480 ELSE
481 CALL GMREDI_CALC_TENSOR_DUMMY(
482 I bi, bj, iMin, iMax, jMin, jMax,
483 I sigmaX, sigmaY, sigmaR,
484 I myThid )
485 #endif /* ALLOW_AUTODIFF_TAMC */
486 ENDIF
487
488 #ifdef ALLOW_AUTODIFF_TAMC
489 CADJ STORE Kwx(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
490 CADJ STORE Kwy(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
491 CADJ STORE Kwz(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
492 #endif /* ALLOW_AUTODIFF_TAMC */
493
494 #endif /* ALLOW_GMREDI */
495
496 #ifdef ALLOW_KPP
497 C-- Compute KPP mixing coefficients
498 IF (useKPP) THEN
499 #ifndef DISABLE_DEBUGMODE
500 IF ( debugLevel .GE. debLevB )
501 & CALL DEBUG_CALL('KPP_CALC',myThid)
502 #endif
503 CALL KPP_CALC(
504 I bi, bj, myTime, myThid )
505 #ifdef ALLOW_AUTODIFF_TAMC
506 ELSE
507 CALL KPP_CALC_DUMMY(
508 I bi, bj, myTime, myThid )
509 #endif /* ALLOW_AUTODIFF_TAMC */
510 ENDIF
511
512 #ifdef ALLOW_AUTODIFF_TAMC
513 CADJ STORE KPPghat (:,:,:,bi,bj)
514 CADJ & , KPPdiffKzT(:,:,:,bi,bj)
515 CADJ & , KPPdiffKzS(:,:,:,bi,bj)
516 CADJ & , KPPfrac (:,: ,bi,bj)
517 CADJ & = comlev1_bibj, key=itdkey, byte=isbyte
518 #endif /* ALLOW_AUTODIFF_TAMC */
519
520 #endif /* ALLOW_KPP */
521
522 #ifdef ALLOW_AUTODIFF_TAMC
523 CADJ STORE KappaRT(:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
524 CADJ STORE KappaRS(:,:,:) = comlev1_bibj, key=itdkey, byte=isbyte
525 CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
526 CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
527 CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
528 CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
529 #ifdef ALLOW_PASSIVE_TRACER
530 CADJ STORE tr1 (:,:,:,bi,bj) = comlev1_bibj, key=itdkey, byte=isbyte
531 #endif
532 #ifdef ALLOW_PTRACERS
533 cph-- moved to forward_step to avoid key computation
534 cphCADJ STORE ptracer(:,:,:,bi,bj,itracer) = comlev1_bibj,
535 cphCADJ & key=itdkey, byte=isbyte
536 #endif
537 #endif /* ALLOW_AUTODIFF_TAMC */
538
539 #ifdef ALLOW_AIM
540 C AIM - atmospheric intermediate model, physics package code.
541 IF ( useAIM ) THEN
542 #ifndef DISABLE_DEBUGMODE
543 IF ( debugLevel .GE. debLevB )
544 & CALL DEBUG_CALL('AIM_DO_PHYSICS',myThid)
545 #endif
546 CALL TIMER_START('AIM_DO_PHYSICS [THERMODYNAMICS]', myThid)
547 CALL AIM_DO_PHYSICS( bi, bj, myTime, myIter, myThid )
548 CALL TIMER_STOP( 'AIM_DO_PHYSICS [THERMODYNAMICS]', myThid)
549 ENDIF
550 #endif /* ALLOW_AIM */
551
552 #ifndef DISABLE_MULTIDIM_ADVECTION
553 C-- Some advection schemes are better calculated using a multi-dimensional
554 C method in the absence of any other terms and, if used, is done here.
555 C
556 C The CPP flag DISABLE_MULTIDIM_ADVECTION is currently unset in GAD_OPTIONS.h
557 C The default is to use multi-dimensinal advection for non-linear advection
558 C schemes. However, for the sake of efficiency of the adjoint it is necessary
559 C to be able to exclude this scheme to avoid excessive storage and
560 C recomputation. It *is* differentiable, if you need it.
561 C Edit GAD_OPTIONS.h and #define DISABLE_MULTIDIM_ADVECTION to
562 C disable this section of code.
563 IF (tempMultiDimAdvec) THEN
564 #ifndef DISABLE_DEBUGMODE
565 IF ( debugLevel .GE. debLevB )
566 & CALL DEBUG_CALL('GAD_ADVECTION',myThid)
567 #endif
568 CALL GAD_ADVECTION(bi,bj,tempAdvScheme,GAD_TEMPERATURE,
569 U theta,gT,
570 I myTime,myIter,myThid)
571 ENDIF
572 IF (saltMultiDimAdvec) THEN
573 #ifndef DISABLE_DEBUGMODE
574 IF ( debugLevel .GE. debLevB )
575 & CALL DEBUG_CALL('GAD_ADVECTION',myThid)
576 #endif
577 CALL GAD_ADVECTION(bi,bj,saltAdvScheme,GAD_SALINITY,
578 U salt,gS,
579 I myTime,myIter,myThid)
580 ENDIF
581 C Since passive tracers are configurable separately from T,S we
582 C call the multi-dimensional method for PTRACERS regardless
583 C of whether multiDimAdvection is set or not.
584 #ifdef ALLOW_PTRACERS
585 IF ( usePTRACERS ) THEN
586 #ifndef DISABLE_DEBUGMODE
587 IF ( debugLevel .GE. debLevB )
588 & CALL DEBUG_CALL('PTRACERS_ADVECTION',myThid)
589 #endif
590 CALL PTRACERS_ADVECTION( bi,bj,myIter,myTime,myThid )
591 ENDIF
592 #endif /* ALLOW_PTRACERS */
593 #endif /* DISABLE_MULTIDIM_ADVECTION */
594
595 #ifndef DISABLE_DEBUGMODE
596 IF ( debugLevel .GE. debLevB )
597 & CALL DEBUG_MSG('ENTERING DOWNWARD K LOOP',myThid)
598 #endif
599
600 C-- Start of thermodynamics loop
601 DO k=Nr,1,-1
602 #ifdef ALLOW_AUTODIFF_TAMC
603 C? Patrick Is this formula correct?
604 cph Yes, but I rewrote it.
605 cph Also, the KappaR? need the index and subscript k!
606 kkey = (itdkey-1)*Nr + k
607 #endif /* ALLOW_AUTODIFF_TAMC */
608
609 C-- km1 Points to level above k (=k-1)
610 C-- kup Cycles through 1,2 to point to layer above
611 C-- kDown Cycles through 2,1 to point to current layer
612
613 km1 = MAX(1,k-1)
614 kup = 1+MOD(k+1,2)
615 kDown= 1+MOD(k,2)
616
617 iMin = 1-OLx
618 iMax = sNx+OLx
619 jMin = 1-OLy
620 jMax = sNy+OLy
621
622 C-- Get temporary terms used by tendency routines
623 CALL CALC_COMMON_FACTORS (
624 I bi,bj,iMin,iMax,jMin,jMax,k,
625 O xA,yA,uTrans,vTrans,rTrans,maskUp,
626 I myThid)
627
628 #ifdef ALLOW_GMREDI
629
630 C-- Residual transp = Bolus transp + Eulerian transp
631 IF (useGMRedi) THEN
632 CALL GMREDI_CALC_UVFLOW(
633 & uTrans, vTrans, bi, bj, k, myThid)
634 IF (K.GE.2) CALL GMREDI_CALC_WFLOW(
635 & rTrans, bi, bj, k, myThid)
636 ENDIF
637
638 #ifdef ALLOW_AUTODIFF_TAMC
639 #ifdef GM_BOLUS_ADVEC
640 CADJ STORE uTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
641 CADJ STORE vTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
642 CADJ STORE rTrans(:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
643 #endif
644 #endif /* ALLOW_AUTODIFF_TAMC */
645
646 #endif /* ALLOW_GMREDI */
647
648 #ifdef ALLOW_AUTODIFF_TAMC
649 CADJ STORE KappaRT(:,:,k) = comlev1_bibj_k, key=kkey, byte=isbyte
650 CADJ STORE KappaRS(:,:,k) = comlev1_bibj_k, key=kkey, byte=isbyte
651 #endif /* ALLOW_AUTODIFF_TAMC */
652
653 #ifdef INCLUDE_CALC_DIFFUSIVITY_CALL
654 C-- Calculate the total vertical diffusivity
655 CALL CALC_DIFFUSIVITY(
656 I bi,bj,iMin,iMax,jMin,jMax,k,
657 I maskUp,
658 O KappaRT,KappaRS,
659 I myThid)
660 #endif
661
662 iMin = 1-OLx+2
663 iMax = sNx+OLx-1
664 jMin = 1-OLy+2
665 jMax = sNy+OLy-1
666
667 C-- Calculate active tracer tendencies (gT,gS,...)
668 C and step forward storing result in gTnm1, gSnm1, etc.
669 IF ( tempStepping ) THEN
670 CALL CALC_GT(
671 I bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
672 I xA,yA,uTrans,vTrans,rTrans,maskUp,
673 I KappaRT,
674 U fVerT,
675 I myTime,myIter,myThid)
676 CALL TIMESTEP_TRACER(
677 I bi,bj,iMin,iMax,jMin,jMax,k,tempAdvScheme,
678 I theta, gT,
679 I myIter, myThid)
680 ENDIF
681
682 #ifdef ALLOW_THERM_SEAICE
683 IF (useThermSeaIce .AND. k.EQ.1) THEN
684 CALL ICE_FREEZE( bi,bj, iMin,iMax,jMin,jMax, myThid )
685 ENDIF
686 #endif
687
688 IF ( saltStepping ) THEN
689 CALL CALC_GS(
690 I bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
691 I xA,yA,uTrans,vTrans,rTrans,maskUp,
692 I KappaRS,
693 U fVerS,
694 I myTime,myIter,myThid)
695 CALL TIMESTEP_TRACER(
696 I bi,bj,iMin,iMax,jMin,jMax,k,saltAdvScheme,
697 I salt, gS,
698 I myIter, myThid)
699 ENDIF
700 #ifdef ALLOW_PASSIVE_TRACER
701 IF ( tr1Stepping ) THEN
702 CALL CALC_GTR1(
703 I bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
704 I xA,yA,uTrans,vTrans,rTrans,maskUp,
705 I KappaRT,
706 U fVerTr1,
707 I myTime,myIter,myThid)
708 CALL TIMESTEP_TRACER(
709 I bi,bj,iMin,iMax,jMin,jMax,k,tracerAdvScheme,
710 I Tr1, gTr1,
711 I myIter,myThid)
712 ENDIF
713 #endif
714 #ifdef ALLOW_PTRACERS
715 IF ( usePTRACERS ) THEN
716 CALL PTRACERS_INTEGRATE(
717 I bi,bj,k,
718 I xA,yA,uTrans,vTrans,rTrans,maskUp,
719 X KappaRS,
720 I myIter,myTime,myThid)
721 ENDIF
722 #endif /* ALLOW_PTRACERS */
723
724 #ifdef ALLOW_OBCS
725 C-- Apply open boundary conditions
726 IF (useOBCS) THEN
727 CALL OBCS_APPLY_TS( bi, bj, k, gT, gS, myThid )
728 END IF
729 #endif /* ALLOW_OBCS */
730
731 C-- Freeze water
732 IF ( allowFreezing .AND. .NOT. useSEAICE
733 & .AND. .NOT.(useThermSeaIce.AND.k.EQ.1) ) THEN
734 #ifdef ALLOW_AUTODIFF_TAMC
735 CADJ STORE gT(:,:,k,bi,bj) = comlev1_bibj_k
736 CADJ & , key = kkey, byte = isbyte
737 #endif /* ALLOW_AUTODIFF_TAMC */
738 CALL FREEZE( bi, bj, iMin, iMax, jMin, jMax, k, myThid )
739 ENDIF
740
741 C-- end of thermodynamic k loop (Nr:1)
742 ENDDO
743
744 cswdice -- add ---
745 #ifdef ALLOW_THERM_SEAICE
746 c timeaveraging for ice model values
747 CALL ICE_AVE(bi,bj,iMin,iMax,jMin,jMax,myThid )
748 #endif
749 cswdice --- end add ---
750
751
752
753
754 C-- Implicit diffusion
755 IF (implicitDiffusion) THEN
756
757 IF (tempStepping) THEN
758 #ifdef ALLOW_AUTODIFF_TAMC
759 CADJ STORE gT(:,:,:,bi,bj) = comlev1_bibj , key=itdkey, byte=isbyte
760 #endif /* ALLOW_AUTODIFF_TAMC */
761 CALL IMPLDIFF(
762 I bi, bj, iMin, iMax, jMin, jMax,
763 I deltaTtracer, KappaRT, recip_HFacC,
764 U gT,
765 I myThid )
766 ENDIF
767
768 IF (saltStepping) THEN
769 #ifdef ALLOW_AUTODIFF_TAMC
770 CADJ STORE gS(:,:,:,bi,bj) = comlev1_bibj , key=itdkey, byte=isbyte
771 #endif /* ALLOW_AUTODIFF_TAMC */
772 CALL IMPLDIFF(
773 I bi, bj, iMin, iMax, jMin, jMax,
774 I deltaTtracer, KappaRS, recip_HFacC,
775 U gS,
776 I myThid )
777 ENDIF
778
779 #ifdef ALLOW_PASSIVE_TRACER
780 IF (tr1Stepping) THEN
781 #ifdef ALLOW_AUTODIFF_TAMC
782 CADJ STORE gTr1(:,:,:,bi,bj) = comlev1_bibj , key=itdkey, byte=isbyte
783 #endif /* ALLOW_AUTODIFF_TAMC */
784 CALL IMPLDIFF(
785 I bi, bj, iMin, iMax, jMin, jMax,
786 I deltaTtracer, KappaRT, recip_HFacC,
787 U gTr1,
788 I myThid )
789 ENDIF
790 #endif
791
792 #ifdef ALLOW_PTRACERS
793 C Vertical diffusion (implicit) for passive tracers
794 IF ( usePTRACERS ) THEN
795 CALL PTRACERS_IMPLDIFF( bi,bj,KappaRS,myThid )
796 ENDIF
797 #endif /* ALLOW_PTRACERS */
798
799 #ifdef ALLOW_OBCS
800 C-- Apply open boundary conditions
801 IF (useOBCS) THEN
802 DO K=1,Nr
803 CALL OBCS_APPLY_TS( bi, bj, k, gT, gS, myThid )
804 ENDDO
805 END IF
806 #endif /* ALLOW_OBCS */
807
808 C-- End If implicitDiffusion
809 ENDIF
810
811 #ifdef ALLOW_TIMEAVE
812 IF (taveFreq.GT.0. .AND. ivdc_kappa.NE.0.) THEN
813 CALL TIMEAVE_CUMUL_1T(ConvectCountTave, ConvectCount,
814 I Nr, deltaTclock, bi, bj, myThid)
815 ENDIF
816 useVariableK = useKPP .OR. useGMredi .OR. ivdc_kappa.NE.0.
817 IF (taveFreq.GT.0. .AND. useVariableK ) THEN
818 IF (implicitDiffusion) THEN
819 CALL TIMEAVE_CUMUL_DIF_1T(TdiffRtave, gT, kappaRT,
820 I Nr, 3, deltaTclock, bi, bj, myThid)
821 ELSE
822 CALL TIMEAVE_CUMUL_DIF_1T(TdiffRtave, theta, kappaRT,
823 I Nr, 3, deltaTclock, bi, bj, myThid)
824 ENDIF
825 ENDIF
826 #endif /* ALLOW_TIMEAVE */
827
828 #endif /* SINGLE_LAYER_MODE */
829
830 C-- end bi,bj loops.
831 ENDDO
832 ENDDO
833
834 #ifndef DISABLE_DEBUGMODE
835 If (debugMode) THEN
836 CALL DEBUG_STATS_RL(Nr,uVel,'Uvel (THERMODYNAMICS)',myThid)
837 CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (THERMODYNAMICS)',myThid)
838 CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (THERMODYNAMICS)',myThid)
839 CALL DEBUG_STATS_RL(Nr,theta,'Theta (THERMODYNAMICS)',myThid)
840 CALL DEBUG_STATS_RL(Nr,salt,'Salt (THERMODYNAMICS)',myThid)
841 CALL DEBUG_STATS_RL(Nr,Gt,'Gt (THERMODYNAMICS)',myThid)
842 CALL DEBUG_STATS_RL(Nr,Gs,'Gs (THERMODYNAMICS)',myThid)
843 CALL DEBUG_STATS_RL(Nr,GtNm1,'GtNm1 (THERMODYNAMICS)',myThid)
844 CALL DEBUG_STATS_RL(Nr,GsNm1,'GsNm1 (THERMODYNAMICS)',myThid)
845 #ifdef ALLOW_PTRACERS
846 IF ( usePTRACERS ) THEN
847 CALL PTRACERS_DEBUG(myThid)
848 ENDIF
849 #endif /* ALLOW_PTRACERS */
850 ENDIF
851 #endif
852
853 #ifndef DISABLE_DEBUGMODE
854 IF ( debugLevel .GE. debLevB )
855 & CALL DEBUG_LEAVE('FORWARD_STEP',myThid)
856 #endif
857
858 RETURN
859 END

  ViewVC Help
Powered by ViewVC 1.1.22