source: palm/trunk/SOURCE/prognostic_equations.f90 @ 1682

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 84.9 KB
RevLine 
[1682]1!> @file prognostic_equations.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1310]16! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[736]19! Current revisions:
[1092]20! ------------------
[1682]21! Code annotations made doxygen readable
[1586]22!
[1485]23! Former revisions:
24! -----------------
25! $Id: prognostic_equations.f90 1682 2015-10-07 23:56:08Z knoop $
26!
[1586]27! 1585 2015-04-30 07:05:52Z maronga
28! Added call for temperature tendency calculation due to radiative flux divergence
29!
[1518]30! 1517 2015-01-07 19:12:25Z hoffmann
31! advec_s_bc_mod addded, since advec_s_bc is now a module
32!
[1517]33! 1496 2014-12-02 17:25:50Z maronga
[1497]34! Renamed "radiation" -> "cloud_top_radiation"
35!
[1496]36! 1484 2014-10-21 10:53:05Z kanani
[1484]37! Changes due to new module structure of the plant canopy model:
38!   parameters cthf and plant_canopy moved to module plant_canopy_model_mod.
39! Removed double-listing of use_upstream_for_tke in ONLY-list of module
40! control_parameters
41!
42! 1409 2014-05-23 12:11:32Z suehring
[1409]43! Bugfix: i_omp_start changed for advec_u_ws at left inflow and outflow boundary.
44! This ensures that left-hand side fluxes are also calculated for nxl in that
45! case, even though the solution at nxl is overwritten in boundary_conds()
46!
47! 1398 2014-05-07 11:15:00Z heinze
[1398]48! Rayleigh-damping for horizontal velocity components changed: instead of damping
49! against ug and vg, damping against u_init and v_init is used to allow for a
50! homogenized treatment in case of nudging
51!
52! 1380 2014-04-28 12:40:45Z heinze
[1381]53! Change order of calls for scalar prognostic quantities:
54! ls_advec -> nudging -> subsidence since initial profiles
55!
[1380]56! 1374 2014-04-25 12:55:07Z raasch
57! missing variables added to ONLY lists
58!
59! 1365 2014-04-22 15:03:56Z boeske
[1365]60! Calls of ls_advec for large scale advection added,
61! subroutine subsidence is only called if use_subsidence_tendencies = .F.,
62! new argument ls_index added to the calls of subsidence
63! +ls_index
64!
65! 1361 2014-04-16 15:17:48Z hoffmann
[1361]66! Two-moment microphysics moved to the start of prognostic equations. This makes
67! the 3d arrays for tend_q, tend_qr, tend_pt and tend_pt redundant.
68! Additionally, it is allowed to call the microphysics just once during the time
69! step (not at each sub-time step).
70!
71! Two-moment cloud physics added for vector and accelerator optimization.
72!
73! 1353 2014-04-08 15:21:23Z heinze
[1354]74! REAL constants provided with KIND-attribute
75!
[1353]76! 1337 2014-03-25 15:11:48Z heinze
77! Bugfix: REAL constants provided with KIND-attribute
78!
79! 1332 2014-03-25 11:59:43Z suehring
[1333]80! Bugfix: call advec_ws or advec_pw for TKE only if NOT use_upstream_for_tke
81!
[1332]82! 1330 2014-03-24 17:29:32Z suehring
[1331]83! In case of SGS-particle velocity advection of TKE is also allowed with
84! dissipative 5th-order scheme.
85!
[1321]86! 1320 2014-03-20 08:40:49Z raasch
[1320]87! ONLY-attribute added to USE-statements,
88! kind-parameters added to all INTEGER and REAL declaration statements,
89! kinds are defined in new module kinds,
90! old module precision_kind is removed,
91! revision history before 2012 removed,
92! comment fields (!:) to be used for variable explanations added to
93! all variable declaration statements
[1054]94!
[1319]95! 1318 2014-03-17 13:35:16Z raasch
96! module interfaces removed
97!
[1258]98! 1257 2013-11-08 15:18:40Z raasch
99! openacc loop vector clauses removed, independent clauses added
100!
[1247]101! 1246 2013-11-01 08:59:45Z heinze
102! enable nudging also for accelerator version
103!
[1242]104! 1241 2013-10-30 11:36:58Z heinze
105! usage of nudging enabled (so far not implemented for accelerator version)
106!
[1182]107! 1179 2013-06-14 05:57:58Z raasch
108! two arguments removed from routine buoyancy, ref_state updated on device
109!
[1132]110! 1128 2013-04-12 06:19:32Z raasch
111! those parts requiring global communication moved to time_integration,
112! loop index bounds in accelerator version replaced by i_left, i_right, j_south,
113! j_north
114!
[1116]115! 1115 2013-03-26 18:16:16Z hoffmann
116! optimized cloud physics: calculation of microphysical tendencies transfered
117! to microphysics.f90; qr and nr are only calculated if precipitation is required
118!
[1112]119! 1111 2013-03-08 23:54:10Z raasch
120! update directives for prognostic quantities removed
121!
[1107]122! 1106 2013-03-04 05:31:38Z raasch
123! small changes in code formatting
124!
[1093]125! 1092 2013-02-02 11:24:22Z raasch
126! unused variables removed
127!
[1054]128! 1053 2012-11-13 17:11:03Z hoffmann
[1053]129! implementation of two new prognostic equations for rain drop concentration (nr)
130! and rain water content (qr)
[979]131!
[1053]132! currently, only available for cache loop optimization
[1020]133!
[1037]134! 1036 2012-10-22 13:43:42Z raasch
135! code put under GPL (PALM 3.9)
136!
[1020]137! 1019 2012-09-28 06:46:45Z raasch
138! non-optimized version of prognostic_equations removed
139!
[1017]140! 1015 2012-09-27 09:23:24Z raasch
141! new branch prognostic_equations_acc
142! OpenACC statements added + code changes required for GPU optimization
143!
[1002]144! 1001 2012-09-13 14:08:46Z raasch
145! all actions concerning leapfrog- and upstream-spline-scheme removed
146!
[979]147! 978 2012-08-09 08:28:32Z fricke
[978]148! km_damp_x and km_damp_y removed in calls of diffusion_u and diffusion_v
149! add ptdf_x, ptdf_y for damping the potential temperature at the inflow
150! boundary in case of non-cyclic lateral boundaries
151! Bugfix: first thread index changes for WS-scheme at the inflow
[736]152!
[941]153! 940 2012-07-09 14:31:00Z raasch
154! temperature equation can be switched off
155!
[736]156! Revision 1.1  2000/04/13 14:56:27  schroeter
157! Initial revision
158!
159!
160! Description:
161! ------------
[1682]162!> Solving the prognostic equations.
[736]163!------------------------------------------------------------------------------!
[1682]164 MODULE prognostic_equations_mod
[736]165
[1682]166 
167
[1320]168    USE arrays_3d,                                                             &
169        ONLY:  diss_l_e, diss_l_nr, diss_l_pt, diss_l_q, diss_l_qr,            &
170               diss_l_sa, diss_s_e, diss_s_nr, diss_s_pt, diss_s_q,            &
171               diss_s_qr, diss_s_sa, e, e_p, flux_s_e, flux_s_nr, flux_s_pt,   &
172               flux_s_q, flux_s_qr, flux_s_sa, flux_l_e, flux_l_nr,            &
173               flux_l_pt, flux_l_q, flux_l_qr, flux_l_sa, nr, nr_p, nrsws,     &
174               nrswst, pt, ptdf_x, ptdf_y, pt_init, pt_p, prho, q, q_init,     &
[1374]175               q_p, qsws, qswst, qr, qr_p, qrsws, qrswst, rdf, rdf_sc,         &
176               ref_state, rho, sa, sa_init, sa_p, saswsb, saswst, shf, tend,   &
177               te_m, tnr_m, tpt_m, tq_m, tqr_m, tsa_m, tswst, tu_m, tv_m,      &
[1398]178               tw_m, u, ug, u_init, u_p, v, vg, vpt, v_init, v_p, w, w_p
[1320]179       
180    USE control_parameters,                                                    &
[1361]181        ONLY:  call_microphysics_at_all_substeps, cloud_physics,               &
[1496]182               cloud_top_radiation, constant_diffusion, dp_external,       &
[1320]183               dp_level_ind_b, dp_smooth_factor, dpdxy, dt_3d, humidity,       &
184               icloud_scheme, inflow_l, intermediate_timestep_count,           &
[1365]185               intermediate_timestep_count_max, large_scale_forcing,           &
186               large_scale_subsidence, neutral, nudging, ocean, outflow_l,     &
[1484]187               outflow_s, passive_scalar, precipitation,                       &
[1365]188               prho_reference, prho_reference, prho_reference, pt_reference,   &
[1496]189               pt_reference, pt_reference, scalar_advec, scalar_advec,         &
190               simulated_time, sloping_surface,                                &
191               timestep_scheme, tsc, use_subsidence_tendencies,                &
192               use_upstream_for_tke, wall_heatflux,                            &
[1320]193               wall_nrflux, wall_qflux, wall_qflux, wall_qflux, wall_qrflux,   &
194               wall_salinityflux, ws_scheme_mom, ws_scheme_sca
[736]195
[1320]196    USE cpulog,                                                                &
197        ONLY:  cpu_log, log_point
[736]198
[1320]199    USE eqn_state_seawater_mod,                                                &
200        ONLY:  eqn_state_seawater
201
202    USE indices,                                                               &
203        ONLY:  i_left, i_right, j_north, j_south, nxl, nxlu, nxr, nyn, nys,    &
204               nysv, nzb_s_inner, nzb_u_inner, nzb_v_inner, nzb_w_inner, nzt
205
206    USE advec_ws,                                                              &
207        ONLY:  advec_s_ws, advec_s_ws_acc, advec_u_ws, advec_u_ws_acc,         &
208               advec_v_ws, advec_v_ws_acc, advec_w_ws, advec_w_ws_acc
209
[1517]210    USE advec_s_bc_mod,                                                        &
211        ONLY:  advec_s_bc
212
[1320]213    USE advec_s_pw_mod,                                                        &
214        ONLY:  advec_s_pw
215
216    USE advec_s_up_mod,                                                        &
217        ONLY:  advec_s_up
218
219    USE advec_u_pw_mod,                                                        &
220        ONLY:  advec_u_pw
221
222    USE advec_u_up_mod,                                                        &
223        ONLY:  advec_u_up
224
225    USE advec_v_pw_mod,                                                        &
226        ONLY:  advec_v_pw
227
228    USE advec_v_up_mod,                                                        &
229        ONLY:  advec_v_up
230
231    USE advec_w_pw_mod,                                                        &
232        ONLY:  advec_w_pw
233
234    USE advec_w_up_mod,                                                        &
235        ONLY:  advec_w_up
236
237    USE buoyancy_mod,                                                          &
238        ONLY:  buoyancy, buoyancy_acc
239
240    USE calc_precipitation_mod,                                                &
241        ONLY:  calc_precipitation
242
243    USE calc_radiation_mod,                                                    &
244        ONLY:  calc_radiation
245 
246    USE coriolis_mod,                                                          &
247        ONLY:  coriolis, coriolis_acc
248
249    USE diffusion_e_mod,                                                       &
250        ONLY:  diffusion_e, diffusion_e_acc
251
252    USE diffusion_s_mod,                                                       &
253        ONLY:  diffusion_s, diffusion_s_acc
254
255    USE diffusion_u_mod,                                                       &
256        ONLY:  diffusion_u, diffusion_u_acc
257
258    USE diffusion_v_mod,                                                       &
259        ONLY:  diffusion_v, diffusion_v_acc
260
261    USE diffusion_w_mod,                                                       &
262        ONLY:  diffusion_w, diffusion_w_acc
263
264    USE impact_of_latent_heat_mod,                                             &
265        ONLY:  impact_of_latent_heat
266
267    USE kinds
268
[1365]269    USE ls_forcing_mod,                                                        &
270        ONLY:  ls_advec
271
[1320]272    USE microphysics_mod,                                                      &
273        ONLY:  microphysics_control
274
275    USE nudge_mod,                                                             &
276        ONLY:  nudge
277
278    USE plant_canopy_model_mod,                                                &
[1484]279        ONLY:  cthf, plant_canopy, plant_canopy_model
[1320]280
281    USE production_e_mod,                                                      &
282        ONLY:  production_e, production_e_acc
283
[1585]284    USE radiation_model_mod,                                                   &
285        ONLY:  radiation, radiation_scheme, radiation_tendency
286
[1374]287    USE statistics,                                                            &
288        ONLY:  hom
289
[1320]290    USE subsidence_mod,                                                        &
291        ONLY:  subsidence
292
293    USE user_actions_mod,                                                      &
294        ONLY:  user_actions
295
296
[736]297    PRIVATE
[1019]298    PUBLIC prognostic_equations_cache, prognostic_equations_vector, &
299           prognostic_equations_acc
[736]300
301    INTERFACE prognostic_equations_cache
302       MODULE PROCEDURE prognostic_equations_cache
303    END INTERFACE prognostic_equations_cache
304
305    INTERFACE prognostic_equations_vector
306       MODULE PROCEDURE prognostic_equations_vector
307    END INTERFACE prognostic_equations_vector
308
[1015]309    INTERFACE prognostic_equations_acc
310       MODULE PROCEDURE prognostic_equations_acc
311    END INTERFACE prognostic_equations_acc
[736]312
[1015]313
[736]314 CONTAINS
315
316
317!------------------------------------------------------------------------------!
[1682]318! Description:
319! ------------
320!> Version with one optimized loop over all equations. It is only allowed to
321!> be called for the Wicker and Skamarock or Piascek-Williams advection scheme.
322!>
323!> Here the calls of most subroutines are embedded in two DO loops over i and j,
324!> so communication between CPUs is not allowed (does not make sense) within
325!> these loops.
326!>
327!> (Optimized to avoid cache missings, i.e. for Power4/5-architectures.)
[736]328!------------------------------------------------------------------------------!
[1682]329 
330 SUBROUTINE prognostic_equations_cache
[736]331
[1682]332
[736]333    IMPLICIT NONE
334
[1682]335    INTEGER(iwp) ::  i                   !<
336    INTEGER(iwp) ::  i_omp_start         !<
337    INTEGER(iwp) ::  j                   !<
338    INTEGER(iwp) ::  k                   !<
339    INTEGER(iwp) ::  omp_get_thread_num  !<
340    INTEGER(iwp) ::  tn = 0              !<
[1320]341   
[1682]342    LOGICAL      ::  loop_start          !<
[736]343
344
345!
346!-- Time measurement can only be performed for the whole set of equations
347    CALL cpu_log( log_point(32), 'all progn.equations', 'start' )
348
349!
350!-- Loop over all prognostic equations
351!$OMP PARALLEL private (i,i_omp_start,j,k,loop_start,tn)
352
353!$  tn = omp_get_thread_num()
354    loop_start = .TRUE.
355!$OMP DO
356    DO  i = nxl, nxr
357
358!
359!--    Store the first loop index. It differs for each thread and is required
360!--    later in advec_ws
361       IF ( loop_start )  THEN
362          loop_start  = .FALSE.
363          i_omp_start = i 
364       ENDIF
[1365]365
[736]366       DO  j = nys, nyn
367!
[1361]368!--       If required, calculate cloud microphysical impacts (two-moment scheme)
369          IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                 &
370               ( intermediate_timestep_count == 1  .OR.                        &
371                 call_microphysics_at_all_substeps )                           &
372             )  THEN
373             CALL microphysics_control( i, j )
374          ENDIF
375!
[736]376!--       Tendency terms for u-velocity component
377          IF ( .NOT. outflow_l  .OR.  i > nxl )  THEN
378
[1337]379             tend(:,j,i) = 0.0_wp
[1001]380             IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]381                IF ( ws_scheme_mom )  THEN
[1409]382                   CALL advec_u_ws( i, j, i_omp_start, tn )
[736]383                ELSE
384                   CALL advec_u_pw( i, j )
385                ENDIF
386             ELSE
387                CALL advec_u_up( i, j )
388             ENDIF
[1001]389             CALL diffusion_u( i, j )
[736]390             CALL coriolis( i, j, 1 )
[940]391             IF ( sloping_surface  .AND.  .NOT. neutral )  THEN
[1179]392                CALL buoyancy( i, j, pt, 1 )
[940]393             ENDIF
[736]394
395!
396!--          Drag by plant canopy
397             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 1 )
398
399!
400!--          External pressure gradient
401             IF ( dp_external )  THEN
402                DO  k = dp_level_ind_b+1, nzt
403                   tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
404                ENDDO
405             ENDIF
406
[1241]407!
408!--          Nudging
409             IF ( nudging )  CALL nudge( i, j, simulated_time, 'u' ) 
410
[736]411             CALL user_actions( i, j, 'u-tendency' )
412!
413!--          Prognostic equation for u-velocity component
414             DO  k = nzb_u_inner(j,i)+1, nzt
[1001]415                u_p(k,j,i) = u(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
416                                                  tsc(3) * tu_m(k,j,i) )       &
[1398]417                                      - tsc(5) * rdf(k) * ( u(k,j,i) - u_init(k) )
[736]418             ENDDO
419
420!
421!--          Calculate tendencies for the next Runge-Kutta step
422             IF ( timestep_scheme(1:5) == 'runge' )  THEN
423                IF ( intermediate_timestep_count == 1 )  THEN
424                   DO  k = nzb_u_inner(j,i)+1, nzt
425                      tu_m(k,j,i) = tend(k,j,i)
426                   ENDDO
427                ELSEIF ( intermediate_timestep_count < &
428                         intermediate_timestep_count_max )  THEN
429                   DO  k = nzb_u_inner(j,i)+1, nzt
[1337]430                      tu_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tu_m(k,j,i)
[736]431                   ENDDO
432                ENDIF
433             ENDIF
434
435          ENDIF
436
437!
438!--       Tendency terms for v-velocity component
439          IF ( .NOT. outflow_s  .OR.  j > nys )  THEN
440
[1337]441             tend(:,j,i) = 0.0_wp
[1001]442             IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]443                IF ( ws_scheme_mom )  THEN
444                    CALL advec_v_ws( i, j, i_omp_start, tn )
445                ELSE
446                    CALL advec_v_pw( i, j )
447                ENDIF
448             ELSE
449                CALL advec_v_up( i, j )
450             ENDIF
[1001]451             CALL diffusion_v( i, j )
[736]452             CALL coriolis( i, j, 2 )
453
454!
455!--          Drag by plant canopy
456             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 2 )       
457
458!
459!--          External pressure gradient
460             IF ( dp_external )  THEN
461                DO  k = dp_level_ind_b+1, nzt
462                   tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
463                ENDDO
464             ENDIF
465
[1241]466!
467!--          Nudging
468             IF ( nudging )  CALL nudge( i, j, simulated_time, 'v' ) 
469
[736]470             CALL user_actions( i, j, 'v-tendency' )
471!
472!--          Prognostic equation for v-velocity component
473             DO  k = nzb_v_inner(j,i)+1, nzt
[1001]474                v_p(k,j,i) = v(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
475                                                  tsc(3) * tv_m(k,j,i) )       &
[1398]476                                      - tsc(5) * rdf(k) * ( v(k,j,i) - v_init(k) )
[736]477             ENDDO
478
479!
480!--          Calculate tendencies for the next Runge-Kutta step
481             IF ( timestep_scheme(1:5) == 'runge' )  THEN
482                IF ( intermediate_timestep_count == 1 )  THEN
483                   DO  k = nzb_v_inner(j,i)+1, nzt
484                      tv_m(k,j,i) = tend(k,j,i)
485                   ENDDO
486                ELSEIF ( intermediate_timestep_count < &
487                         intermediate_timestep_count_max )  THEN
488                   DO  k = nzb_v_inner(j,i)+1, nzt
[1337]489                      tv_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tv_m(k,j,i)
[736]490                   ENDDO
491                ENDIF
492             ENDIF
493
494          ENDIF
495
496!
497!--       Tendency terms for w-velocity component
[1337]498          tend(:,j,i) = 0.0_wp
[1001]499          IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]500             IF ( ws_scheme_mom )  THEN
501                CALL advec_w_ws( i, j, i_omp_start, tn )
502             ELSE
503                CALL advec_w_pw( i, j )
504             END IF
505          ELSE
506             CALL advec_w_up( i, j )
507          ENDIF
[1001]508          CALL diffusion_w( i, j )
[736]509          CALL coriolis( i, j, 3 )
[940]510
511          IF ( .NOT. neutral )  THEN
512             IF ( ocean )  THEN
[1179]513                CALL buoyancy( i, j, rho, 3 )
[736]514             ELSE
[940]515                IF ( .NOT. humidity )  THEN
[1179]516                   CALL buoyancy( i, j, pt, 3 )
[940]517                ELSE
[1179]518                   CALL buoyancy( i, j, vpt, 3 )
[940]519                ENDIF
[736]520             ENDIF
521          ENDIF
522
523!
524!--       Drag by plant canopy
525          IF ( plant_canopy )  CALL plant_canopy_model( i, j, 3 )
526
527          CALL user_actions( i, j, 'w-tendency' )
528
529!
530!--       Prognostic equation for w-velocity component
531          DO  k = nzb_w_inner(j,i)+1, nzt-1
[1001]532             w_p(k,j,i) = w(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +          &
533                                               tsc(3) * tw_m(k,j,i) )          &
534                                   - tsc(5) * rdf(k) * w(k,j,i)
[736]535          ENDDO
536
537!
538!--       Calculate tendencies for the next Runge-Kutta step
539          IF ( timestep_scheme(1:5) == 'runge' )  THEN
540             IF ( intermediate_timestep_count == 1 )  THEN
541                DO  k = nzb_w_inner(j,i)+1, nzt-1
542                   tw_m(k,j,i) = tend(k,j,i)
543                ENDDO
544             ELSEIF ( intermediate_timestep_count < &
545                      intermediate_timestep_count_max )  THEN
546                DO  k = nzb_w_inner(j,i)+1, nzt-1
[1337]547                   tw_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tw_m(k,j,i)
[736]548                ENDDO
549             ENDIF
550          ENDIF
[1361]551
[736]552!
[940]553!--       If required, compute prognostic equation for potential temperature
554          IF ( .NOT. neutral )  THEN
555!
556!--          Tendency terms for potential temperature
[1337]557             tend(:,j,i) = 0.0_wp
[1001]558             IF ( timestep_scheme(1:5) == 'runge' )  THEN
[940]559                   IF ( ws_scheme_sca )  THEN
560                      CALL advec_s_ws( i, j, pt, 'pt', flux_s_pt, diss_s_pt, &
561                                       flux_l_pt, diss_l_pt, i_omp_start, tn )
562                   ELSE
563                      CALL advec_s_pw( i, j, pt )
564                   ENDIF
565             ELSE
566                CALL advec_s_up( i, j, pt )
567             ENDIF
[1001]568             CALL diffusion_s( i, j, pt, shf, tswst, wall_heatflux )
[736]569
570!
[940]571!--          If required compute heating/cooling due to long wave radiation
572!--          processes
[1496]573             IF ( cloud_top_radiation )  THEN
[940]574                CALL calc_radiation( i, j )
575             ENDIF
[736]576
[1106]577!
[1361]578!--          If required compute impact of latent heat due to precipitation
579             IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.              &
580                  precipitation )  THEN
581                CALL impact_of_latent_heat( i, j ) 
[940]582             ENDIF
[736]583
584!
[940]585!--          Consideration of heat sources within the plant canopy
[1337]586             IF ( plant_canopy  .AND.  cthf /= 0.0_wp )  THEN
[940]587                CALL plant_canopy_model( i, j, 4 )
588             ENDIF
[736]589
[940]590!
[1365]591!--          Large scale advection
592             IF ( large_scale_forcing )  THEN
593                CALL ls_advec( i, j, simulated_time, 'pt' )
594             ENDIF     
595
596!
[1380]597!--          Nudging
598             IF ( nudging )  CALL nudge( i, j, simulated_time, 'pt' ) 
599
600!
[1106]601!--          If required, compute effect of large-scale subsidence/ascent
[1365]602             IF ( large_scale_subsidence  .AND.                                &
603                  .NOT. use_subsidence_tendencies )  THEN
604                CALL subsidence( i, j, tend, pt, pt_init, 2 )
[940]605             ENDIF
[736]606
[1585]607!
608!--          If required, add tendency due to radiative heating/cooling
609             IF ( radiation .AND. radiation_scheme == 'rrtmg' )  THEN
610                CALL radiation_tendency ( i, j, tend )
611             ENDIF
612
613
[940]614             CALL user_actions( i, j, 'pt-tendency' )
[736]615
616!
[940]617!--          Prognostic equation for potential temperature
618             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]619                pt_p(k,j,i) = pt(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +     &
620                                                    tsc(3) * tpt_m(k,j,i) )    &
621                                        - tsc(5) * ( pt(k,j,i) - pt_init(k) ) *&
622                                          ( rdf_sc(k) + ptdf_x(i) + ptdf_y(j) )
[940]623             ENDDO
[736]624
625!
[940]626!--          Calculate tendencies for the next Runge-Kutta step
627             IF ( timestep_scheme(1:5) == 'runge' )  THEN
628                IF ( intermediate_timestep_count == 1 )  THEN
629                   DO  k = nzb_s_inner(j,i)+1, nzt
630                      tpt_m(k,j,i) = tend(k,j,i)
631                   ENDDO
632                ELSEIF ( intermediate_timestep_count < &
633                         intermediate_timestep_count_max )  THEN
634                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]635                      tpt_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
636                                      5.3125_wp * tpt_m(k,j,i)
[940]637                   ENDDO
638                ENDIF
[736]639             ENDIF
[940]640
[736]641          ENDIF
642
643!
644!--       If required, compute prognostic equation for salinity
645          IF ( ocean )  THEN
646
647!
648!--          Tendency-terms for salinity
[1337]649             tend(:,j,i) = 0.0_wp
[1001]650             IF ( timestep_scheme(1:5) == 'runge' ) &
[736]651             THEN
652                IF ( ws_scheme_sca )  THEN
653                    CALL advec_s_ws( i, j, sa, 'sa', flux_s_sa,  &
654                                diss_s_sa, flux_l_sa, diss_l_sa, i_omp_start, tn  )
655                ELSE
656                    CALL advec_s_pw( i, j, sa )
657                ENDIF
658             ELSE
659                CALL advec_s_up( i, j, sa )
660             ENDIF
[1001]661             CALL diffusion_s( i, j, sa, saswsb, saswst, wall_salinityflux )
[736]662
663             CALL user_actions( i, j, 'sa-tendency' )
664
665!
666!--          Prognostic equation for salinity
667             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]668                sa_p(k,j,i) = sa(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +     &
669                                                    tsc(3) * tsa_m(k,j,i) )    &
670                                        - tsc(5) * rdf_sc(k) *                 &
671                                          ( sa(k,j,i) - sa_init(k) )
[1337]672                IF ( sa_p(k,j,i) < 0.0_wp )  sa_p(k,j,i) = 0.1_wp * sa(k,j,i)
[736]673             ENDDO
674
675!
676!--          Calculate tendencies for the next Runge-Kutta step
677             IF ( timestep_scheme(1:5) == 'runge' )  THEN
678                IF ( intermediate_timestep_count == 1 )  THEN
679                   DO  k = nzb_s_inner(j,i)+1, nzt
680                      tsa_m(k,j,i) = tend(k,j,i)
681                   ENDDO
682                ELSEIF ( intermediate_timestep_count < &
683                         intermediate_timestep_count_max )  THEN
684                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]685                      tsa_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
686                                      5.3125_wp * tsa_m(k,j,i)
[736]687                   ENDDO
688                ENDIF
689             ENDIF
690
691!
692!--          Calculate density by the equation of state for seawater
693             CALL eqn_state_seawater( i, j )
694
695          ENDIF
696
697!
698!--       If required, compute prognostic equation for total water content /
699!--       scalar
700          IF ( humidity  .OR.  passive_scalar )  THEN
701
702!
703!--          Tendency-terms for total water content / scalar
[1337]704             tend(:,j,i) = 0.0_wp
[1001]705             IF ( timestep_scheme(1:5) == 'runge' ) &
[736]706             THEN
707                IF ( ws_scheme_sca )  THEN
708                   CALL advec_s_ws( i, j, q, 'q', flux_s_q, & 
709                                diss_s_q, flux_l_q, diss_l_q, i_omp_start, tn )
710                ELSE
711                   CALL advec_s_pw( i, j, q )
712                ENDIF
713             ELSE
714                CALL advec_s_up( i, j, q )
715             ENDIF
[1001]716             CALL diffusion_s( i, j, q, qsws, qswst, wall_qflux )
[1053]717     
[736]718!
[1361]719!--          If required compute decrease of total water content due to
720!--          precipitation
721             IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.              &
722                  precipitation )  THEN
723                CALL calc_precipitation( i, j )             
[736]724             ENDIF
725!
726!--          Sink or source of scalar concentration due to canopy elements
[1106]727             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 5 )
[736]728
[1053]729!
[1365]730!--          Large scale advection
731             IF ( large_scale_forcing )  THEN
732                CALL ls_advec( i, j, simulated_time, 'q' )
733             ENDIF
734
735!
[1380]736!--          Nudging
737             IF ( nudging )  CALL nudge( i, j, simulated_time, 'q' ) 
738
739!
[736]740!--          If required compute influence of large-scale subsidence/ascent
[1365]741             IF ( large_scale_subsidence  .AND.                                &
742                  .NOT. use_subsidence_tendencies )  THEN
743                CALL subsidence( i, j, tend, q, q_init, 3 )
[736]744             ENDIF
745
746             CALL user_actions( i, j, 'q-tendency' )
747
748!
749!--          Prognostic equation for total water content / scalar
750             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]751                q_p(k,j,i) = q(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
752                                                  tsc(3) * tq_m(k,j,i) )       &
753                                      - tsc(5) * rdf_sc(k) *                   &
754                                        ( q(k,j,i) - q_init(k) )
[1337]755                IF ( q_p(k,j,i) < 0.0_wp )  q_p(k,j,i) = 0.1_wp * q(k,j,i)
[736]756             ENDDO
757
758!
759!--          Calculate tendencies for the next Runge-Kutta step
760             IF ( timestep_scheme(1:5) == 'runge' )  THEN
761                IF ( intermediate_timestep_count == 1 )  THEN
762                   DO  k = nzb_s_inner(j,i)+1, nzt
763                      tq_m(k,j,i) = tend(k,j,i)
764                   ENDDO
765                ELSEIF ( intermediate_timestep_count < &
766                         intermediate_timestep_count_max )  THEN
767                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]768                      tq_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
769                                     5.3125_wp * tq_m(k,j,i)
[736]770                   ENDDO
771                ENDIF
772             ENDIF
773
[1053]774!
775!--          If required, calculate prognostic equations for rain water content
776!--          and rain drop concentration
[1115]777             IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.              &
778                  precipitation )  THEN
[1053]779!
780!--             Calculate prognostic equation for rain water content
[1337]781                tend(:,j,i) = 0.0_wp
[1053]782                IF ( timestep_scheme(1:5) == 'runge' ) &
783                THEN
784                   IF ( ws_scheme_sca )  THEN
785                      CALL advec_s_ws( i, j, qr, 'qr', flux_s_qr,       & 
786                                       diss_s_qr, flux_l_qr, diss_l_qr, &
787                                       i_omp_start, tn )
788                   ELSE
789                      CALL advec_s_pw( i, j, qr )
790                   ENDIF
791                ELSE
792                   CALL advec_s_up( i, j, qr )
793                ENDIF
794                CALL diffusion_s( i, j, qr, qrsws, qrswst, wall_qrflux )
795
[1115]796                CALL user_actions( i, j, 'qr-tendency' )
[1053]797!
798!--             Prognostic equation for rain water content
799                DO  k = nzb_s_inner(j,i)+1, nzt
[1115]800                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +  &
801                                                       tsc(3) * tqr_m(k,j,i) ) &
802                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
[1337]803                   IF ( qr_p(k,j,i) < 0.0_wp )  qr_p(k,j,i) = 0.0_wp
[1053]804                ENDDO
805!
806!--             Calculate tendencies for the next Runge-Kutta step
807                IF ( timestep_scheme(1:5) == 'runge' )  THEN
808                   IF ( intermediate_timestep_count == 1 )  THEN
809                      DO  k = nzb_s_inner(j,i)+1, nzt
810                         tqr_m(k,j,i) = tend(k,j,i)
811                      ENDDO
812                   ELSEIF ( intermediate_timestep_count < &
813                            intermediate_timestep_count_max )  THEN
814                      DO  k = nzb_s_inner(j,i)+1, nzt
[1337]815                         tqr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
816                                        5.3125_wp * tqr_m(k,j,i)
[1053]817                      ENDDO
818                   ENDIF
819                ENDIF
820
821!
822!--             Calculate prognostic equation for rain drop concentration.
[1337]823                tend(:,j,i) = 0.0_wp
[1053]824                IF ( timestep_scheme(1:5) == 'runge' )  THEN
825                   IF ( ws_scheme_sca )  THEN
[1115]826                      CALL advec_s_ws( i, j, nr, 'nr', flux_s_nr,    & 
827                                    diss_s_nr, flux_l_nr, diss_l_nr, &
828                                    i_omp_start, tn )
[1053]829                   ELSE
830                      CALL advec_s_pw( i, j, nr )
831                   ENDIF
832                ELSE
833                   CALL advec_s_up( i, j, nr )
834                ENDIF
835                CALL diffusion_s( i, j, nr, nrsws, nrswst, wall_nrflux )
836
[1115]837                CALL user_actions( i, j, 'nr-tendency' )
[1053]838!
839!--             Prognostic equation for rain drop concentration
840                DO  k = nzb_s_inner(j,i)+1, nzt
[1115]841                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +  &
842                                                       tsc(3) * tnr_m(k,j,i) ) &
843                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
[1337]844                   IF ( nr_p(k,j,i) < 0.0_wp )  nr_p(k,j,i) = 0.0_wp
[1053]845                ENDDO
846!
847!--             Calculate tendencies for the next Runge-Kutta step
848                IF ( timestep_scheme(1:5) == 'runge' )  THEN
849                   IF ( intermediate_timestep_count == 1 )  THEN
850                      DO  k = nzb_s_inner(j,i)+1, nzt
851                         tnr_m(k,j,i) = tend(k,j,i)
852                      ENDDO
853                   ELSEIF ( intermediate_timestep_count < &
854                            intermediate_timestep_count_max )  THEN
855                      DO  k = nzb_s_inner(j,i)+1, nzt
[1337]856                         tnr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
857                                        5.3125_wp * tnr_m(k,j,i)
[1053]858                      ENDDO
859                   ENDIF
860                ENDIF
861
862             ENDIF
863
[1128]864          ENDIF
865
[736]866!
867!--       If required, compute prognostic equation for turbulent kinetic
868!--       energy (TKE)
869          IF ( .NOT. constant_diffusion )  THEN
870
871!
872!--          Tendency-terms for TKE
[1337]873             tend(:,j,i) = 0.0_wp
[1332]874             IF ( timestep_scheme(1:5) == 'runge'  &
875                 .AND.  .NOT. use_upstream_for_tke )  THEN
[736]876                 IF ( ws_scheme_sca )  THEN
[1001]877                     CALL advec_s_ws( i, j, e, 'e', flux_s_e, diss_s_e, &
878                                      flux_l_e, diss_l_e , i_omp_start, tn )
[736]879                 ELSE
880                     CALL advec_s_pw( i, j, e )
881                 ENDIF
882             ELSE
883                CALL advec_s_up( i, j, e )
884             ENDIF
[1001]885             IF ( .NOT. humidity )  THEN
886                IF ( ocean )  THEN
887                   CALL diffusion_e( i, j, prho, prho_reference )
[736]888                ELSE
[1001]889                   CALL diffusion_e( i, j, pt, pt_reference )
[736]890                ENDIF
891             ELSE
[1001]892                CALL diffusion_e( i, j, vpt, pt_reference )
[736]893             ENDIF
894             CALL production_e( i, j )
895
896!
897!--          Additional sink term for flows through plant canopies
898             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 6 ) 
899
900             CALL user_actions( i, j, 'e-tendency' )
901
902!
903!--          Prognostic equation for TKE.
904!--          Eliminate negative TKE values, which can occur due to numerical
905!--          reasons in the course of the integration. In such cases the old
906!--          TKE value is reduced by 90%.
907             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]908                e_p(k,j,i) = e(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
909                                                  tsc(3) * te_m(k,j,i) )
[1337]910                IF ( e_p(k,j,i) < 0.0_wp )  e_p(k,j,i) = 0.1_wp * e(k,j,i)
[736]911             ENDDO
912
913!
914!--          Calculate tendencies for the next Runge-Kutta step
915             IF ( timestep_scheme(1:5) == 'runge' )  THEN
916                IF ( intermediate_timestep_count == 1 )  THEN
917                   DO  k = nzb_s_inner(j,i)+1, nzt
918                      te_m(k,j,i) = tend(k,j,i)
919                   ENDDO
920                ELSEIF ( intermediate_timestep_count < &
921                         intermediate_timestep_count_max )  THEN
922                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]923                      te_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
924                                     5.3125_wp * te_m(k,j,i)
[736]925                   ENDDO
926                ENDIF
927             ENDIF
928
929          ENDIF   ! TKE equation
930
931       ENDDO
932    ENDDO
933!$OMP END PARALLEL
934
935    CALL cpu_log( log_point(32), 'all progn.equations', 'stop' )
936
937
938 END SUBROUTINE prognostic_equations_cache
939
940
941!------------------------------------------------------------------------------!
[1682]942! Description:
943! ------------
944!> Version for vector machines
[736]945!------------------------------------------------------------------------------!
[1682]946 
947 SUBROUTINE prognostic_equations_vector
[736]948
[1682]949
[736]950    IMPLICIT NONE
951
[1682]952    INTEGER(iwp) ::  i    !<
953    INTEGER(iwp) ::  j    !<
954    INTEGER(iwp) ::  k    !<
[736]955
[1682]956    REAL(wp)     ::  sbt  !<
[736]957
[1320]958
[736]959!
[1361]960!-- If required, calculate cloud microphysical impacts (two-moment scheme)
961    IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                       &
962         ( intermediate_timestep_count == 1  .OR.                              &
963           call_microphysics_at_all_substeps )                                 &
964       )  THEN
965       CALL cpu_log( log_point(51), 'microphysics', 'start' )
966       CALL microphysics_control
967       CALL cpu_log( log_point(51), 'microphysics', 'stop' )
968    ENDIF
969
970!
[736]971!-- u-velocity component
972    CALL cpu_log( log_point(5), 'u-equation', 'start' )
973
[1337]974    tend = 0.0_wp
[1001]975    IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]976       IF ( ws_scheme_mom )  THEN
977          CALL advec_u_ws
978       ELSE
979          CALL advec_u_pw
980       ENDIF
981    ELSE
[1001]982       CALL advec_u_up
[736]983    ENDIF
[1001]984    CALL diffusion_u
[736]985    CALL coriolis( 1 )
[940]986    IF ( sloping_surface  .AND.  .NOT. neutral )  THEN
[1179]987       CALL buoyancy( pt, 1 )
[940]988    ENDIF
[736]989
990!
991!-- Drag by plant canopy
992    IF ( plant_canopy )  CALL plant_canopy_model( 1 )
993
994!
995!-- External pressure gradient
996    IF ( dp_external )  THEN
997       DO  i = nxlu, nxr
998          DO  j = nys, nyn
999             DO  k = dp_level_ind_b+1, nzt
1000                tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
1001             ENDDO
1002          ENDDO
1003       ENDDO
1004    ENDIF
1005
[1241]1006!
1007!-- Nudging
1008    IF ( nudging )  CALL nudge( simulated_time, 'u' ) 
1009
[736]1010    CALL user_actions( 'u-tendency' )
1011
1012!
1013!-- Prognostic equation for u-velocity component
1014    DO  i = nxlu, nxr
1015       DO  j = nys, nyn
1016          DO  k = nzb_u_inner(j,i)+1, nzt
[1001]1017             u_p(k,j,i) = u(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +          &
1018                                               tsc(3) * tu_m(k,j,i) )          &
[1398]1019                                   - tsc(5) * rdf(k) * ( u(k,j,i) - u_init(k) )
[736]1020          ENDDO
1021       ENDDO
1022    ENDDO
1023
1024!
1025!-- Calculate tendencies for the next Runge-Kutta step
1026    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1027       IF ( intermediate_timestep_count == 1 )  THEN
1028          DO  i = nxlu, nxr
1029             DO  j = nys, nyn
1030                DO  k = nzb_u_inner(j,i)+1, nzt
1031                   tu_m(k,j,i) = tend(k,j,i)
1032                ENDDO
1033             ENDDO
1034          ENDDO
1035       ELSEIF ( intermediate_timestep_count < &
1036                intermediate_timestep_count_max )  THEN
1037          DO  i = nxlu, nxr
1038             DO  j = nys, nyn
1039                DO  k = nzb_u_inner(j,i)+1, nzt
[1337]1040                   tu_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tu_m(k,j,i)
[736]1041                ENDDO
1042             ENDDO
1043          ENDDO
1044       ENDIF
1045    ENDIF
1046
1047    CALL cpu_log( log_point(5), 'u-equation', 'stop' )
1048
1049!
1050!-- v-velocity component
1051    CALL cpu_log( log_point(6), 'v-equation', 'start' )
1052
[1337]1053    tend = 0.0_wp
[1001]1054    IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]1055       IF ( ws_scheme_mom )  THEN
1056          CALL advec_v_ws
1057       ELSE
1058          CALL advec_v_pw
1059       END IF
1060    ELSE
[1001]1061       CALL advec_v_up
[736]1062    ENDIF
[1001]1063    CALL diffusion_v
[736]1064    CALL coriolis( 2 )
1065
1066!
1067!-- Drag by plant canopy
1068    IF ( plant_canopy )  CALL plant_canopy_model( 2 )
1069
1070!
1071!-- External pressure gradient
1072    IF ( dp_external )  THEN
1073       DO  i = nxl, nxr
1074          DO  j = nysv, nyn
1075             DO  k = dp_level_ind_b+1, nzt
1076                tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
1077             ENDDO
1078          ENDDO
1079       ENDDO
1080    ENDIF
1081
[1241]1082!
1083!-- Nudging
1084    IF ( nudging )  CALL nudge( simulated_time, 'v' ) 
1085
[736]1086    CALL user_actions( 'v-tendency' )
1087
1088!
1089!-- Prognostic equation for v-velocity component
1090    DO  i = nxl, nxr
1091       DO  j = nysv, nyn
1092          DO  k = nzb_v_inner(j,i)+1, nzt
[1001]1093             v_p(k,j,i) = v(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +          &
1094                                               tsc(3) * tv_m(k,j,i) )          &
[1398]1095                                   - tsc(5) * rdf(k) * ( v(k,j,i) - v_init(k) )
[736]1096          ENDDO
1097       ENDDO
1098    ENDDO
1099
1100!
1101!-- Calculate tendencies for the next Runge-Kutta step
1102    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1103       IF ( intermediate_timestep_count == 1 )  THEN
1104          DO  i = nxl, nxr
1105             DO  j = nysv, nyn
1106                DO  k = nzb_v_inner(j,i)+1, nzt
1107                   tv_m(k,j,i) = tend(k,j,i)
1108                ENDDO
1109             ENDDO
1110          ENDDO
1111       ELSEIF ( intermediate_timestep_count < &
1112                intermediate_timestep_count_max )  THEN
1113          DO  i = nxl, nxr
1114             DO  j = nysv, nyn
1115                DO  k = nzb_v_inner(j,i)+1, nzt
[1337]1116                   tv_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tv_m(k,j,i)
[736]1117                ENDDO
1118             ENDDO
1119          ENDDO
1120       ENDIF
1121    ENDIF
1122
1123    CALL cpu_log( log_point(6), 'v-equation', 'stop' )
1124
1125!
1126!-- w-velocity component
1127    CALL cpu_log( log_point(7), 'w-equation', 'start' )
1128
[1353]1129    tend = 0.0_wp
[1001]1130    IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]1131       IF ( ws_scheme_mom )  THEN
1132          CALL advec_w_ws
1133       ELSE
1134          CALL advec_w_pw
1135       ENDIF
1136    ELSE
[1001]1137       CALL advec_w_up
[736]1138    ENDIF
[1001]1139    CALL diffusion_w
[736]1140    CALL coriolis( 3 )
[940]1141
1142    IF ( .NOT. neutral )  THEN
1143       IF ( ocean )  THEN
[1179]1144          CALL buoyancy( rho, 3 )
[736]1145       ELSE
[940]1146          IF ( .NOT. humidity )  THEN
[1179]1147             CALL buoyancy( pt, 3 )
[940]1148          ELSE
[1179]1149             CALL buoyancy( vpt, 3 )
[940]1150          ENDIF
[736]1151       ENDIF
1152    ENDIF
1153
1154!
1155!-- Drag by plant canopy
1156    IF ( plant_canopy )  CALL plant_canopy_model( 3 )
1157
1158    CALL user_actions( 'w-tendency' )
1159
1160!
1161!-- Prognostic equation for w-velocity component
1162    DO  i = nxl, nxr
1163       DO  j = nys, nyn
1164          DO  k = nzb_w_inner(j,i)+1, nzt-1
[1001]1165             w_p(k,j,i) = w(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +          &
1166                                               tsc(3) * tw_m(k,j,i) )          &
1167                                   - tsc(5) * rdf(k) * w(k,j,i)
[736]1168          ENDDO
1169       ENDDO
1170    ENDDO
1171
1172!
1173!-- Calculate tendencies for the next Runge-Kutta step
1174    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1175       IF ( intermediate_timestep_count == 1 )  THEN
1176          DO  i = nxl, nxr
1177             DO  j = nys, nyn
1178                DO  k = nzb_w_inner(j,i)+1, nzt-1
1179                   tw_m(k,j,i) = tend(k,j,i)
1180                ENDDO
1181             ENDDO
1182          ENDDO
1183       ELSEIF ( intermediate_timestep_count < &
1184                intermediate_timestep_count_max )  THEN
1185          DO  i = nxl, nxr
1186             DO  j = nys, nyn
1187                DO  k = nzb_w_inner(j,i)+1, nzt-1
[1337]1188                   tw_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tw_m(k,j,i)
[736]1189                ENDDO
1190             ENDDO
1191          ENDDO
1192       ENDIF
1193    ENDIF
1194
1195    CALL cpu_log( log_point(7), 'w-equation', 'stop' )
1196
[940]1197
[736]1198!
[940]1199!-- If required, compute prognostic equation for potential temperature
1200    IF ( .NOT. neutral )  THEN
[736]1201
[940]1202       CALL cpu_log( log_point(13), 'pt-equation', 'start' )
1203
[736]1204!
[940]1205!--    pt-tendency terms with communication
1206       sbt = tsc(2)
1207       IF ( scalar_advec == 'bc-scheme' )  THEN
[736]1208
[940]1209          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
[736]1210!
[1001]1211!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1353]1212             sbt = 1.0_wp
[940]1213          ENDIF
[1337]1214          tend = 0.0_wp
[940]1215          CALL advec_s_bc( pt, 'pt' )
[1001]1216
[736]1217       ENDIF
[940]1218
1219!
1220!--    pt-tendency terms with no communication
[1001]1221       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1337]1222          tend = 0.0_wp
[1001]1223          IF ( timestep_scheme(1:5) == 'runge' )  THEN
[940]1224             IF ( ws_scheme_sca )  THEN
1225                CALL advec_s_ws( pt, 'pt' )
1226             ELSE
1227                CALL advec_s_pw( pt )
1228             ENDIF
1229          ELSE
[1001]1230             CALL advec_s_up( pt )
[940]1231          ENDIF
[736]1232       ENDIF
1233
[1001]1234       CALL diffusion_s( pt, shf, tswst, wall_heatflux )
1235
[736]1236!
[940]1237!--    If required compute heating/cooling due to long wave radiation processes
[1496]1238       IF ( cloud_top_radiation )  THEN
[940]1239          CALL calc_radiation
1240       ENDIF
[736]1241
1242!
[940]1243!--    If required compute impact of latent heat due to precipitation
[1361]1244       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
[940]1245          CALL impact_of_latent_heat
1246       ENDIF
[736]1247
1248!
[940]1249!--    Consideration of heat sources within the plant canopy
[1337]1250       IF ( plant_canopy .AND. ( cthf /= 0.0_wp ) ) THEN
[940]1251          CALL plant_canopy_model( 4 )
1252       ENDIF
[736]1253
[940]1254!
[1365]1255!--    Large scale advection
1256       IF ( large_scale_forcing )  THEN
1257          CALL ls_advec( simulated_time, 'pt' )
1258       ENDIF
1259
1260!
[1380]1261!--    Nudging
1262       IF ( nudging )  CALL nudge( simulated_time, 'pt' ) 
1263
1264!
[940]1265!--    If required compute influence of large-scale subsidence/ascent
[1365]1266       IF ( large_scale_subsidence  .AND.                                      &
1267            .NOT. use_subsidence_tendencies )  THEN
1268          CALL subsidence( tend, pt, pt_init, 2 )
[940]1269       ENDIF
[736]1270
[1585]1271!
1272!--    If required, add tendency due to radiative heating/cooling
1273       IF ( radiation .AND. radiation_scheme == 'rrtmg' )  THEN
1274          CALL radiation_tendency ( tend )
1275       ENDIF
1276
[940]1277       CALL user_actions( 'pt-tendency' )
[736]1278
1279!
[940]1280!--    Prognostic equation for potential temperature
1281       DO  i = nxl, nxr
1282          DO  j = nys, nyn
1283             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]1284                pt_p(k,j,i) = pt(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +        &
1285                                                    tsc(3) * tpt_m(k,j,i) )    &
1286                                        - tsc(5) * ( pt(k,j,i) - pt_init(k) ) *&
1287                                          ( rdf_sc(k) + ptdf_x(i) + ptdf_y(j) )
[940]1288             ENDDO
[736]1289          ENDDO
1290       ENDDO
1291
1292!
[940]1293!--    Calculate tendencies for the next Runge-Kutta step
1294       IF ( timestep_scheme(1:5) == 'runge' )  THEN
1295          IF ( intermediate_timestep_count == 1 )  THEN
1296             DO  i = nxl, nxr
1297                DO  j = nys, nyn
1298                   DO  k = nzb_s_inner(j,i)+1, nzt
1299                      tpt_m(k,j,i) = tend(k,j,i)
1300                   ENDDO
[736]1301                ENDDO
1302             ENDDO
[940]1303          ELSEIF ( intermediate_timestep_count < &
1304                   intermediate_timestep_count_max )  THEN
1305             DO  i = nxl, nxr
1306                DO  j = nys, nyn
1307                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]1308                      tpt_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
1309                                      5.3125_wp * tpt_m(k,j,i)
[940]1310                   ENDDO
[736]1311                ENDDO
1312             ENDDO
[940]1313          ENDIF
[736]1314       ENDIF
[940]1315
1316       CALL cpu_log( log_point(13), 'pt-equation', 'stop' )
1317
[736]1318    ENDIF
1319
1320!
1321!-- If required, compute prognostic equation for salinity
1322    IF ( ocean )  THEN
1323
1324       CALL cpu_log( log_point(37), 'sa-equation', 'start' )
1325
1326!
1327!--    sa-tendency terms with communication
1328       sbt = tsc(2)
1329       IF ( scalar_advec == 'bc-scheme' )  THEN
1330
1331          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
1332!
[1001]1333!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1353]1334             sbt = 1.0_wp
[736]1335          ENDIF
[1337]1336          tend = 0.0_wp
[736]1337          CALL advec_s_bc( sa, 'sa' )
[1001]1338
[736]1339       ENDIF
1340
1341!
1342!--    sa-tendency terms with no communication
[1001]1343       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1353]1344          tend = 0.0_wp
[1001]1345          IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]1346             IF ( ws_scheme_sca )  THEN
1347                 CALL advec_s_ws( sa, 'sa' )
1348             ELSE
1349                 CALL advec_s_pw( sa )
1350             ENDIF
1351          ELSE
[1001]1352             CALL advec_s_up( sa )
[736]1353          ENDIF
1354       ENDIF
[1001]1355
1356       CALL diffusion_s( sa, saswsb, saswst, wall_salinityflux )
[736]1357       
1358       CALL user_actions( 'sa-tendency' )
1359
1360!
1361!--    Prognostic equation for salinity
1362       DO  i = nxl, nxr
1363          DO  j = nys, nyn
1364             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]1365                sa_p(k,j,i) = sa(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +        &
1366                                                    tsc(3) * tsa_m(k,j,i) )    &
1367                                        - tsc(5) * rdf_sc(k) *                 &
1368                                          ( sa(k,j,i) - sa_init(k) )
[1337]1369                IF ( sa_p(k,j,i) < 0.0_wp )  sa_p(k,j,i) = 0.1_wp * sa(k,j,i)
[736]1370             ENDDO
1371          ENDDO
1372       ENDDO
1373
1374!
1375!--    Calculate tendencies for the next Runge-Kutta step
1376       IF ( timestep_scheme(1:5) == 'runge' )  THEN
1377          IF ( intermediate_timestep_count == 1 )  THEN
1378             DO  i = nxl, nxr
1379                DO  j = nys, nyn
1380                   DO  k = nzb_s_inner(j,i)+1, nzt
1381                      tsa_m(k,j,i) = tend(k,j,i)
1382                   ENDDO
1383                ENDDO
1384             ENDDO
1385          ELSEIF ( intermediate_timestep_count < &
1386                   intermediate_timestep_count_max )  THEN
1387             DO  i = nxl, nxr
1388                DO  j = nys, nyn
1389                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]1390                      tsa_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
1391                                      5.3125_wp * tsa_m(k,j,i)
[736]1392                   ENDDO
1393                ENDDO
1394             ENDDO
1395          ENDIF
1396       ENDIF
1397
1398       CALL cpu_log( log_point(37), 'sa-equation', 'stop' )
1399
1400!
1401!--    Calculate density by the equation of state for seawater
1402       CALL cpu_log( log_point(38), 'eqns-seawater', 'start' )
1403       CALL eqn_state_seawater
1404       CALL cpu_log( log_point(38), 'eqns-seawater', 'stop' )
1405
1406    ENDIF
1407
1408!
1409!-- If required, compute prognostic equation for total water content / scalar
1410    IF ( humidity  .OR.  passive_scalar )  THEN
1411
1412       CALL cpu_log( log_point(29), 'q/s-equation', 'start' )
1413
1414!
1415!--    Scalar/q-tendency terms with communication
1416       sbt = tsc(2)
1417       IF ( scalar_advec == 'bc-scheme' )  THEN
1418
1419          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
1420!
[1001]1421!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1337]1422             sbt = 1.0_wp
[736]1423          ENDIF
[1337]1424          tend = 0.0_wp
[736]1425          CALL advec_s_bc( q, 'q' )
[1001]1426
[736]1427       ENDIF
1428
1429!
1430!--    Scalar/q-tendency terms with no communication
[1001]1431       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1337]1432          tend = 0.0_wp
[1001]1433          IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]1434             IF ( ws_scheme_sca )  THEN
1435                CALL advec_s_ws( q, 'q' )
1436             ELSE
1437                CALL advec_s_pw( q )
1438             ENDIF
1439          ELSE
[1001]1440             CALL advec_s_up( q )
[736]1441          ENDIF
1442       ENDIF
[1001]1443
1444       CALL diffusion_s( q, qsws, qswst, wall_qflux )
[736]1445       
1446!
1447!--    If required compute decrease of total water content due to
1448!--    precipitation
[1361]1449       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
[736]1450          CALL calc_precipitation
1451       ENDIF
1452
1453!
1454!--    Sink or source of scalar concentration due to canopy elements
1455       IF ( plant_canopy ) CALL plant_canopy_model( 5 )
[1365]1456
[736]1457!
[1365]1458!--    Large scale advection
1459       IF ( large_scale_forcing )  THEN
1460          CALL ls_advec( simulated_time, 'q' )
1461       ENDIF
1462
1463!
[1380]1464!--    Nudging
1465       IF ( nudging )  CALL nudge( simulated_time, 'q' ) 
1466
1467!
[736]1468!--    If required compute influence of large-scale subsidence/ascent
[1365]1469       IF ( large_scale_subsidence  .AND.                                      &
1470            .NOT. use_subsidence_tendencies )  THEN
1471         CALL subsidence( tend, q, q_init, 3 )
[736]1472       ENDIF
1473
1474       CALL user_actions( 'q-tendency' )
1475
1476!
1477!--    Prognostic equation for total water content / scalar
1478       DO  i = nxl, nxr
1479          DO  j = nys, nyn
1480             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]1481                q_p(k,j,i) = q(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +          &
1482                                                  tsc(3) * tq_m(k,j,i) )       &
1483                                      - tsc(5) * rdf_sc(k) *                   &
1484                                        ( q(k,j,i) - q_init(k) )
[1337]1485                IF ( q_p(k,j,i) < 0.0_wp )  q_p(k,j,i) = 0.1_wp * q(k,j,i)
[736]1486             ENDDO
1487          ENDDO
1488       ENDDO
1489
1490!
1491!--    Calculate tendencies for the next Runge-Kutta step
1492       IF ( timestep_scheme(1:5) == 'runge' )  THEN
1493          IF ( intermediate_timestep_count == 1 )  THEN
1494             DO  i = nxl, nxr
1495                DO  j = nys, nyn
1496                   DO  k = nzb_s_inner(j,i)+1, nzt
1497                      tq_m(k,j,i) = tend(k,j,i)
1498                   ENDDO
1499                ENDDO
1500             ENDDO
1501          ELSEIF ( intermediate_timestep_count < &
1502                   intermediate_timestep_count_max )  THEN
1503             DO  i = nxl, nxr
1504                DO  j = nys, nyn
1505                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]1506                      tq_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tq_m(k,j,i)
[736]1507                   ENDDO
1508                ENDDO
1509             ENDDO
1510          ENDIF
1511       ENDIF
1512
1513       CALL cpu_log( log_point(29), 'q/s-equation', 'stop' )
1514
[1361]1515!
1516!--    If required, calculate prognostic equations for rain water content
1517!--    and rain drop concentration
1518       IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  precipitation )  THEN
1519
1520          CALL cpu_log( log_point(52), 'qr-equation', 'start' )
1521
1522!
1523!--       Calculate prognostic equation for rain water content
1524          sbt = tsc(2)
1525          IF ( scalar_advec == 'bc-scheme' )  THEN
1526
1527             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
1528!
1529!--             Bott-Chlond scheme always uses Euler time step. Thus:
1530                sbt = 1.0_wp
1531             ENDIF
1532             tend = 0.0_wp
1533             CALL advec_s_bc( qr, 'qr' )
1534
1535          ENDIF
1536
1537!
1538!--       qr-tendency terms with no communication
1539          IF ( scalar_advec /= 'bc-scheme' )  THEN
1540             tend = 0.0_wp
1541             IF ( timestep_scheme(1:5) == 'runge' )  THEN
1542                IF ( ws_scheme_sca )  THEN
1543                   CALL advec_s_ws( qr, 'qr' )
1544                ELSE
1545                   CALL advec_s_pw( qr )
1546                ENDIF
1547             ELSE
1548                CALL advec_s_up( qr )
1549             ENDIF
1550          ENDIF
1551
1552          CALL diffusion_s( qr, qrsws, qrswst, wall_qrflux )
1553
1554          CALL user_actions( 'qr-tendency' )
1555
1556!
1557!--       Prognostic equation for rain water content
1558          DO  i = nxl, nxr
1559             DO  j = nys, nyn
1560                DO  k = nzb_s_inner(j,i)+1, nzt
1561                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
1562                                                     tsc(3) * tqr_m(k,j,i) )   &
1563                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
1564                   IF ( qr_p(k,j,i) < 0.0_wp )  qr_p(k,j,i) = 0.0_wp
1565                ENDDO
1566             ENDDO
1567          ENDDO
1568
1569!
1570!--       Calculate tendencies for the next Runge-Kutta step
1571          IF ( timestep_scheme(1:5) == 'runge' )  THEN
1572             IF ( intermediate_timestep_count == 1 )  THEN
1573                DO  i = nxl, nxr
1574                   DO  j = nys, nyn
1575                      DO  k = nzb_s_inner(j,i)+1, nzt
1576                         tqr_m(k,j,i) = tend(k,j,i)
1577                      ENDDO
1578                   ENDDO
1579                ENDDO
1580             ELSEIF ( intermediate_timestep_count < &
1581                      intermediate_timestep_count_max )  THEN
1582                DO  i = nxl, nxr
1583                   DO  j = nys, nyn
1584                      DO  k = nzb_s_inner(j,i)+1, nzt
1585                         tqr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * &
1586                                                                   tqr_m(k,j,i)
1587                      ENDDO
1588                   ENDDO
1589                ENDDO
1590             ENDIF
1591          ENDIF
1592
1593          CALL cpu_log( log_point(52), 'qr-equation', 'stop' )
1594          CALL cpu_log( log_point(53), 'nr-equation', 'start' )
1595
1596!
1597!--       Calculate prognostic equation for rain drop concentration
1598          sbt = tsc(2)
1599          IF ( scalar_advec == 'bc-scheme' )  THEN
1600
1601             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
1602!
1603!--             Bott-Chlond scheme always uses Euler time step. Thus:
1604                sbt = 1.0_wp
1605             ENDIF
1606             tend = 0.0_wp
1607             CALL advec_s_bc( nr, 'nr' )
1608
1609          ENDIF
1610
1611!
1612!--       nr-tendency terms with no communication
1613          IF ( scalar_advec /= 'bc-scheme' )  THEN
1614             tend = 0.0_wp
1615             IF ( timestep_scheme(1:5) == 'runge' )  THEN
1616                IF ( ws_scheme_sca )  THEN
1617                   CALL advec_s_ws( nr, 'nr' )
1618                ELSE
1619                   CALL advec_s_pw( nr )
1620                ENDIF
1621             ELSE
1622                CALL advec_s_up( nr )
1623             ENDIF
1624          ENDIF
1625
1626          CALL diffusion_s( nr, nrsws, nrswst, wall_nrflux )
1627
1628          CALL user_actions( 'nr-tendency' )
1629
1630!
1631!--       Prognostic equation for rain drop concentration
1632          DO  i = nxl, nxr
1633             DO  j = nys, nyn
1634                DO  k = nzb_s_inner(j,i)+1, nzt
1635                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
1636                                                     tsc(3) * tnr_m(k,j,i) )   &
1637                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
1638                   IF ( nr_p(k,j,i) < 0.0_wp )  nr_p(k,j,i) = 0.0_wp
1639                ENDDO
1640             ENDDO
1641          ENDDO
1642
1643!
1644!--       Calculate tendencies for the next Runge-Kutta step
1645          IF ( timestep_scheme(1:5) == 'runge' )  THEN
1646             IF ( intermediate_timestep_count == 1 )  THEN
1647                DO  i = nxl, nxr
1648                   DO  j = nys, nyn
1649                      DO  k = nzb_s_inner(j,i)+1, nzt
1650                         tnr_m(k,j,i) = tend(k,j,i)
1651                      ENDDO
1652                   ENDDO
1653                ENDDO
1654             ELSEIF ( intermediate_timestep_count < &
1655                      intermediate_timestep_count_max )  THEN
1656                DO  i = nxl, nxr
1657                   DO  j = nys, nyn
1658                      DO  k = nzb_s_inner(j,i)+1, nzt
1659                         tnr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * &
1660                                                                   tnr_m(k,j,i)
1661                      ENDDO
1662                   ENDDO
1663                ENDDO
1664             ENDIF
1665          ENDIF
1666
1667          CALL cpu_log( log_point(53), 'nr-equation', 'stop' )
1668
1669       ENDIF
1670
[736]1671    ENDIF
1672
1673!
1674!-- If required, compute prognostic equation for turbulent kinetic
1675!-- energy (TKE)
1676    IF ( .NOT. constant_diffusion )  THEN
1677
1678       CALL cpu_log( log_point(16), 'tke-equation', 'start' )
1679
1680       sbt = tsc(2)
1681       IF ( .NOT. use_upstream_for_tke )  THEN
1682          IF ( scalar_advec == 'bc-scheme' )  THEN
1683
1684             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
1685!
[1001]1686!--             Bott-Chlond scheme always uses Euler time step. Thus:
[1337]1687                sbt = 1.0_wp
[736]1688             ENDIF
[1337]1689             tend = 0.0_wp
[736]1690             CALL advec_s_bc( e, 'e' )
[1001]1691
[736]1692          ENDIF
1693       ENDIF
1694
1695!
1696!--    TKE-tendency terms with no communication
[1001]1697       IF ( scalar_advec /= 'bc-scheme'  .OR.  use_upstream_for_tke )  THEN
[736]1698          IF ( use_upstream_for_tke )  THEN
[1337]1699             tend = 0.0_wp
[736]1700             CALL advec_s_up( e )
1701          ELSE
[1337]1702             tend = 0.0_wp
[1001]1703             IF ( timestep_scheme(1:5) == 'runge' )  THEN
[736]1704                IF ( ws_scheme_sca )  THEN
1705                   CALL advec_s_ws( e, 'e' )
1706                ELSE
1707                   CALL advec_s_pw( e )
1708                ENDIF
1709             ELSE
[1001]1710                CALL advec_s_up( e )
[736]1711             ENDIF
1712          ENDIF
[1001]1713       ENDIF
1714
1715       IF ( .NOT. humidity )  THEN
1716          IF ( ocean )  THEN
1717             CALL diffusion_e( prho, prho_reference )
[736]1718          ELSE
[1001]1719             CALL diffusion_e( pt, pt_reference )
[736]1720          ENDIF
[1001]1721       ELSE
1722          CALL diffusion_e( vpt, pt_reference )
[736]1723       ENDIF
[1001]1724
[736]1725       CALL production_e
1726
1727!
1728!--    Additional sink term for flows through plant canopies
1729       IF ( plant_canopy )  CALL plant_canopy_model( 6 )
1730       CALL user_actions( 'e-tendency' )
1731
1732!
1733!--    Prognostic equation for TKE.
1734!--    Eliminate negative TKE values, which can occur due to numerical
1735!--    reasons in the course of the integration. In such cases the old TKE
1736!--    value is reduced by 90%.
1737       DO  i = nxl, nxr
1738          DO  j = nys, nyn
1739             DO  k = nzb_s_inner(j,i)+1, nzt
[1001]1740                e_p(k,j,i) = e(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +          &
1741                                                  tsc(3) * te_m(k,j,i) )
[1337]1742                IF ( e_p(k,j,i) < 0.0_wp )  e_p(k,j,i) = 0.1_wp * e(k,j,i)
[736]1743             ENDDO
1744          ENDDO
1745       ENDDO
1746
1747!
1748!--    Calculate tendencies for the next Runge-Kutta step
1749       IF ( timestep_scheme(1:5) == 'runge' )  THEN
1750          IF ( intermediate_timestep_count == 1 )  THEN
1751             DO  i = nxl, nxr
1752                DO  j = nys, nyn
1753                   DO  k = nzb_s_inner(j,i)+1, nzt
1754                      te_m(k,j,i) = tend(k,j,i)
1755                   ENDDO
1756                ENDDO
1757             ENDDO
1758          ELSEIF ( intermediate_timestep_count < &
1759                   intermediate_timestep_count_max )  THEN
1760             DO  i = nxl, nxr
1761                DO  j = nys, nyn
1762                   DO  k = nzb_s_inner(j,i)+1, nzt
[1337]1763                      te_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * te_m(k,j,i)
[736]1764                   ENDDO
1765                ENDDO
1766             ENDDO
1767          ENDIF
1768       ENDIF
1769
1770       CALL cpu_log( log_point(16), 'tke-equation', 'stop' )
1771
1772    ENDIF
1773
1774 END SUBROUTINE prognostic_equations_vector
1775
1776
[1015]1777!------------------------------------------------------------------------------!
[1682]1778! Description:
1779! ------------
1780!> Version for accelerator boards
[1015]1781!------------------------------------------------------------------------------!
[1682]1782 
1783 SUBROUTINE prognostic_equations_acc
[1015]1784
[1682]1785
[1015]1786    IMPLICIT NONE
1787
[1682]1788    INTEGER(iwp) ::  i           !<
1789    INTEGER(iwp) ::  j           !<
1790    INTEGER(iwp) ::  k           !<
1791    INTEGER(iwp) ::  runge_step  !<
[1015]1792
[1682]1793    REAL(wp)     ::  sbt         !<
[1320]1794
[1015]1795!
1796!-- Set switch for intermediate Runge-Kutta step
1797    runge_step = 0
1798    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1799       IF ( intermediate_timestep_count == 1 )  THEN
1800          runge_step = 1
1801       ELSEIF ( intermediate_timestep_count < &
1802                intermediate_timestep_count_max )  THEN
1803          runge_step = 2
1804       ENDIF
1805    ENDIF
1806
1807!
[1361]1808!-- If required, calculate cloud microphysical impacts (two-moment scheme)
1809    IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.                       &
1810         ( intermediate_timestep_count == 1  .OR.                              &
1811           call_microphysics_at_all_substeps )                                 &
1812       )  THEN
1813       CALL cpu_log( log_point(51), 'microphysics', 'start' )
1814       CALL microphysics_control
1815       CALL cpu_log( log_point(51), 'microphysics', 'stop' )
1816    ENDIF
1817
1818!
[1015]1819!-- u-velocity component
[1374]1820!++ Statistics still not completely ported to accelerators
[1179]1821    !$acc update device( hom, ref_state )
[1015]1822    CALL cpu_log( log_point(5), 'u-equation', 'start' )
1823
1824    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1825       IF ( ws_scheme_mom )  THEN
1826          CALL advec_u_ws_acc
1827       ELSE
[1337]1828          tend = 0.0_wp   ! to be removed later??
[1015]1829          CALL advec_u_pw
1830       ENDIF
1831    ELSE
1832       CALL advec_u_up
1833    ENDIF
1834    CALL diffusion_u_acc
1835    CALL coriolis_acc( 1 )
1836    IF ( sloping_surface  .AND.  .NOT. neutral )  THEN
[1179]1837       CALL buoyancy( pt, 1 )
[1015]1838    ENDIF
1839
1840!
1841!-- Drag by plant canopy
1842    IF ( plant_canopy )  CALL plant_canopy_model( 1 )
1843
1844!
1845!-- External pressure gradient
1846    IF ( dp_external )  THEN
[1128]1847       DO  i = i_left, i_right
1848          DO  j = j_south, j_north
[1015]1849             DO  k = dp_level_ind_b+1, nzt
1850                tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
1851             ENDDO
1852          ENDDO
1853       ENDDO
1854    ENDIF
1855
[1246]1856!
1857!-- Nudging
1858    IF ( nudging )  CALL nudge( simulated_time, 'u' ) 
1859
[1015]1860    CALL user_actions( 'u-tendency' )
1861
1862!
1863!-- Prognostic equation for u-velocity component
[1398]1864    !$acc kernels present( nzb_u_inner, rdf, tend, tu_m, u, u_init, u_p )
[1257]1865    !$acc loop independent
[1128]1866    DO  i = i_left, i_right
[1257]1867       !$acc loop independent
[1128]1868       DO  j = j_south, j_north
[1257]1869          !$acc loop independent
[1015]1870          DO  k = 1, nzt
1871             IF ( k > nzb_u_inner(j,i) )  THEN
1872                u_p(k,j,i) = u(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
1873                                                  tsc(3) * tu_m(k,j,i) )       &
[1398]1874                                      - tsc(5) * rdf(k) * ( u(k,j,i) - u_init(k) )
[1015]1875!
1876!--             Tendencies for the next Runge-Kutta step
1877                IF ( runge_step == 1 )  THEN
1878                   tu_m(k,j,i) = tend(k,j,i)
1879                ELSEIF ( runge_step == 2 )  THEN
[1337]1880                   tu_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tu_m(k,j,i)
[1015]1881                ENDIF
1882             ENDIF
1883          ENDDO
1884       ENDDO
1885    ENDDO
1886    !$acc end kernels
1887
1888    CALL cpu_log( log_point(5), 'u-equation', 'stop' )
1889
1890!
1891!-- v-velocity component
1892    CALL cpu_log( log_point(6), 'v-equation', 'start' )
1893
1894    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1895       IF ( ws_scheme_mom )  THEN
1896          CALL advec_v_ws_acc
1897       ELSE
[1337]1898          tend = 0.0_wp    ! to be removed later??
[1015]1899          CALL advec_v_pw
1900       END IF
1901    ELSE
1902       CALL advec_v_up
1903    ENDIF
1904    CALL diffusion_v_acc
1905    CALL coriolis_acc( 2 )
1906
1907!
1908!-- Drag by plant canopy
1909    IF ( plant_canopy )  CALL plant_canopy_model( 2 )
1910
1911!
1912!-- External pressure gradient
1913    IF ( dp_external )  THEN
[1128]1914       DO  i = i_left, i_right
1915          DO  j = j_south, j_north
[1015]1916             DO  k = dp_level_ind_b+1, nzt
1917                tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
1918             ENDDO
1919          ENDDO
1920       ENDDO
1921    ENDIF
1922
[1246]1923!
1924!-- Nudging
1925    IF ( nudging )  CALL nudge( simulated_time, 'v' ) 
1926
[1015]1927    CALL user_actions( 'v-tendency' )
1928
1929!
1930!-- Prognostic equation for v-velocity component
[1398]1931    !$acc kernels present( nzb_v_inner, rdf, tend, tv_m, v, v_init, v_p )
[1257]1932    !$acc loop independent
[1128]1933    DO  i = i_left, i_right
[1257]1934       !$acc loop independent
[1128]1935       DO  j = j_south, j_north
[1257]1936          !$acc loop independent
[1015]1937          DO  k = 1, nzt
1938             IF ( k > nzb_v_inner(j,i) )  THEN
1939                v_p(k,j,i) = v(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
1940                                                  tsc(3) * tv_m(k,j,i) )       &
[1398]1941                                      - tsc(5) * rdf(k) * ( v(k,j,i) - v_init(k) )
[1015]1942!
1943!--             Tendencies for the next Runge-Kutta step
1944                IF ( runge_step == 1 )  THEN
1945                   tv_m(k,j,i) = tend(k,j,i)
1946                ELSEIF ( runge_step == 2 )  THEN
[1337]1947                   tv_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tv_m(k,j,i)
[1015]1948                ENDIF
1949             ENDIF
1950          ENDDO
1951       ENDDO
1952    ENDDO
1953    !$acc end kernels
1954
1955    CALL cpu_log( log_point(6), 'v-equation', 'stop' )
1956
1957!
1958!-- w-velocity component
1959    CALL cpu_log( log_point(7), 'w-equation', 'start' )
1960
1961    IF ( timestep_scheme(1:5) == 'runge' )  THEN
1962       IF ( ws_scheme_mom )  THEN
1963          CALL advec_w_ws_acc
1964       ELSE
[1337]1965          tend = 0.0_wp    ! to be removed later??
[1015]1966          CALL advec_w_pw
1967       ENDIF
1968    ELSE
1969       CALL advec_w_up
1970    ENDIF
1971    CALL diffusion_w_acc
1972    CALL coriolis_acc( 3 )
1973
1974    IF ( .NOT. neutral )  THEN
1975       IF ( ocean )  THEN
[1179]1976          CALL buoyancy( rho, 3 )
[1015]1977       ELSE
1978          IF ( .NOT. humidity )  THEN
[1179]1979             CALL buoyancy_acc( pt, 3 )
[1015]1980          ELSE
[1179]1981             CALL buoyancy( vpt, 3 )
[1015]1982          ENDIF
1983       ENDIF
1984    ENDIF
1985
1986!
1987!-- Drag by plant canopy
1988    IF ( plant_canopy )  CALL plant_canopy_model( 3 )
1989
1990    CALL user_actions( 'w-tendency' )
1991
1992!
1993!-- Prognostic equation for w-velocity component
1994    !$acc kernels present( nzb_w_inner, rdf, tend, tw_m, w, w_p )
[1257]1995    !$acc loop independent
[1128]1996    DO  i = i_left, i_right
[1257]1997       !$acc loop independent
[1128]1998       DO  j = j_south, j_north
[1257]1999          !$acc loop independent
[1015]2000          DO  k = 1, nzt-1
2001             IF ( k > nzb_w_inner(j,i) )  THEN
2002                w_p(k,j,i) = w(k,j,i) + dt_3d * ( tsc(2) * tend(k,j,i) +       &
2003                                                  tsc(3) * tw_m(k,j,i) )       &
2004                                      - tsc(5) * rdf(k) * w(k,j,i)
2005   !
2006   !--          Tendencies for the next Runge-Kutta step
2007                IF ( runge_step == 1 )  THEN
2008                   tw_m(k,j,i) = tend(k,j,i)
2009                ELSEIF ( runge_step == 2 )  THEN
[1337]2010                   tw_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tw_m(k,j,i)
[1015]2011                ENDIF
2012             ENDIF
2013          ENDDO
2014       ENDDO
2015    ENDDO
2016    !$acc end kernels
2017
2018    CALL cpu_log( log_point(7), 'w-equation', 'stop' )
2019
2020
2021!
2022!-- If required, compute prognostic equation for potential temperature
2023    IF ( .NOT. neutral )  THEN
2024
2025       CALL cpu_log( log_point(13), 'pt-equation', 'start' )
2026
2027!
2028!--    pt-tendency terms with communication
2029       sbt = tsc(2)
2030       IF ( scalar_advec == 'bc-scheme' )  THEN
2031
2032          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2033!
2034!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1353]2035             sbt = 1.0_wp
[1015]2036          ENDIF
[1337]2037          tend = 0.0_wp
[1015]2038          CALL advec_s_bc( pt, 'pt' )
2039
2040       ENDIF
2041
2042!
2043!--    pt-tendency terms with no communication
2044       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1337]2045          tend = 0.0_wp
[1015]2046          IF ( timestep_scheme(1:5) == 'runge' )  THEN
2047             IF ( ws_scheme_sca )  THEN
2048                CALL advec_s_ws_acc( pt, 'pt' )
2049             ELSE
[1337]2050                tend = 0.0_wp    ! to be removed later??
[1015]2051                CALL advec_s_pw( pt )
2052             ENDIF
2053          ELSE
2054             CALL advec_s_up( pt )
2055          ENDIF
2056       ENDIF
2057
2058       CALL diffusion_s_acc( pt, shf, tswst, wall_heatflux )
2059
2060!
2061!--    If required compute heating/cooling due to long wave radiation processes
[1496]2062       IF ( cloud_top_radiation )  THEN
[1015]2063          CALL calc_radiation
2064       ENDIF
2065
2066!
2067!--    If required compute impact of latent heat due to precipitation
[1361]2068       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
[1015]2069          CALL impact_of_latent_heat
2070       ENDIF
2071
2072!
2073!--    Consideration of heat sources within the plant canopy
[1337]2074       IF ( plant_canopy .AND. ( cthf /= 0.0_wp ) ) THEN
[1015]2075          CALL plant_canopy_model( 4 )
2076       ENDIF
2077
2078!
[1365]2079!--    Large scale advection
2080       IF ( large_scale_forcing )  THEN
2081          CALL ls_advec( simulated_time, 'pt' )
2082       ENDIF
2083
2084!
[1380]2085!--    Nudging
2086       IF ( nudging )  CALL nudge( simulated_time, 'pt' ) 
2087
2088!
[1015]2089!--    If required compute influence of large-scale subsidence/ascent
[1365]2090       IF ( large_scale_subsidence  .AND.                                      &
2091            .NOT. use_subsidence_tendencies )  THEN
2092          CALL subsidence( tend, pt, pt_init, 2 )
[1015]2093       ENDIF
2094
2095       CALL user_actions( 'pt-tendency' )
2096
2097!
2098!--    Prognostic equation for potential temperature
2099       !$acc kernels present( nzb_s_inner, rdf_sc, ptdf_x, ptdf_y, pt_init ) &
2100       !$acc         present( tend, tpt_m, pt, pt_p )
[1257]2101       !$acc loop independent
[1128]2102       DO  i = i_left, i_right
[1257]2103          !$acc loop independent
[1128]2104          DO  j = j_south, j_north
[1257]2105             !$acc loop independent
[1015]2106             DO  k = 1, nzt
2107                IF ( k > nzb_s_inner(j,i) )  THEN
2108                   pt_p(k,j,i) = pt(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +        &
2109                                                       tsc(3) * tpt_m(k,j,i) )    &
2110                                           - tsc(5) * ( pt(k,j,i) - pt_init(k) ) *&
2111                                             ( rdf_sc(k) + ptdf_x(i) + ptdf_y(j) )
2112!
2113!--                Tendencies for the next Runge-Kutta step
2114                   IF ( runge_step == 1 )  THEN
2115                      tpt_m(k,j,i) = tend(k,j,i)
2116                   ELSEIF ( runge_step == 2 )  THEN
[1337]2117                      tpt_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tpt_m(k,j,i)
[1015]2118                   ENDIF
2119                ENDIF
2120             ENDDO
2121          ENDDO
2122       ENDDO
2123       !$acc end kernels
2124
2125       CALL cpu_log( log_point(13), 'pt-equation', 'stop' )
2126
2127    ENDIF
2128
2129!
2130!-- If required, compute prognostic equation for salinity
2131    IF ( ocean )  THEN
2132
2133       CALL cpu_log( log_point(37), 'sa-equation', 'start' )
2134
2135!
2136!--    sa-tendency terms with communication
2137       sbt = tsc(2)
2138       IF ( scalar_advec == 'bc-scheme' )  THEN
2139
2140          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2141!
2142!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1337]2143             sbt = 1.0_wp
[1015]2144          ENDIF
[1337]2145          tend = 0.0_wp
[1015]2146          CALL advec_s_bc( sa, 'sa' )
2147
2148       ENDIF
2149
2150!
2151!--    sa-tendency terms with no communication
2152       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1337]2153          tend = 0.0_wp
[1015]2154          IF ( timestep_scheme(1:5) == 'runge' )  THEN
2155             IF ( ws_scheme_sca )  THEN
2156                 CALL advec_s_ws( sa, 'sa' )
2157             ELSE
2158                 CALL advec_s_pw( sa )
2159             ENDIF
2160          ELSE
2161             CALL advec_s_up( sa )
2162          ENDIF
2163       ENDIF
2164
2165       CALL diffusion_s( sa, saswsb, saswst, wall_salinityflux )
2166
2167       CALL user_actions( 'sa-tendency' )
2168
2169!
2170!--    Prognostic equation for salinity
[1128]2171       DO  i = i_left, i_right
2172          DO  j = j_south, j_north
[1015]2173             DO  k = nzb_s_inner(j,i)+1, nzt
2174                sa_p(k,j,i) = sa(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +        &
2175                                                    tsc(3) * tsa_m(k,j,i) )    &
2176                                        - tsc(5) * rdf_sc(k) *                 &
2177                                          ( sa(k,j,i) - sa_init(k) )
[1337]2178                IF ( sa_p(k,j,i) < 0.0_wp )  sa_p(k,j,i) = 0.1_wp * sa(k,j,i)
[1015]2179!
2180!--             Tendencies for the next Runge-Kutta step
2181                IF ( runge_step == 1 )  THEN
2182                   tsa_m(k,j,i) = tend(k,j,i)
2183                ELSEIF ( runge_step == 2 )  THEN
[1337]2184                   tsa_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tsa_m(k,j,i)
[1015]2185                ENDIF
2186             ENDDO
2187          ENDDO
2188       ENDDO
2189
2190       CALL cpu_log( log_point(37), 'sa-equation', 'stop' )
2191
2192!
2193!--    Calculate density by the equation of state for seawater
2194       CALL cpu_log( log_point(38), 'eqns-seawater', 'start' )
2195       CALL eqn_state_seawater
2196       CALL cpu_log( log_point(38), 'eqns-seawater', 'stop' )
2197
2198    ENDIF
2199
2200!
2201!-- If required, compute prognostic equation for total water content / scalar
2202    IF ( humidity  .OR.  passive_scalar )  THEN
2203
2204       CALL cpu_log( log_point(29), 'q/s-equation', 'start' )
2205
2206!
2207!--    Scalar/q-tendency terms with communication
2208       sbt = tsc(2)
2209       IF ( scalar_advec == 'bc-scheme' )  THEN
2210
2211          IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2212!
2213!--          Bott-Chlond scheme always uses Euler time step. Thus:
[1337]2214             sbt = 1.0_wp
[1015]2215          ENDIF
[1337]2216          tend = 0.0_wp
[1015]2217          CALL advec_s_bc( q, 'q' )
2218
2219       ENDIF
2220
2221!
2222!--    Scalar/q-tendency terms with no communication
2223       IF ( scalar_advec /= 'bc-scheme' )  THEN
[1337]2224          tend = 0.0_wp
[1015]2225          IF ( timestep_scheme(1:5) == 'runge' )  THEN
2226             IF ( ws_scheme_sca )  THEN
2227                CALL advec_s_ws( q, 'q' )
2228             ELSE
2229                CALL advec_s_pw( q )
2230             ENDIF
2231          ELSE
2232             CALL advec_s_up( q )
2233          ENDIF
2234       ENDIF
2235
2236       CALL diffusion_s( q, qsws, qswst, wall_qflux )
2237
2238!
2239!--    If required compute decrease of total water content due to
2240!--    precipitation
[1361]2241       IF ( cloud_physics  .AND.  icloud_scheme == 1  .AND.  precipitation )  THEN
[1015]2242          CALL calc_precipitation
2243       ENDIF
2244
2245!
2246!--    Sink or source of scalar concentration due to canopy elements
2247       IF ( plant_canopy ) CALL plant_canopy_model( 5 )
2248
2249!
[1365]2250!--    Large scale advection
2251       IF ( large_scale_forcing )  THEN
2252          CALL ls_advec( simulated_time, 'q' )
2253       ENDIF
2254
2255!
[1380]2256!--    Nudging
2257       IF ( nudging )  CALL nudge( simulated_time, 'q' ) 
2258
2259!
[1015]2260!--    If required compute influence of large-scale subsidence/ascent
[1365]2261       IF ( large_scale_subsidence  .AND.                                      &
2262            .NOT. use_subsidence_tendencies )  THEN
2263         CALL subsidence( tend, q, q_init, 3 )
[1015]2264       ENDIF
2265
2266       CALL user_actions( 'q-tendency' )
2267
2268!
2269!--    Prognostic equation for total water content / scalar
[1128]2270       DO  i = i_left, i_right
2271          DO  j = j_south, j_north
[1015]2272             DO  k = nzb_s_inner(j,i)+1, nzt
2273                q_p(k,j,i) = q(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +          &
2274                                                  tsc(3) * tq_m(k,j,i) )       &
2275                                      - tsc(5) * rdf_sc(k) *                   &
2276                                        ( q(k,j,i) - q_init(k) )
[1337]2277                IF ( q_p(k,j,i) < 0.0_wp )  q_p(k,j,i) = 0.1_wp * q(k,j,i)
[1015]2278!
2279!--             Tendencies for the next Runge-Kutta step
2280                IF ( runge_step == 1 )  THEN
2281                   tq_m(k,j,i) = tend(k,j,i)
2282                ELSEIF ( runge_step == 2 )  THEN
[1337]2283                   tq_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * tq_m(k,j,i)
[1015]2284                ENDIF
2285             ENDDO
2286          ENDDO
2287       ENDDO
2288
2289       CALL cpu_log( log_point(29), 'q/s-equation', 'stop' )
2290
[1361]2291!
2292!--    If required, calculate prognostic equations for rain water content
2293!--    and rain drop concentration
2294       IF ( cloud_physics  .AND.  icloud_scheme == 0  .AND.  precipitation )  THEN
2295
2296          CALL cpu_log( log_point(52), 'qr-equation', 'start' )
2297!
2298!--       qr-tendency terms with communication
2299          sbt = tsc(2)
2300          IF ( scalar_advec == 'bc-scheme' )  THEN
2301
2302             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2303!
2304!--             Bott-Chlond scheme always uses Euler time step. Thus:
2305                sbt = 1.0_wp
2306             ENDIF
2307             tend = 0.0_wp
2308             CALL advec_s_bc( qr, 'qr' )
2309
2310          ENDIF
2311
2312!
2313!--       qr-tendency terms with no communication
2314          IF ( scalar_advec /= 'bc-scheme' )  THEN
2315             tend = 0.0_wp
2316             IF ( timestep_scheme(1:5) == 'runge' )  THEN
2317                IF ( ws_scheme_sca )  THEN
2318                   CALL advec_s_ws( qr, 'qr' )
2319                ELSE
2320                   CALL advec_s_pw( qr )
2321                ENDIF
2322             ELSE
2323                CALL advec_s_up( qr )
2324             ENDIF
2325          ENDIF
2326
2327          CALL diffusion_s( qr, qrsws, qrswst, wall_qrflux )
2328
2329          CALL user_actions( 'qr-tendency' )
2330
2331!
2332!--       Prognostic equation for rain water content
2333          DO  i = i_left, i_right
2334             DO  j = j_south, j_north
2335                DO  k = nzb_s_inner(j,i)+1, nzt
2336                   qr_p(k,j,i) = qr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
2337                                                       tsc(3) * tqr_m(k,j,i) ) &
2338                                           - tsc(5) * rdf_sc(k) * qr(k,j,i)
2339                   IF ( qr_p(k,j,i) < 0.0_wp )  qr_p(k,j,i) = 0.0_wp
2340!
2341!--                Tendencies for the next Runge-Kutta step
2342                   IF ( runge_step == 1 )  THEN
2343                      tqr_m(k,j,i) = tend(k,j,i)
2344                   ELSEIF ( runge_step == 2 )  THEN
2345                      tqr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp *    &
2346                                                                tqr_m(k,j,i)
2347                   ENDIF
2348                ENDDO
2349             ENDDO
2350          ENDDO
2351
2352          CALL cpu_log( log_point(52), 'qr-equation', 'stop' )
2353          CALL cpu_log( log_point(53), 'nr-equation', 'start' )
2354
2355!
2356!--       nr-tendency terms with communication
2357          sbt = tsc(2)
2358          IF ( scalar_advec == 'bc-scheme' )  THEN
2359
2360             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2361!
2362!--             Bott-Chlond scheme always uses Euler time step. Thus:
2363                sbt = 1.0_wp
2364             ENDIF
2365             tend = 0.0_wp
2366             CALL advec_s_bc( nr, 'nr' )
2367
2368          ENDIF
2369
2370!
2371!--       nr-tendency terms with no communication
2372          IF ( scalar_advec /= 'bc-scheme' )  THEN
2373             tend = 0.0_wp
2374             IF ( timestep_scheme(1:5) == 'runge' )  THEN
2375                IF ( ws_scheme_sca )  THEN
2376                   CALL advec_s_ws( nr, 'nr' )
2377                ELSE
2378                   CALL advec_s_pw( nr )
2379                ENDIF
2380             ELSE
2381                CALL advec_s_up( nr )
2382             ENDIF
2383          ENDIF
2384
2385          CALL diffusion_s( nr, nrsws, nrswst, wall_nrflux )
2386
2387          CALL user_actions( 'nr-tendency' )
2388
2389!
2390!--       Prognostic equation for rain drop concentration
2391          DO  i = i_left, i_right
2392             DO  j = j_south, j_north
2393                DO  k = nzb_s_inner(j,i)+1, nzt
2394                   nr_p(k,j,i) = nr(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +     &
2395                                                       tsc(3) * tnr_m(k,j,i) ) &
2396                                           - tsc(5) * rdf_sc(k) * nr(k,j,i)
2397                   IF ( nr_p(k,j,i) < 0.0_wp )  nr_p(k,j,i) = 0.0_wp
2398!
2399!--                Tendencies for the next Runge-Kutta step
2400                   IF ( runge_step == 1 )  THEN
2401                      tnr_m(k,j,i) = tend(k,j,i)
2402                   ELSEIF ( runge_step == 2 )  THEN
2403                      tnr_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp *    &
2404                                                                tnr_m(k,j,i)
2405                   ENDIF
2406                ENDDO
2407             ENDDO
2408          ENDDO
2409
2410          CALL cpu_log( log_point(53), 'nr-equation', 'stop' )
2411
2412       ENDIF
2413
[1015]2414    ENDIF
2415
2416!
2417!-- If required, compute prognostic equation for turbulent kinetic
2418!-- energy (TKE)
2419    IF ( .NOT. constant_diffusion )  THEN
2420
2421       CALL cpu_log( log_point(16), 'tke-equation', 'start' )
2422
2423       sbt = tsc(2)
2424       IF ( .NOT. use_upstream_for_tke )  THEN
2425          IF ( scalar_advec == 'bc-scheme' )  THEN
2426
2427             IF ( timestep_scheme(1:5) /= 'runge' )  THEN
2428!
2429!--             Bott-Chlond scheme always uses Euler time step. Thus:
[1337]2430                sbt = 1.0_wp
[1015]2431             ENDIF
[1337]2432             tend = 0.0_wp
[1015]2433             CALL advec_s_bc( e, 'e' )
2434
2435          ENDIF
2436       ENDIF
2437
2438!
2439!--    TKE-tendency terms with no communication
2440       IF ( scalar_advec /= 'bc-scheme'  .OR.  use_upstream_for_tke )  THEN
2441          IF ( use_upstream_for_tke )  THEN
[1337]2442             tend = 0.0_wp
[1015]2443             CALL advec_s_up( e )
2444          ELSE
2445             IF ( timestep_scheme(1:5) == 'runge' )  THEN
2446                IF ( ws_scheme_sca )  THEN
2447                   CALL advec_s_ws_acc( e, 'e' )
2448                ELSE
[1337]2449                   tend = 0.0_wp    ! to be removed later??
[1015]2450                   CALL advec_s_pw( e )
2451                ENDIF
2452             ELSE
[1337]2453                tend = 0.0_wp    ! to be removed later??
[1015]2454                CALL advec_s_up( e )
2455             ENDIF
2456          ENDIF
2457       ENDIF
2458
2459       IF ( .NOT. humidity )  THEN
2460          IF ( ocean )  THEN
2461             CALL diffusion_e( prho, prho_reference )
2462          ELSE
2463             CALL diffusion_e_acc( pt, pt_reference )
2464          ENDIF
2465       ELSE
2466          CALL diffusion_e( vpt, pt_reference )
2467       ENDIF
2468
2469       CALL production_e_acc
2470
2471!
2472!--    Additional sink term for flows through plant canopies
2473       IF ( plant_canopy )  CALL plant_canopy_model( 6 )
2474       CALL user_actions( 'e-tendency' )
2475
2476!
2477!--    Prognostic equation for TKE.
2478!--    Eliminate negative TKE values, which can occur due to numerical
2479!--    reasons in the course of the integration. In such cases the old TKE
2480!--    value is reduced by 90%.
2481       !$acc kernels present( e, e_p, nzb_s_inner, tend, te_m )
[1257]2482       !$acc loop independent
[1128]2483       DO  i = i_left, i_right
[1257]2484          !$acc loop independent
[1128]2485          DO  j = j_south, j_north
[1257]2486             !$acc loop independent
[1015]2487             DO  k = 1, nzt
2488                IF ( k > nzb_s_inner(j,i) )  THEN
2489                   e_p(k,j,i) = e(k,j,i) + dt_3d * ( sbt * tend(k,j,i) +          &
2490                                                     tsc(3) * te_m(k,j,i) )
[1337]2491                   IF ( e_p(k,j,i) < 0.0_wp )  e_p(k,j,i) = 0.1_wp * e(k,j,i)
[1015]2492!
2493!--                Tendencies for the next Runge-Kutta step
2494                   IF ( runge_step == 1 )  THEN
2495                      te_m(k,j,i) = tend(k,j,i)
2496                   ELSEIF ( runge_step == 2 )  THEN
[1337]2497                      te_m(k,j,i) = -9.5625_wp * tend(k,j,i) + 5.3125_wp * te_m(k,j,i)
[1015]2498                   ENDIF
2499                ENDIF
2500             ENDDO
2501          ENDDO
2502       ENDDO
2503       !$acc end kernels
2504
2505       CALL cpu_log( log_point(16), 'tke-equation', 'stop' )
2506
2507    ENDIF
2508
2509 END SUBROUTINE prognostic_equations_acc
2510
2511
[736]2512 END MODULE prognostic_equations_mod
Note: See TracBrowser for help on using the repository browser.