source: palm/trunk/SOURCE/modules.f90 @ 4087

Last change on this file since 4087 was 4079, checked in by suehring, 5 years ago

Implementation of a monotonic flux limiter for vertical advection term in Wicker-Skamarock scheme. The flux limiter is currently only applied for passive scalars (passive scalar, chemical species, aerosols) within the region up to the highest topography, in order to avoid the built-up of large concentrations within poorly resolved cavities in urban environments. To enable the limiter monotonic_limiter_z = .T. must be set. Note, the limiter is currently only implemented for the cache-optimized version of advec_ws. Further changes in offline nesting: Set boundary condition for w at nzt+1 at all lateral boundaries (even though these won't enter the numerical solution), in order to avoid high vertical velocities in the run-control file which might built-up due to the mass-conservation; bugfix in offline nesting for chemical species

  • Property svn:keywords set to Id
File size: 138.7 KB
Line 
1!> @file modules.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: modules.f90 4079 2019-07-09 18:04:41Z gronemeier $
27! + monotonic_limiter_z
28!
29! 4069 2019-07-01 14:05:51Z Giersch
30! Masked output running index mid has been introduced as a local variable to
31! avoid runtime error (Loop variable has been modified) in time_integration
32!
33! 4017 2019-06-06 12:16:46Z schwenkel
34! increase maximum number of virtual flights
35!
36! 3987 2019-05-22 09:52:13Z kanani
37! Introduce alternative switch for debug output during timestepping
38!
39! 3885 2019-04-11 11:29:34Z kanani
40! Changes related to global restructuring of location messages and introduction
41! of additional debug messages
42!
43! 3871 2019-04-08 14:38:39Z knoop
44! Initialized parameter region
45!
46! 3746 2019-02-16 12:41:27Z gronemeier
47! Removed most_method
48!
49! 3648 2019-01-02 16:35:46Z suehring
50! -surface_data_output +surface_output
51!
52! 3636 2018-12-19 13:48:34Z raasch
53! nopointer option removed
54!
55! 3597 2018-12-04 08:40:18Z maronga
56! Added flag parameter do_output_at_2m for automatic output of 2m-temperature
57!
58! 3589 2018-11-30 15:09:51Z suehring
59! Move the control parameter "salsa" from salsa_mod to control_parameters
60! (M. Kurppa)
61!
62! 3582 2018-11-29 19:16:36Z suehring
63! dom_dwd_user, Schrempf:
64! -uv_exposure flag, UV model is now part of biometeorology_mod
65!
66! 3543 2018-11-20 17:06:15Z suehring
67! +type_x_byte, type_y_byte
68!
69! 3542 2018-11-20 17:04:13Z suehring
70! +run_zone
71!
72! 3473 2018-10-30 20:50:15Z suehring
73! +virtual_measurement
74!
75! 3472 2018-10-30 20:43:50Z suehring
76! Add indoor model (kanani, srissman, tlang)
77!
78! 3467 2018-10-30 19:05:21Z suehring
79! Add biometeorology
80!
81! 3435 2018-10-26 18:25:44Z gronemeier
82! +mask_k_over_surface, mask_surface
83!
84! 3422 2018-10-24 19:01:57Z gronemeier
85! bugfix: increase number of blanks in output string
86!
87! 3421 2018-10-24 18:39:32Z gronemeier
88! Renamed output variables
89! +surface_data_output
90!
91! 3355 2018-10-16 14:03:34Z knoop
92! (from branch resler)
93! Increase dimension of uv_heights etc.
94!
95! 3302 2018-10-03 02:39:40Z raasch
96! +u/v_stokes_zu, u/v_stokes_zw
97!
98! 3298 2018-10-02 12:21:11Z kanani
99! Minor formatting/clean-up (kanani)
100! Added some variables for time treatment (Russo)
101!
102! 3294 2018-10-01 02:37:10Z raasch
103! ocean renamed ocean_mode
104!
105! 3289 2018-09-28 10:23:58Z suehring
106! +num_mean_inflow_profiles
107!
108! 3288 2018-09-28 10:23:08Z suehring
109! Modularization of all bulk cloud physics code components
110!
111! 3240 2018-09-12 12:04:40Z Giersch
112! max_pr_user_tmp has been defined as a control variable because it is not
113! local anymore
114!
115! 3235 2018-09-07 14:06:15Z sward
116! Added global variable dim_size_agtnum to own module. Necessary to avoid
117! circular dependency in agent output.
118!
119! 3232 2018-09-07 12:21:44Z raasch
120! references to mrun replaced by palmrun, and updated
121!
122! 3198 2018-08-15 09:23:10Z sward
123! Added multi_agent_system_end and multi_agent_system_start
124!
125! 3183 2018-07-27 14:25:55Z suehring
126! Rename offline nesting variables:
127! -inflow_l, inflow_n, inflow_r, inflow_s,
128!  nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s, nest_domain, forcing,
129!  force_bound_l, force_bound_n, force_bound_r, force_bound_s, outflow_l,
130!  outflow_n, outflow_r, outflow_s
131! +bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_n, bc_dirichlet_r,
132!  bc_radiation_l, bc_radiation_n, bc_radiation_n, bc_radiation_r, child_domain
133!  nesting_offline
134!
135! 3182 2018-07-27 13:36:03Z suehring
136! Default value of dz_max has changed to a more uncommon value of 999 (value
137! of dz_max can not be part of dz values when using new stretching procedure)
138!
139! 3159 2018-07-20 11:20:01Z sward
140! Added multi agent system
141!
142! 3157 2018-07-19 21:08:49Z maronga
143! added use_free_convection_scaling
144!
145! 3129 2018-07-16 07:45:13Z gronemeier
146! add target attribute to km and kh, necessary for output in tcm_data_output_3d
147!
148! 3120 2018-07-11 18:30:57Z gronemeier
149! +les_dynamic
150!
151! 3083 2018-06-19 14:03:12Z gronemeier
152! set dt_3d = 0.01
153!
154! 3065 2018-06-12 07:03:02Z Giersch
155! Variables concerning stretching introduced or revised
156!
157! 3045 2018-05-28 07:55:41Z Giersch
158! z_max_do2d removed
159!
160! 3026 2018-05-22 10:30:53Z schwenkel
161! Changed the name specific humidity to mixing ratio, since we are computing
162! mixing ratios.
163!
164! 3014 2018-05-09 08:42:38Z maronga
165! Added default values of u_max, v_max, and w_max to avoid floating invalid
166! during spinup
167!
168! 3004 2018-04-27 12:33:25Z Giersch
169! precipitation_rate removed
170!
171! 3003 2018-04-23 10:22:58Z Giersch
172! The inversion height is defined as a global variable now which belongs to the
173! module statistics
174!
175! 2968 2018-04-13 11:52:24Z suehring
176! +topo_min_level
177!
178! 2964 2018-04-12 16:04:03Z raasch
179! *_time_count variables are all initialized with zero now
180!
181! 2918 2018-03-21 15:52:14Z gronemeier
182! -l_grid, -l_wall
183!
184! 2906 2018-03-19 08:56:40Z Giersch
185! Module control_parameters has been extended with ENVIRONMENT variables
186! read/write_svf
187!
188! 2894 2018-03-15 09:17:58Z Giersch
189! _prerun flags were removed, Control paramters restart_string and length have
190! been added
191!
192! 2881 2018-03-13 16:24:40Z suehring
193! Added flag for switching on/off calculation of soil moisture
194!
195! 2797 2018-02-08 13:24:35Z suehring
196! +ghf_av
197!
198! 2776 2018-01-31 10:44:42Z Giersch
199! Variable synthetic_turbulence_generator has been abbreviated and _prerun flags
200! for skipping module related restart data has beed introduced
201!
202! 2765 2018-01-22 11:34:58Z maronga
203! Set initial value for time_since_reference_point
204!
205! 2746 2018-01-15 12:06:04Z suehring
206! +plant_canopy
207!
208! 2742 2018-01-12 14:59:47Z suehring
209! +tsurf_av
210!
211! 2735 2018-01-11 12:01:27Z suehring
212! +r_a_av
213!
214! 2718 2018-01-02 08:49:38Z maronga
215! Corrected "Former revisions" section
216!
217! 2696 2017-12-14 17:12:51Z kanani
218! Change in file header (GPL part)
219! Implementation of uv exposure model (FK)
220! + turbulence closure variables (control_parameters)
221! + arrays for prognostic equation of disspiation (arrays_3d)
222! + km_av, kh_av (TG)
223! Implementation of chemistry module (FK)
224! -lod
225! +topo_distinct (MS)
226!
227! 2669 2017-12-06 16:03:27Z raasch
228! CONTIGUOUS-attribut added to 3d pointer arrays,
229! coupling_char extended to LEN=8
230!
231! 2575 2017-10-24 09:57:58Z maronga
232! Renamed phi -> latitude, moved longitude from radiation model to modules
233!
234! 2563 2017-10-19 15:36:10Z Giersch
235! Variable wind_turbine was added to control_parameters
236!
237! 2550 2017-10-16 17:12:01Z boeske
238! complex_terrain namelist parameter added
239!
240! 2508 2017-10-02 08:57:09Z suehring
241! Change default value for pt/q/s/sa_vertical_gradient_level
242!
243! 2499 2017-09-22 16:47:58Z kanani
244! Default changed to fft_method = 'temperton-algorithm'
245!
246! 2408 2017-09-05 15:47:53Z gronemeier
247! Changed default value of mg_cycles from -1 to 4.
248!
249! 2375 2017-08-29 14:10:28Z schwenkel
250! Moved mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
251! vanthoff back from particle attributes because they can now also be used in
252! bulk microphysics.
253! Added aerosol_bulk, aerosol_nacl, aerosol_c3h4o4, aerosol_nh4no3
254!
255! 2372 2017-08-25 12:37:32Z sward
256! y_shift namelist parameter added
257!
258! 2339 2017-08-07 13:55:26Z gronemeier
259! corrected timestamp in header
260!
261! 2338 2017-08-07 12:15:38Z gronemeier
262! moved 1d-model varaibles to own module model_1d_mod
263!
264! 2337 2017-08-07 08:59:53Z gronemeier
265! -old_dt_1d
266! +l1d_diss
267!
268! 2326 2017-08-01 07:23:24Z gronemeier
269! Updated variable descriptions
270!
271! 2320 2017-07-21 12:47:43Z suehring
272! -ptnudge, qnudge, tnudge, td_lsa_lpt, td_lsa_q, td_sub_lpt, td_sub_q, ug_vert,
273!  vg_vert, unudge, vnudge, wsubs_vert, shf_surf, p_surf, pt_surf, q_surt,
274!  qsws_surf, tmp_tnudge, timenudge, time_surf, time_vert
275!
276! 2300 2017-06-29 13:31:14Z raasch
277! default value for host changed to '????', default value for loop_optimization
278! changed to 'cache', default value for termination_time_needed set to 35.0
279!
280! 2298 2017-06-29 09:28:18Z raasch
281! missing variable descriptions have been added,
282! type of write_binary changed from CHARACTER to LOGICAL
283! -plot_precision, plot_3d_precision, return_addres, return_username,
284! avs_data_file, exchange_mg, sendrecvcound_yxd, sendrecv_in_background,
285! port_name, profile_number, cross_ts_numbers, cross_ts_number_count,
286! dots_crossindex, dots_index, cross_ts_uymax, cross_ts_uymax_computed,
287! cross_ts_uymin, cross_ts_uymin_computed
288!
289! 2296 2017-06-28 07:53:56Z maronga
290! Added parameters for model spinup
291!
292! 2292 2017-06-20 09:51:42Z schwenkel
293! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
294! includes two more prognostic equations for cloud drop concentration (nc) 
295! and cloud water content (qc).
296!
297! 2277 2017-06-12 10:47:51Z kanani
298! Added doxygen comments for variables/parameters,
299! removed unused variables dissipation_control, do2d_xy_n, do2d_xz_n, do2d_yz_n,
300! do3d_avs_n, lptnudge, lqnudge, lunudge, lvnudge, lwnudge, skip_do_avs,
301! sums_up_fraction_l.
302!
303! 2259 2017-06-08 09:09:11Z gronemeier
304! Implemented synthetic turbulence generator
305!
306! 2256 2017-06-07 13:58:08Z suehring
307! Change default value of zeta_min to -20
308! Increase dimension for wall_heatflux, etc.
309!
310! 2233 2017-05-30 18:08:54Z suehring
311!
312! 2232 2017-05-30 17:47:52Z suehring
313! Renamed wall_flags_0 and wall_flags_00 into advc_flags_1 and advc_flags_2,
314! respectively. Moreover, introduced further flag array wall_flags_0.
315!
316! Adjustments for new topography concept:
317!   -fwxm, fwxp, fwym, fwyp, fxm, fxp, fym, fyp, rif_wall, wall_e_x, wall_e_y,
318!   -wall_v, wall_u, wall_w_x, wall_w_y, wall_qflux, wall_sflux, wall_nrflux,
319!   -wall_qrflux
320!
321! Adjustments for new surface concept:
322!   +land_surface
323!   -z0, z0h, z0q, us, ts, qs, qsws, nrs, nrsws, qrs, qrsws, ssws, ss, saswsb
324!   -nzb_diff_u, nzb_diff_v, nzt_diff
325!   -uswst, vswst, tswst, sswst, saswst, qswst, qrswst, nrswst, qswst_remote
326!
327! Generic tunnel setup:
328!   +tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,
329!   +tunnel_wall_depth
330!
331! Topography input via netcdf
332!   +lod
333!
334! 2200 2017-04-11 11:37:51Z suehring
335! -monotonic_adjustment
336!
337! 2174 2017-03-13 08:18:57Z maronga
338! Changed default values for most_method to 'newton'
339!
340! 2118 2017-01-17 16:38:49Z raasch
341! -acc_rank, background_communication, i_left, i_right, j_south, j_north,
342!  num_acc_per_node, on_device
343!
344! 2107 2017-01-09 12:21:49Z kanani
345! Preparation for doxygen comments (Giersch)
346!
347! 2050 2016-11-08 15:00:55Z gronemeier
348! Implement turbulent outflow condition
349!
350! 2037 2016-10-26 11:15:40Z knoop
351! Anelastic approximation implemented
352!
353! 2031 2016-10-21 15:11:58Z knoop
354! renamed variable rho to rho_ocean and rho_av to rho_ocean_av
355!
356! 2011 2016-09-19 17:29:57Z kanani
357! +urban_surface, +lsf_exception, +varnamelength
358!
359! 2007 2016-08-24 15:47:17Z kanani
360! Increased DIMENSION of data_output, data_output_user, do2d, do3d
361!
362! 2000 2016-08-20 18:09:15Z knoop
363! Forced header and separation lines into 80 columns
364!
365! 1992 2016-08-12 15:14:59Z suehring
366! +constant_top_scalarflux, top_scalarflux
367! default of bc_s_t adjusted
368!
369! 1968 2016-07-18 12:01:49Z suehring
370! Changed dimension for MPI-datatypes type_x_int and type_y_int
371!
372! 1960 2016-07-12 16:34:24Z suehring
373! Separate humidity and passive scalar
374! +bc_s_t_val, diss_s_s, diss_l_s, flux_s_s, flux_l_s, s, sp, s1, s2, s3, ssws_av,
375!  s_init, s_surf, sums_wsss_ws_l, ss, ssws, sswst, ts_m, wall_sflux
376! +constant_scalarflux, ibc_s_b, ibc_s_t, s_vertical_gradient_level_ind
377!
378! Unused variables removed
379! -gamma_x, gamma_y, gamma_z, var_x, var_y, var_z
380!
381! Change initial values (in order to unify gradient calculation):
382! pt_vertical_gradient_level, sa_vertical_gradient_level
383!
384! 1957 2016-07-07 10:43:48Z suehring
385! +fl_max, num_leg, num_var_fl, num_var_fl_user, var_fl_max, virtual_flight
386!
387! 1918 2016-05-27 14:35:57Z raasch
388! default timestep switched from -1.0 to +1.0 in order to avoid wrong sign of
389! initially calculated divergence
390!
391! 1906 2016-05-24 14:38:08Z suehring
392! default value of mg_switch_to_pe0_level changed to -1
393!
394! 1849 2016-04-08 11:33:18Z hoffmann
395! bfactor, mass_of_solute, molecular_weight_of_solute, molecular_weight_of_water,
396! vanthoff moved to mod_particle_attributes.
397! dt_micro and several cloud_parameters moved to microphysics_mod.
398! 1d-microphysics profiles moved to microphysics_mod.
399!
400! 1845 2016-04-08 08:29:13Z raasch
401! -nzb_2d
402!
403! 1833 2016-04-07 14:23:03Z raasch
404! spectra parameter moved to spectra module
405!
406! 1831 2016-04-07 13:15:51Z hoffmann
407! curvature_solution_effects removed
408! turbulence renamed collision_turbulence, drizzle renamed
409! cloud_water_sedimentation
410!
411! 1822 2016-04-07 07:49:42Z hoffmann
412! icloud_scheme removed. microphysics_sat_adjust, microphysics_kessler,
413! microphysics_seifert added.
414!
415! 1815 2016-04-06 13:49:59Z raasch
416! cpp-directive for decalpha removed
417!
418! 1808 2016-04-05 19:44:00Z raasch
419! MPI module used by default on all machines
420!
421! 1804 2016-04-05 16:30:18Z maronga
422! Removed code for parameter file check (__check)
423!
424! 1788 2016-03-10 11:01:04Z maronga
425! Added roughness length for moisture (z0q)
426!
427! 1786 2016-03-08 05:49:27Z raasch
428! module spectrum moved to new separate module
429!
430! 1783 2016-03-06 18:36:17Z raasch
431! netcdf variables moved to the netcdf-interface module
432!
433! 1779 2016-03-03 08:01:28Z raasch
434! coupling_char extended to LEN=3
435!
436! 1764 2016-02-28 12:45:19Z raasch
437! some reformatting
438!
439! 1762 2016-02-25 12:31:13Z hellstea
440! +nest_* variables, size of volume_flow arrays increased by one element
441!
442! 1738 2015-12-18 13:56:05Z raasch
443! +mean_surface_level_height
444!
445! 1695 2015-10-27 10:03:11Z maronga
446! Removed rif (forgotten in last revision)
447!
448! 1693 2015-10-27 08:35:45Z maronga
449! Renamed zp -> z_mo
450!
451! 1691 2015-10-26 16:17:44Z maronga
452! Renamed Obukhov length. Added ol, removed rif. Increased number of profiles
453! (pr_palm). Changed default values for dissipation_1d to 'detering' and
454! (mixing_length_1d to 'blackadar'. Added most_method. rif_min and rif_max
455! renamed to zeta_min and zeta_max and new values assigned.
456!
457! 1682 2015-10-07 23:56:08Z knoop
458! Code annotations made doxygen readable
459!
460! 1677 2015-10-02 13:25:23Z boeske
461! +ngp_yz_int, type_xz_int, type_yz_int
462!
463! 1666 2015-09-23 07:31:10Z raasch
464! +user_interface_current_revision, user_interface_required_revision in
465! control_parameters
466!
467! 1639 2015-08-31 14:46:48Z knoop
468! Bugfix: string 'unknown' extended to match LEN=13
469!
470! 1575 2015-03-27 09:56:27Z raasch
471! +ngp_xz
472!
473! 1560 2015-03-06 10:48:54Z keck
474! +recycling_yshift
475!
476! 1557 2015-03-05 16:43:04Z suehring
477! +monotonic_adjustment
478!
479! 1551 2015-03-03 14:18:16Z maronga
480! Increased pr_palm to 120. Increased length of dots_unit and dots_label to 13
481! digits. Increased length of domask, do2d, and do3d to 20 digits.
482!
483! 1496 2014-12-02 17:25:50Z maronga
484! Renamed "radiation" -> "cloud_top_radiation"
485!
486! 1484 2014-10-21 10:53:05Z kanani
487! Changes due to new module structure of the plant canopy model:
488!   canopy-model related parameters/variables moved to module
489!   plant_canopy_model_mod
490!
491! 1468 2014-09-24 14:06:57Z maronga
492! Adapted for use on up to 6-digit processor cores.
493! Increased identifier string length for user-defined quantities to 20.
494!
495! 1450 2014-08-21 07:31:51Z heinze
496! ntnudge from 100 to 1000 increased to allow longer simulations
497!
498! 1431 2014-07-15 14:47:17Z suehring
499! +var_d
500!
501! 1429 2014-07-15 12:53:45Z knoop
502! +ensemble_member_nr to prepare the random_generator for ensemble runs
503!
504! 1382 2014-04-30 12:15:41Z boeske
505! Renamed variables which store large scale forcing tendencies
506! pt_lsa -> td_lsa_lpt, pt_subs -> td_sub_lpt,
507! q_lsa  -> td_lsa_q,   q_subs  -> td_sub_q
508!
509! 1365 2014-04-22 15:03:56Z boeske
510! Usage of large scale forcing enabled:
511! increase pr_palm from 90 to 100 to allow for more standard profiles
512! + ngp_sums_ls, pt_lsa, pt_subs, q_lsa, q_subs, tmp_tnudge, sums_ls_l,
513! use_subsidence_tendencies
514!
515! 1361 2014-04-16 15:17:48Z hoffmann
516! tend_* removed
517! call_microphysics_at_all_substeps added
518! default of drizzle set to true
519!
520! 1359 2014-04-11 17:15:14Z hoffmann
521! particle_attributes moved to mod_particle_attributes.f90
522!
523! 1353 2014-04-08 15:21:23Z heinze
524! REAL constants provided with KIND-attribute
525!
526! 1327 2014-03-21 11:00:16Z raasch
527! REAL constants defined as wp-kind
528! -avs_output, data_output_format, do3d_compress, iso2d_output, netcdf_output
529!
530! 1320 2014-03-20 08:40:49Z raasch
531! ONLY-attribute added to USE-statements,
532! kind-parameters added to all INTEGER and REAL declaration statements,
533! kinds are defined in new module kinds,
534! old module precision_kind is removed,
535! revision history before 2012 removed,
536! comment fields (!:) to be used for variable explanations added to
537! all variable declaration statements
538!
539! 1318 2014-03-17 13:35:16Z raasch
540! module cpulog moved to new separate module-file
541! interface for cpu_log removed
542!
543! 1314 2014-03-14 18:25:17Z suehring
544! + log_z_z0, number_of_sublayers, z0_av_global
545! 1308 2014-03-13 14:58:42Z fricke
546! +ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz, ntdim_3d
547!
548! 1257 2013-11-08 15:18:40Z raasch
549! set default values for grid indices of maximum velocity components
550! u|v|w_max_ijk
551!
552! 1241 2013-10-30 11:36:58Z heinze
553! Usage of nudging enabled
554! +nudging, ntnudge, ptnudge, qnudge, tnudge, unudge, vnudge, wnudge
555! increase pr_palm from 80 to 90 to allow for more standard profiles
556!
557! Enable prescribed time depenend surface fluxes and geostrophic wind read in
558! from external file LSF_DATA
559! +large_scale_forcing, lsf_surf, lsf_vert, nlsf, time_surf, shf_surf, qsws_surf,
560!  pt_surf, q_surf, p_surf, time_vert, ug_vert, vg_vert, wsubs_vert
561!
562! 1221 2013-09-10 08:59:13Z raasch
563! wall_flags_0 changed to 32bit int, +wall_flags_00,
564! +rflags_s_inner, rflags_invers
565!
566! 1216 2013-08-26 09:31:42Z raasch
567! +transpose_compute_overlap,
568! several variables are now defined in the serial (non-parallel) case also
569!
570! 1212 2013-08-15 08:46:27Z raasch
571! +tri
572!
573! 1179 2013-06-14 05:57:58Z raasch
574! +reference_state, ref_state, use_initial_profile_as_reference, vpt_reference,
575! use_reference renamed use_single_reference_value
576!
577! 1159 2013-05-21 11:58:22Z fricke
578! -bc_lr_dirneu, bc_lr_neudir, bc_ns_dirneu, bc_ns_neudir
579! +use_cmax
580!
581! 1128 2013-04-12 06:19:32Z raasch
582! +background_communication, i_left, i_right, j_north, j_south, req, req_count,
583! send_receive, sendrecv_in_background, wait_stat
584!
585! 1115 2013-03-26 18:16:16Z hoffmann
586! unused variables removed
587!
588! 1113 2013-03-10 02:48:14Z raasch
589! +on_device
590!
591! 1111 2013-03-08 23:54:10Z raasch
592! +tric, nr_timesteps_this_run
593!
594! 1106 2013-03-04 05:31:38Z raasch
595! array_kind renamed precision_kind, pdims defined in serial code
596! bugfix: default value assigned to coupling_start_time
597!
598! 1095 2013-02-03 02:21:01Z raasch
599! FORTRAN error in r1092 removed
600!
601! 1092 2013-02-02 11:24:22Z raasch
602! character length in some derived type changed for better alignment
603!
604! 1065 2012-11-22 17:42:36Z hoffmann
605! + c_sedimentation, limiter_sedimentation, turbulence, a_1, a_2, a_3, b_1, b_2,
606! + b_3, c_1, c_2, c_3, beta_cc
607!
608! bottom boundary condition of qr, nr changed from Dirichlet to Neumann
609!
610! 1053 2012-11-13 17:11:03Z hoffmann
611! necessary expansions according to the two new prognostic equations (nr, qr)
612! of the two-moment cloud physics scheme:
613! +*_init, flux_l_*, diss_l_*, flux_s_*, diss_s_*, *sws, *swst, tend_*, *, *_p
614! +t*_m, *_1, *_2, *_3, *_av, bc_*_b, bc_*_t, ibc_*_b, ibc_*_t, bc_*_t_val,
615! +*_vertical_gradient, *_surface_initial_change, *_vertical_gradient_level,
616! +*_vertical_gradient_level_ind, *_surface, constant_waterflux_*, 
617! +cloud_scheme, icloud_scheme, surface_waterflux_*, sums_ws*s_ws_l, wall_*flux
618!
619! constants for the two-moment scheme:
620! +a_vent, a_term, b_vent, b_term, c_evap, c_term, cof, eps_sb, k_cc, k_cr, k_rr,
621! +k_br, kappa_rr, kin_vis_air, mu_constant_value, nc, pirho_l, dpirho_l, rho_1,
622! +schmidt, schmidt_p_1d3, stp, x0, xmin, xmax, dt_precipitation, w_precipitation
623!
624! steering parameters for the two_moment scheme:
625! +mu_constant, ventilation_effect
626!
627! 1036 2012-10-22 13:43:42Z raasch
628! code put under GPL (PALM 3.9)
629!
630! 1031 2012-10-19 14:35:30Z raasch
631! +output_format_netcdf
632!
633! 1015 2012-09-27 09:23:24Z raasch
634! +acc_rank, num_acc_per_node,
635! -adjust_mixing_length
636!
637! 1010 2012-09-20 07:59:54Z raasch
638! pointer free version can be generated with cpp switch __nopointer
639!
640! 1003 2012-09-14 14:35:53Z raasch
641! -grid_matching, nxa, nya, etc., nnx_pe, nny_pe, spl_*
642!
643! 1001 2012-09-13 14:08:46Z raasch
644! -asselin_filter_factor, cut_spline_overshoot, dt_changed, last_dt_change,
645! last_dt_change_1d, long_filter_factor, overshoot_limit_*, ups_limit_*
646! several pointer/target arrays converted to normal ones
647!
648! 996 2012-09-07 10:41:47Z raasch
649! -use_prior_plot1d_parameters
650!
651! 978 2012-08-09 08:28:32Z fricke
652! +c_u_m, c_u_m_l, c_v_m, c_v_m_l, c_w_m, c_w_m_l,
653! +bc_lr_dirneu, bc_lr_neudir, bc_ns_dirneu, bc_ns_neudir
654! -km_damp_x, km_damp_y, km_damp_max, outflow_damping_width
655! +z0h, z0h_av, z0h_factor, z0h1d
656! +ptdf_x, ptdf_y, pt_damping_width, pt_damping_factor
657!
658! 964 2012-07-26 09:14:24Z raasch
659! -cross_linecolors, cross_linestyles, cross_normalized_x, cross_normx_factor,
660! cross_normalized_y, cross_normy_factor, cross_pnc_local,
661! cross_profile_numbers, cross_profile_number_counter, cross_uxmax,
662! cross_uxmax_computed, cross_uxmax_normalized,
663! cross_uxmax_normalized_computed, cross_uxmin, cross_uxmin_computed,
664! cross_uxmin_normalized, cross_uxmin_normalized_computed, cross_uymax,
665! cross_uymin, cross_xtext, dopr_crossindex, dopr_label, linecolors, linestyles,
666! nz_do1d, profil_output, z_max_do1d, z_max_do1d_normalized
667!
668! 951 2012-07-19 14:22:52Z hoffmann
669! changing profile_columns and profile_rows
670!
671! 940 2012-07-09 14:31:00Z raasch
672! +neutral
673!
674! 927 2012-06-06 19:15:04Z raasch
675! +masking_method
676!
677! 880 2012-04-13 06:28:59Z raasch
678! gathered_size, subdomain_size moved to control_parameters
679!
680! 866 2012-03-28 06:44:41Z raasch
681! interface for global_min_max changed
682!
683! 861 2012-03-26 14:18:34Z suehring
684! +wall_flags_0
685! -boundary_flags
686! +nzb_max
687! +adv_sca_1, +adv_mom_1
688!
689! 849 2012-03-15 10:35:09Z raasch
690! +deleted_particles, deleted_tails, tr.._count_sum, tr.._count_recv_sum in
691! particle_attributes,
692! +de_dx, de_dy, de_dz in arrays_3d,
693! first_call_advec_particles renamed first_call_lpm
694!
695! 828 2012-02-21 12:00:36Z raasch
696! +dissipation_classes, radius_classes, use_kernel_tables,
697! particle feature color renamed class
698!
699! 825 2012-02-19 03:03:44Z raasch
700! +bfactor, curvature_solution_effects, eps_ros, molecular_weight_of_water,
701! vanthoff, -b_cond in cloud_parameters,
702! dopts_num increased to 29, particle attributes speed_x|y|z_sgs renamed
703! rvar1|2|3
704! wang_collision_kernel and turbulence_effects_on_collision replaced by
705! collision_kernel, hall_kernel, palm_kernel, wang_kernel
706!
707! 809 2012-01-30 13:32:58Z marongas
708! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives
709!
710! 807 2012-01-25 11:53:51Z maronga
711! New cpp directive "__check" implemented which is used by check_namelist_files.
712! New parameter check_restart has been defined which is needed by
713! check_namelist_files only.
714!
715! 805 2012-01-17 15:53:28Z franke
716! Bugfix collective_wait must be out of parallel branch for runs in serial mode
717!
718! 801 2012-01-10 17:30:36Z suehring
719! Dimesion of sums_wsus_ws_l, ! sums_wsvs_ws_l, sums_us2_ws_l, sums_vs2_ws_l,
720! sums_ws2_ws_l, sums_wspts_ws_l, sums_wsqs_ws_l, sums_wssas_ws_l increased.
721! for thread-safe summation in advec_ws.
722!
723! RCS Log replace by Id keyword, revision history cleaned up
724!
725! Revision 1.95  2007/02/11 13:18:30  raasch
726! version 3.1b (last under RCS control)
727!
728! Revision 1.1  1997/07/24 11:21:26  raasch
729! Initial revision
730!
731!
732!------------------------------------------------------------------------------!
733! Description:
734! ------------
735!> Definition of global variables
736!------------------------------------------------------------------------------!
737
738
739!------------------------------------------------------------------------------!
740! Description:
741! ------------
742!> Definition of variables for special advection schemes.
743!------------------------------------------------------------------------------!
744 MODULE advection
745 
746    USE kinds
747
748    REAL(wp), DIMENSION(:), ALLOCATABLE ::  aex  !< exponential coefficient for the Bott-Chlond advection scheme
749    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bex  !< exponential coefficient for the Bott-Chlond advection scheme
750    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dex  !< exponential coefficient for the Bott-Chlond advection scheme
751    REAL(wp), DIMENSION(:), ALLOCATABLE ::  eex  !< exponential coefficient for the Bott-Chlond advection scheme
752   
753    SAVE
754
755 END MODULE advection
756
757
758
759!------------------------------------------------------------------------------!
760! Description:
761! ------------
762!> The variable in this module is used by multi_agent_system_mod AND
763!> netcdf_interface_mod. It must be here to avoid circular dependency.
764!> This is a workaround.
765!------------------------------------------------------------------------------!
766 MODULE mas_global_attributes
767 
768    USE kinds
769
770    INTEGER(iwp) ::  dim_size_agtnum  !< size of agent number dimension for netCDF output
771
772    SAVE
773
774 END MODULE mas_global_attributes
775
776
777!------------------------------------------------------------------------------!
778! Description:
779! ------------
780!> Definition of all arrays defined on the computational grid.
781!------------------------------------------------------------------------------!
782 MODULE arrays_3d
783
784    USE kinds
785
786    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m                  !< mean phase velocity at outflow for u-component used in radiation boundary condition
787    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m_l                !< mean phase velocity at outflow for u-component used in radiation boundary condition (local subdomain value)
788    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m                  !< mean phase velocity at outflow for v-component used in radiation boundary condition
789    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m_l                !< mean phase velocity at outflow for v-component used in radiation boundary condition (local subdomain value)
790    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m                  !< mean phase velocity at outflow for w-component used in radiation boundary condition
791    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m_l                !< mean phase velocity at outflow for w-component used in radiation boundary condition (local subdomain value)
792    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                   !< 1/dzu
793    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu_pres              !< modified ddzu for pressure solver
794    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dd2zu                  !< 1/(dzu(k)+dzu(k+1))
795    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzu                    !< vertical grid size (u-grid)
796    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzw                   !< 1/dzw
797    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzw                    !< vertical grid size (w-grid)
798    REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp                    !< hydrostatic pressure
799    REAL(wp), DIMENSION(:), ALLOCATABLE ::  inflow_damping_factor  !< used for turbulent inflow (non-cyclic boundary conditions)
800    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_x                 !< damping factor for potential temperature in x-direction
801    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_y                 !< damping factor for potential temperature in y-direction
802    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init                !< initial profile of potential temperature
803    REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init                 !< initial profile of total water mixing ratio
804                                                                   !< (or total water content with active cloud physics)
805    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf                    !< rayleigh damping factor for velocity components
806    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf_sc                 !< rayleigh damping factor for scalar quantities
807    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ref_state              !< reference state of potential temperature
808                                                                   !< (and density in case of ocean simulation)
809    REAL(wp), DIMENSION(:), ALLOCATABLE ::  s_init                 !< initial profile of passive scalar concentration
810    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sa_init                !< initial profile of salinity (ocean)
811    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug                     !< geostrophic wind component in x-direction
812    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init                 !< initial profile of horizontal velocity component u
813    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zu            !< u-component of Stokes drift velocity at zu levels
814    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zw            !< u-component of Stokes drift velocity at zw levels
815    REAL(wp), DIMENSION(:), ALLOCATABLE ::  vg                     !< geostrophic wind component in y-direction
816    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_init                 !< initial profile of horizontal velocity component v
817    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zu            !< v-component of Stokes drift velocity at zu levels
818    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zw            !< v-component of Stokes drift velocity at zw levels
819    REAL(wp), DIMENSION(:), ALLOCATABLE ::  w_subs                 !< subsidence/ascent velocity
820    REAL(wp), DIMENSION(:), ALLOCATABLE ::  x                      !< horizontal grid coordinate of v-grid (in m)
821    REAL(wp), DIMENSION(:), ALLOCATABLE ::  xu                     !< horizontal grid coordinate of u-grid (in m)
822    REAL(wp), DIMENSION(:), ALLOCATABLE ::  y                      !< horizontal grid coordinate of u-grid (in m)
823    REAL(wp), DIMENSION(:), ALLOCATABLE ::  yv                     !< horizontal grid coordinate of v-grid (in m)
824    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu                     !< vertical grid coordinate of u-grid (in m)
825    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw                     !< vertical grid coordinate of w-grid (in m)
826
827    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_u                   !< phase speed of u-velocity component
828    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_v                   !< phase speed of v-velocity component
829    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_w                   !< phase speed of w-velocity component
830    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_diss           !< artificial numerical dissipation flux at south face of grid box - TKE dissipation
831    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_e              !< artificial numerical dissipation flux at south face of grid box - subgrid-scale TKE
832    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid box - clouddrop-number concentration   
833    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nr             !< artificial numerical dissipation flux at south face of grid box - raindrop-number concentration   
834    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_pt             !< artificial numerical dissipation flux at south face of grid box - potential temperature
835    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_q              !< artificial numerical dissipation flux at south face of grid box - mixing ratio
836    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qc             !< artificial numerical dissipation flux at south face of grid box - cloudwater
837    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qr             !< artificial numerical dissipation flux at south face of grid box - rainwater
838    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_s              !< artificial numerical dissipation flux at south face of grid box - passive scalar
839    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_sa             !< artificial numerical dissipation flux at south face of grid box - salinity
840    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_u              !< artificial numerical dissipation flux at south face of grid box - u-component
841    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_v              !< artificial numerical dissipation flux at south face of grid box - v-component
842    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_w              !< artificial numerical dissipation flux at south face of grid box - w-component
843    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzu_mg                !< vertical grid size (u-grid) for multigrid pressure solver
844    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzw_mg                !< vertical grid size (w-grid) for multigrid pressure solver
845    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_diss           !< 6th-order advective flux at south face of grid box - TKE dissipation
846    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_e              !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
847    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
848    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nr             !< 6th-order advective flux at south face of grid box - raindrop-number concentration
849    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_pt             !< 6th-order advective flux at south face of grid box - potential temperature
850    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_q              !< 6th-order advective flux at south face of grid box - mixing ratio
851    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qc             !< 6th-order advective flux at south face of grid box - cloudwater
852    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qr             !< 6th-order advective flux at south face of grid box - rainwater
853    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_s              !< 6th-order advective flux at south face of grid box - passive scalar
854    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_sa             !< 6th-order advective flux at south face of grid box - salinity
855    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_u              !< 6th-order advective flux at south face of grid box - u-component
856    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_v              !< 6th-order advective flux at south face of grid box - v-component
857    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_w              !< 6th-order advective flux at south face of grid box - w-component
858    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f1_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
859    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f2_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
860    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f3_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
861    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  mean_inflow_profiles  !< used for turbulent inflow (non-cyclic boundary conditions)
862    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount  !< precipitation amount due to gravitational settling (bulk microphysics)
863    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pt_slope_ref          !< potential temperature in rotated coordinate system
864                                                                    !< (in case of sloped surface)
865    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_a            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (atmosphere data)
866    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_o            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (ocean data)
867   
868    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  d           !< divergence
869    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dx       !< gradient of sgs tke in x-direction (lpm)
870    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dy       !< gradient of sgs tke in y-direction (lpm)
871    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dz       !< gradient of sgs tke in z-direction (lpm)
872    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_diss !< artificial numerical dissipation flux at left face of grid box - TKE dissipation
873    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_e    !< artificial numerical dissipation flux at left face of grid box - subgrid-scale TKE
874    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nc   !< artificial numerical dissipation flux at left face of grid box - clouddrop-number concentration
875    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nr   !< artificial numerical dissipation flux at left face of grid box - raindrop-number concentration
876    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_pt   !< artificial numerical dissipation flux at left face of grid box - potential temperature
877    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_q    !< artificial numerical dissipation flux at left face of grid box - mixing ratio
878    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qc   !< artificial numerical dissipation flux at left face of grid box - cloudwater
879    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qr   !< artificial numerical dissipation flux at left face of grid box - rainwater
880    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_s    !< artificial numerical dissipation flux at left face of grid box - passive scalar
881    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_sa   !< artificial numerical dissipation flux at left face of grid box - salinity
882    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_u    !< artificial numerical dissipation flux at left face of grid box - u-component
883    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_v    !< artificial numerical dissipation flux at left face of grid box - v-component
884    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_w    !< artificial numerical dissipation flux at left face of grid box - w-component
885    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_diss !< 6th-order advective flux at south face of grid box - TKE dissipation
886    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_e    !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
887    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nc   !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
888    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nr   !< 6th-order advective flux at south face of grid box - raindrop-number concentration
889    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_pt   !< 6th-order advective flux at south face of grid box - potential temperature
890    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_q    !< 6th-order advective flux at south face of grid box - mixing ratio
891    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qc   !< 6th-order advective flux at south face of grid box - cloudwater
892    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qr   !< 6th-order advective flux at south face of grid box - rainwater
893    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_s    !< 6th-order advective flux at south face of grid box - passive scalar
894    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_sa   !< 6th-order advective flux at south face of grid box - salinity
895    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_u    !< 6th-order advective flux at south face of grid box - u-component
896    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_v    !< 6th-order advective flux at south face of grid box - v-component
897    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_w    !< 6th-order advective flux at south face of grid box - w-component
898    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh  !< eddy diffusivity for heat
899    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km  !< eddy diffusivity for momentum
900    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr         !< rain rate
901    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc       !< local array in multigrid/sor solver containing the pressure which is iteratively advanced in each iteration step
902    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tend        !< tendency field (time integration)
903    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric        !< coefficients of the tridiagonal matrix for solution of the Poisson equation in Fourier space
904    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l       !< velocity data (u at left boundary) from time level t-dt required for radiation boundary condition
905    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n       !< velocity data (u at north boundary) from time level t-dt required for radiation boundary condition
906    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r       !< velocity data (u at right boundary) from time level t-dt required for radiation boundary condition
907    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s       !< velocity data (u at south boundary) from time level t-dt required for radiation boundary condition
908    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l       !< velocity data (v at left boundary) from time level t-dt required for radiation boundary condition
909    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n       !< velocity data (v at north boundary) from time level t-dt required for radiation boundary condition
910    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r       !< velocity data (v at right boundary) from time level t-dt required for radiation boundary condition
911    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s       !< velocity data (v at south boundary) from time level t-dt required for radiation boundary condition
912    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l       !< velocity data (w at left boundary) from time level t-dt required for radiation boundary condition
913    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n       !< velocity data (w at north boundary) from time level t-dt required for radiation boundary condition
914    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r       !< velocity data (w at right boundary) from time level t-dt required for radiation boundary condition
915    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for radiation boundary condition
916
917    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_1  !< pointer for swapping of timelevels for respective quantity
918    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_2  !< pointer for swapping of timelevels for respective quantity
919    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_3  !< pointer for swapping of timelevels for respective quantity
920    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_1     !< pointer for swapping of timelevels for respective quantity
921    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_2     !< pointer for swapping of timelevels for respective quantity
922    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_3     !< pointer for swapping of timelevels for respective quantity
923    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  p       !< pointer: perturbation pressure
924    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  prho_1  !< pointer for swapping of timelevels for respective quantity
925    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_1    !< pointer for swapping of timelevels for respective quantity
926    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_2    !< pointer for swapping of timelevels for respective quantity
927    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_3    !< pointer for swapping of timelevels for respective quantity
928    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_1    !< pointer for swapping of timelevels for respective quantity
929    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_2    !< pointer for swapping of timelevels for respective quantity
930    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_3    !< pointer for swapping of timelevels for respective quantity
931    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_1    !< pointer for swapping of timelevels for respective quantity
932    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_2    !< pointer for swapping of timelevels for respective quantity
933    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_3    !< pointer for swapping of timelevels for respective quantity
934    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q_1     !< pointer for swapping of timelevels for respective quantity
935    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q_2     !< pointer for swapping of timelevels for respective quantity
936    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q_3     !< pointer for swapping of timelevels for respective quantity
937    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_1    !< pointer for swapping of timelevels for respective quantity
938    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_2    !< pointer for swapping of timelevels for respective quantity
939    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_3    !< pointer for swapping of timelevels for respective quantity
940    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_v    !< pointer: volume of liquid water
941    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_vp   !< pointer: liquid water weighting factor
942    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_1    !< pointer for swapping of timelevels for respective quantity
943    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_2    !< pointer for swapping of timelevels for respective quantity
944    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr_1    !< pointer for swapping of timelevels for respective quantity
945    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr_2    !< pointer for swapping of timelevels for respective quantity
946    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr_3    !< pointer for swapping of timelevels for respective quantity
947    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  rho_1   !< pointer for swapping of timelevels for respective quantity
948    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_1     !< pointer for swapping of timelevels for respective quantity
949    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_2     !< pointer for swapping of timelevels for respective quantity
950    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_3     !< pointer for swapping of timelevels for respective quantity
951    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_1    !< pointer for swapping of timelevels for respective quantity
952    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_2    !< pointer for swapping of timelevels for respective quantity
953    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_3    !< pointer for swapping of timelevels for respective quantity
954    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_1     !< pointer for swapping of timelevels for respective quantity
955    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_2     !< pointer for swapping of timelevels for respective quantity
956    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_3     !< pointer for swapping of timelevels for respective quantity
957    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_1     !< pointer for swapping of timelevels for respective quantity
958    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_2     !< pointer for swapping of timelevels for respective quantity
959    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_3     !< pointer for swapping of timelevels for respective quantity
960    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  vpt_1   !< pointer for swapping of timelevels for respective quantity
961    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_1     !< pointer for swapping of timelevels for respective quantity
962    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_2     !< pointer for swapping of timelevels for respective quantity
963    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_3     !< pointer for swapping of timelevels for respective quantity
964
965    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  diss       !< pointer: TKE dissipation
966    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  diss_p     !< pointer: prognostic value of TKE dissipation
967    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
968    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e_p        !< pointer: prognostic value of sgs tke
969    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc         !< pointer: cloud drop number density
970    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc_p       !< pointer: prognostic value of cloud drop number density
971    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr         !< pointer: rain drop number density
972    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr_p       !< pointer: prognostic value of rain drop number density
973    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  prho       !< pointer: potential density
974    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt         !< pointer: potential temperature
975    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt_p       !< pointer: prognostic value of potential temperature
976    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q          !< pointer: mixing ratio
977    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q_p        !< pointer: prognostic value of mixing ratio
978    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc         !< pointer: cloud water content
979    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc_p       !< pointer: cloud water content
980    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql         !< pointer: liquid water content
981    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql_c       !< pointer: change in liquid water content due to
982                                                                   !< condensation/evaporation during last time step
983    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr         !< pointer: rain water content
984    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr_p       !< pointer: prognostic value of rain water content
985    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  rho_ocean  !< pointer: density of ocean
986    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s          !< pointer: passive scalar
987    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s_p        !< pointer: prognostic value of passive scalar
988    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa         !< pointer: ocean salinity
989    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa_p       !< pointer: prognostic value of ocean salinity
990    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tdiss_m    !< pointer: weighted tendency of diss for previous sub-timestep (Runge-Kutta)
991    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
992    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
993    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
994    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
995    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
996    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
997    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
998    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
999    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
1000    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
1001    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
1002    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
1003    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u          !< pointer: horizontal velocity component u (x-direction)
1004    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u_p        !< pointer: prognostic value of u
1005    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v          !< pointer: horizontal velocity component v (y-direction)
1006    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v_p        !< pointer: prognostic value of v
1007    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  vpt        !< pointer: virtual potential temperature
1008    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w          !< pointer: vertical velocity component w (z-direction)
1009    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w_p        !< pointer: prognostic value of w
1010
1011    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  tri    !<  array to hold the tridiagonal matrix for solution of the Poisson equation in Fourier space (4th dimension for threads)
1012
1013    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air      !< air density profile on the uv grid
1014    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air_zw   !< air density profile on the w grid
1015    REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air     !< inverse air density profile on the uv grid
1016    REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air_zw  !< inverse air density profile on the w grid
1017
1018    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_mg     !< air density profiles on the uv grid for multigrid
1019    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_zw_mg  !< air density profiles on the w grid for multigrid
1020
1021    REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_input_conversion       !< conversion factor array for heatflux input
1022    REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_input_conversion      !< conversion factor array for waterflux input
1023    REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_input_conversion   !< conversion factor array for momentumflux input
1024    REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_output_conversion      !< conversion factor array for heatflux output
1025    REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_output_conversion     !< conversion factor array for waterflux output
1026    REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_output_conversion  !< conversion factor array for momentumflux output
1027
1028    REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyrho   !< density of air calculated with hydrostatic pressure
1029    REAL(wp), DIMENSION(:), ALLOCATABLE ::  exner   !< ratio of actual and potential temperature
1030    REAL(wp), DIMENSION(:), ALLOCATABLE ::  d_exner !< ratio of potential and actual temperature
1031
1032    SAVE
1033
1034 END MODULE arrays_3d
1035
1036
1037!------------------------------------------------------------------------------!
1038! Description:
1039! ------------
1040!> Definition of variables needed for time-averaging of 2d/3d data.
1041!------------------------------------------------------------------------------!
1042 MODULE averaging
1043 
1044    USE kinds
1045
1046    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ghf_av                 !< avg. ground heat flux
1047    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lwp_av                 !< avg. liquid water path
1048    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ol_av                  !< avg. Obukhov length
1049    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pt_2m_av               !< avg. 2m- air potential temperature
1050    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  qsws_av                !< avg. surface moisture flux
1051    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  r_a_av                 !< avg. resistance
1052    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ssws_av                !< avg. surface scalar flux
1053    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  shf_av                 !< avg. surface heat flux
1054    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tsurf_av               !< avg. surface temperature
1055    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ts_av                  !< avg. characteristic temperature scale
1056    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  us_av                  !< avg. friction velocity
1057    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  z0_av                  !< avg. roughness length for momentum
1058    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  z0h_av                 !< avg. roughness length for heat
1059    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  z0q_av                 !< avg. roughness length for moisture
1060
1061    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_av       !< avg. tke dissipation rate
1062    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_av          !< avg. subgrid-scale tke
1063    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh_av         !< avg. eddy diffusivity for heat
1064    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km_av         !< avg. eddy diffusivity for momentum
1065    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  lpt_av        !< avg. liquid water potential temperature
1066    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_av         !< avg. cloud drop number density
1067    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_av         !< avg. rain drop number density
1068    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  p_av          !< avg. perturbation pressure
1069    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pc_av         !< avg. particle/droplet concentration
1070    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pr_av         !< avg. particle/droplet radius
1071    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  prr_av        !< avg. precipitation rate
1072    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_av         !< avg. potential temperature
1073    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  q_av          !< avg. mixing ratio
1074                                                                      !< (or total water content with active cloud physics)
1075    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_av         !< avg. cloud water content
1076    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_av         !< avg. liquid water content
1077    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_c_av       !< avg. change in liquid water content due to
1078                                                                      !< condensation/evaporation during last time step
1079    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_v_av       !< avg. volume of liquid water
1080    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_vp_av      !< avg. liquid water weighting factor
1081    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qr_av         !< avg. rain water content
1082    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qv_av         !< avg. water vapor content (mixing ratio)
1083    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  rho_ocean_av  !< avg. ocean density
1084    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_av          !< avg. passive scalar
1085    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_av         !< avg. salinity
1086    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_av          !< avg. horizontal velocity component u
1087    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_av          !< avg. horizontal velocity component v
1088    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  vpt_av        !< avg. virtual potential temperature
1089    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_av          !< avg. vertical velocity component
1090 
1091 END MODULE averaging
1092
1093 
1094!------------------------------------------------------------------------------!
1095! Description:
1096! ------------
1097!> Definition of parameters for program control
1098!------------------------------------------------------------------------------!
1099 MODULE control_parameters
1100
1101    USE kinds
1102
1103    TYPE file_status
1104       LOGICAL ::  opened         !< file is currently open
1105       LOGICAL ::  opened_before  !< file is currently closed, but has been openend before
1106    END TYPE file_status
1107   
1108    INTEGER, PARAMETER      ::  mask_xyz_dimension = 100  !< limit of mask dimensions (100 points in each direction)
1109    INTEGER, PARAMETER      ::  max_masks = 50            !< maximum number of masks
1110    INTEGER(iwp), PARAMETER ::  varnamelength = 30        !< length of output variable names
1111
1112    TYPE(file_status), DIMENSION(200+2*max_masks) ::                &  !< indicates if file is open or if it has been opened before
1113                             openfile = file_status(.FALSE.,.FALSE.)
1114
1115    CHARACTER (LEN=1)    ::  cycle_mg = 'w'                               !< namelist parameter (see documentation)
1116    CHARACTER (LEN=1)    ::  timestep_reason = ' '                        !< 'A'dvection or 'D'iffusion criterion, written to RUN_CONTROL file
1117    CHARACTER (LEN=8)    ::  coupling_char = ''                           !< appended to filenames in coupled or nested runs ('_O': ocean PE,
1118                                                                          !< '_NV': vertically nested atmosphere PE, '_N##': PE of nested domain ##
1119    CHARACTER (LEN=10)   ::  run_date = ' '                               !< date of simulation run
1120    CHARACTER (LEN=8)    ::  run_time = ' '                               !< time of simulation run
1121    CHARACTER (LEN=5)    ::  run_zone = ' '                               !< time zone of simulation run
1122    CHARACTER (LEN=9)    ::  simulated_time_chr                           !< simulated time, printed to RUN_CONTROL file
1123    CHARACTER (LEN=11)   ::  topography_grid_convention = ' '             !< namelist parameter
1124    CHARACTER (LEN=12)   ::  version = ' '                                !< PALM version number
1125    CHARACTER (LEN=12)   ::  revision = ' '                               !< PALM revision number
1126    CHARACTER (LEN=12)   ::  user_interface_current_revision = ' '        !< revision number of the currently used user-interface (must match user_interface_required_revision)
1127    CHARACTER (LEN=12)   ::  user_interface_required_revision = ' '       !< required user-interface revision number
1128    CHARACTER (LEN=16)   ::  conserve_volume_flow_mode = 'default'        !< namelist parameter
1129    CHARACTER (LEN=16)   ::  loop_optimization = 'cache'                  !< namelist parameter
1130    CHARACTER (LEN=16)   ::  momentum_advec = 'ws-scheme'                 !< namelist parameter
1131    CHARACTER (LEN=16)   ::  psolver = 'poisfft'                          !< namelist parameter
1132    CHARACTER (LEN=16)   ::  scalar_advec = 'ws-scheme'                   !< namelist parameter
1133    CHARACTER (LEN=20)   ::  approximation = 'boussinesq'                 !< namelist parameter
1134    CHARACTER (LEN=40)   ::  flux_input_mode = 'approximation-specific'   !< type of flux input: dynamic or kinematic
1135    CHARACTER (LEN=40)   ::  flux_output_mode = 'approximation-specific'  !< type of flux output: dynamic or kinematic
1136    CHARACTER (LEN=20)   ::  bc_e_b = 'neumann'                           !< namelist parameter
1137    CHARACTER (LEN=20)   ::  bc_lr = 'cyclic'                             !< namelist parameter
1138    CHARACTER (LEN=20)   ::  bc_ns = 'cyclic'                             !< namelist parameter
1139    CHARACTER (LEN=20)   ::  bc_p_b = 'neumann'                           !< namelist parameter
1140    CHARACTER (LEN=20)   ::  bc_p_t = 'dirichlet'                         !< namelist parameter
1141    CHARACTER (LEN=20)   ::  bc_pt_b = 'dirichlet'                        !< namelist parameter
1142    CHARACTER (LEN=20)   ::  bc_pt_t = 'initial_gradient'                 !< namelist parameter
1143    CHARACTER (LEN=20)   ::  bc_q_b = 'dirichlet'                         !< namelist parameter
1144    CHARACTER (LEN=20)   ::  bc_q_t = 'neumann'                           !< namelist parameter
1145    CHARACTER (LEN=20)   ::  bc_s_b = 'dirichlet'                         !< namelist parameter
1146    CHARACTER (LEN=20)   ::  bc_s_t = 'initial_gradient'                  !< namelist parameter
1147    CHARACTER (LEN=20)   ::  bc_uv_b = 'dirichlet'                        !< namelist parameter
1148    CHARACTER (LEN=20)   ::  bc_uv_t = 'dirichlet'                        !< namelist parameter
1149    CHARACTER (LEN=20)   ::  coupling_mode = 'uncoupled'                  !< coupling mode for atmosphere-ocean coupling 
1150    CHARACTER (LEN=20)   ::  coupling_mode_remote = 'uncoupled'           !< coupling mode of the remote process in case of coupled atmosphere-ocean runs
1151    CHARACTER (LEN=20)   ::  dissipation_1d = 'detering'                  !< namelist parameter
1152    CHARACTER (LEN=20)   ::  fft_method = 'temperton-algorithm'           !< namelist parameter
1153    CHARACTER (LEN=20)   ::  mixing_length_1d = 'blackadar'               !< namelist parameter
1154    CHARACTER (LEN=20)   ::  random_generator = 'random-parallel'         !< namelist parameter
1155    CHARACTER (LEN=20)   ::  reference_state = 'initial_profile'          !< namelist parameter 
1156    CHARACTER (LEN=20)   ::  timestep_scheme = 'runge-kutta-3'            !< namelist parameter       
1157    CHARACTER (LEN=20)   ::  turbulence_closure = 'Moeng_Wyngaard'        !< namelist parameter
1158    CHARACTER (LEN=40)   ::  topography = 'flat'                          !< namelist parameter
1159    CHARACTER (LEN=64)   ::  host = '????'                                !< configuration identifier as given by palmrun option -c, ENVPAR namelist parameter provided by palmrun
1160    CHARACTER (LEN=80)   ::  log_message                                  !< user-defined message for debugging (sse data_log.f90)
1161    CHARACTER (LEN=80)   ::  run_identifier                               !< run identifier as given by palmrun option -r, ENVPAR namelist parameter provided by palmrun
1162    CHARACTER (LEN=100)  ::  initializing_actions = ' '                   !< namelist parameter
1163    CHARACTER (LEN=100)  ::  restart_string = ' '                         !< for storing strings in case of writing/reading restart data
1164    CHARACTER (LEN=210)  ::  run_description_header                       !< string containing diverse run informations as run identifier, coupling mode, host, ensemble number, run date and time
1165    CHARACTER (LEN=1000) ::  debug_string = ' '                           !<.....
1166    CHARACTER (LEN=1000) ::  message_string = ' '                         !< dynamic string for error message output
1167
1168    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output = ' '       !< namelist parameter
1169    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output_user = ' '  !< namelist parameter
1170    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  doav = ' '              !< label array for multi-dimensional,
1171                                                                              !< averaged output quantities
1172                                           
1173    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks = ' '       !< namelist parameter
1174    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks_user = ' '  !< namelist parameter
1175
1176    CHARACTER (LEN=varnamelength), DIMENSION(300) ::  data_output_pr = ' '  !< namelist parameter
1177   
1178    CHARACTER (LEN=varnamelength), DIMENSION(200) ::  data_output_pr_user = ' '  !< namelist parameter
1179   
1180    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,0:1,100) ::  domask = ' ' !< label array for multi-dimensional,
1181                                                                                 !< masked output quantities
1182   
1183    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do2d = ' '  !< label array for 2d output quantities
1184    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do3d = ' '  !< label array for 3d output quantities
1185
1186    INTEGER(iwp), PARAMETER ::  fl_max = 500     !< maximum number of virtual-flight measurements
1187    INTEGER(iwp), PARAMETER ::  var_fl_max = 20  !< maximum number of different sampling variables in virtual flight measurements
1188   
1189    INTEGER(iwp) ::  abort_mode = 1                    !< abort condition (nested runs)
1190    INTEGER(iwp) ::  agt_time_count = 0                !< number of output intervals for agent data output
1191    INTEGER(iwp) ::  average_count_pr = 0              !< number of samples in vertical-profile output
1192    INTEGER(iwp) ::  average_count_3d = 0              !< number of samples in 3d output
1193    INTEGER(iwp) ::  current_timestep_number = 0       !< current timestep number, printed to RUN_CONTROL file
1194    INTEGER(iwp) ::  coupling_topology = 0             !< switch for atmosphere-ocean-coupling: 0: same number of grid points and PEs along x and y in atmosphere and ocean, otherwise 1
1195    INTEGER(iwp) ::  dist_range = 0                    !< switch for steering the horizontal disturbance range, 1: inflow disturbances in case of non-cyclic horizontal BC, 0: otherwise
1196    INTEGER(iwp) ::  disturbance_level_ind_b           !< lowest grid index where flow disturbance is applied
1197    INTEGER(iwp) ::  disturbance_level_ind_t           !< highest grid index where flow disturbance is applied
1198    INTEGER(iwp) ::  doav_n = 0                        !< number of 2d/3d output quantities subject to time averaging
1199    INTEGER(iwp) ::  dopr_n = 0                        !< number of profile output quantities subject to time averaging
1200    INTEGER(iwp) ::  dopr_time_count = 0               !< number of output intervals for profile output
1201    INTEGER(iwp) ::  dopts_time_count = 0              !< number of output intervals for particle data timeseries
1202    INTEGER(iwp) ::  dots_time_count = 0               !< number of output intervals for timeseries output
1203    INTEGER(iwp) ::  dp_level_ind_b = 0                !< lowest grid index for external pressure gradient forcing
1204    INTEGER(iwp) ::  ensemble_member_nr = 0            !< namelist parameter
1205    INTEGER(iwp) ::  gamma_mg                          !< switch for steering the multigrid cycle: 1: v-cycle, 2: w-cycle
1206    INTEGER(iwp) ::  gathered_size                     !< number of total domain grid points of the grid level which is gathered on PE0 (multigrid solver)
1207    INTEGER(iwp) ::  grid_level                        !< current grid level handled in the multigrid solver
1208    INTEGER(iwp) ::  ibc_e_b                           !< integer flag for bc_e_b
1209    INTEGER(iwp) ::  ibc_p_b                           !< integer flag for bc_p_b
1210    INTEGER(iwp) ::  ibc_p_t                           !< integer flag for bc_p_t
1211    INTEGER(iwp) ::  ibc_pt_b                          !< integer flag for bc_pt_b
1212    INTEGER(iwp) ::  ibc_pt_t                          !< integer flag for bc_pt_t
1213    INTEGER(iwp) ::  ibc_q_b                           !< integer flag for bc_q_b
1214    INTEGER(iwp) ::  ibc_q_t                           !< integer flag for bc_q_t
1215    INTEGER(iwp) ::  ibc_s_b                           !< integer flag for bc_s_b
1216    INTEGER(iwp) ::  ibc_s_t                           !< integer flag for bc_s_t
1217    INTEGER(iwp) ::  ibc_uv_b                          !< integer flag for bc_uv_b
1218    INTEGER(iwp) ::  ibc_uv_t                          !< integer flag for bc_uv_t
1219    INTEGER(iwp) ::  inflow_disturbance_begin = -1     !< namelist parameter
1220    INTEGER(iwp) ::  inflow_disturbance_end = -1       !< namelist parameter
1221    INTEGER(iwp) ::  intermediate_timestep_count       !< number of current Runge-Kutta substep
1222    INTEGER(iwp) ::  intermediate_timestep_count_max   !< maximum number of Runge-Kutta substeps
1223    INTEGER(iwp) ::  io_group = 0                      !< I/O group to which the PE belongs (= #PE / io_blocks)
1224    INTEGER(iwp) ::  io_blocks = 1                     !< number of blocks for which I/O is done in sequence (total number of PEs / maximum_parallel_io_streams)
1225    INTEGER(iwp) ::  iran = -1234567                   !< integer random number used for flow disturbances
1226    INTEGER(iwp) ::  length = 0                        !< integer that specifies the length of a string in case of writing/reading restart data
1227    INTEGER(iwp) ::  masks = 0                         !< counter for number of masked output quantities
1228    INTEGER(iwp) ::  maximum_grid_level                !< number of grid levels that the multigrid solver is using
1229    INTEGER(iwp) ::  maximum_parallel_io_streams = -1  !< maximum number of parallel io streams that the underlying parallel file system allows, set with palmrun option -w, ENVPAR namelist parameter, provided by palmrun
1230    INTEGER(iwp) ::  max_pr_user = 0                   !< number of user-defined profiles (must not change within a job chain)
1231    INTEGER(iwp) ::  max_pr_user_tmp = 0               !< number of user-defined profiles that is temporary stored to check it against max_pr_user in case of restarts
1232    INTEGER(iwp) ::  mgcycles = 0                      !< number of multigrid cycles that the multigrid solver has actually carried out
1233    INTEGER(iwp) ::  mg_cycles = 4                     !< namelist parameter
1234    INTEGER(iwp) ::  mg_switch_to_pe0_level = -1       !< namelist parameter
1235    INTEGER(iwp) ::  ngsrb = 2                         !< namelist parameter
1236    INTEGER(iwp) ::  nr_timesteps_this_run = 0         !< number of timesteps (cpu time measurements)
1237    INTEGER(iwp) ::  nsor = 20                         !< namelist parameter
1238    INTEGER(iwp) ::  nsor_ini = 100                    !< namelist parameter
1239    INTEGER(iwp) ::  n_sor                             !< number of iterations to be used in SOR-scheme
1240    INTEGER(iwp) ::  normalizing_region = 0            !< namelist parameter
1241    INTEGER(iwp) ::  num_mean_inflow_profiles = 7      !< number of mean inflow profiles in case of turbulent inflow
1242    INTEGER(iwp) ::  num_leg=0                         !< number of different legs in virtual flight measurements
1243    INTEGER(iwp) ::  num_var_fl                        !< number of sampling/output variables in virtual flight measurements
1244    INTEGER(iwp) ::  num_var_fl_user=0                 !< number of user-defined sampling/output variables in virtual flight measurements
1245    INTEGER(iwp) ::  number_stretch_level_start        !< number of user-specified start levels for stretching
1246    INTEGER(iwp) ::  number_stretch_level_end          !< number of user-specified end levels for stretching
1247    INTEGER(iwp) ::  nz_do3d = -9999                   !< namelist parameter
1248    INTEGER(iwp) ::  prt_time_count = 0                !< number of output intervals for particle data output
1249    INTEGER(iwp) ::  recycling_plane                   !< position of recycling plane along x (in grid points) in case of turbulence recycling
1250    INTEGER(iwp) ::  runnr = 0                         !< number of run in job chain
1251    INTEGER(iwp) ::  subdomain_size                    !< number of grid points in (3d) subdomain including ghost points
1252    INTEGER(iwp) ::  terminate_coupled = 0             !< switch for steering termination in case of coupled runs
1253    INTEGER(iwp) ::  terminate_coupled_remote = 0      !< switch for steering termination in case of coupled runs (condition of the remote model)
1254    INTEGER(iwp) ::  timestep_count = 0                !< number of timesteps carried out since the beginning of the initial run
1255    INTEGER(iwp) ::  y_shift = 0                       !< namelist parameter
1256   
1257    INTEGER(iwp) ::  dist_nxl(0:1)                               !< left boundary of disturbance region
1258    INTEGER(iwp) ::  dist_nxr(0:1)                               !< right boundary of disturbance region
1259    INTEGER(iwp) ::  dist_nyn(0:1)                               !< north boundary of disturbance region
1260    INTEGER(iwp) ::  dist_nys(0:1)                               !< south boundary of disturbance region
1261    INTEGER(iwp) ::  do2d_no(0:1) = 0                            !< number of 2d output quantities
1262    INTEGER(iwp) ::  do2d_xy_time_count(0:1) = 0                 !< number of output intervals for 2d data (xy)
1263    INTEGER(iwp) ::  do2d_xz_time_count(0:1) = 0                 !< number of output intervals for 2d data (xz)
1264    INTEGER(iwp) ::  do2d_yz_time_count(0:1) = 0                 !< number of output intervals for 2d data (yz)
1265    INTEGER(iwp) ::  do3d_no(0:1) = 0                            !< number of 3d output quantities
1266    INTEGER(iwp) ::  do3d_time_count(0:1) = 0                    !< number of output intervals for 3d data
1267    INTEGER(iwp) ::  domask_no(max_masks,0:1) = 0                !< number of masked output quantities
1268    INTEGER(iwp) ::  domask_time_count(max_masks,0:1)            !< number of output intervals for masked data
1269    INTEGER(iwp) ::  dz_stretch_level_end_index(9)               !< vertical grid level index until which the vertical grid spacing is stretched
1270    INTEGER(iwp) ::  dz_stretch_level_start_index(9)             !< vertical grid level index above which the vertical grid spacing is stretched
1271    INTEGER(iwp) ::  mask_size(max_masks,3) = -1                 !< size of mask array per mask and dimension (for netcdf output)
1272    INTEGER(iwp) ::  mask_size_l(max_masks,3) = -1               !< subdomain size of mask array per mask and dimension (for netcdf output)
1273    INTEGER(iwp) ::  mask_start_l(max_masks,3) = -1              !< subdomain start index of mask array (for netcdf output)
1274    INTEGER(iwp) ::  pt_vertical_gradient_level_ind(10) = -9999  !< grid index values of pt_vertical_gradient_level(s)
1275    INTEGER(iwp) ::  q_vertical_gradient_level_ind(10) = -9999   !< grid index values of q_vertical_gradient_level(s)
1276    INTEGER(iwp) ::  s_vertical_gradient_level_ind(10) = -9999   !< grid index values of s_vertical_gradient_level(s)   
1277    INTEGER(iwp) ::  section(100,3)                              !< collective array for section_xy/xz/yz
1278    INTEGER(iwp) ::  section_xy(100) = -9999                     !< namelist parameter
1279    INTEGER(iwp) ::  section_xz(100) = -9999                     !< namelist parameter
1280    INTEGER(iwp) ::  section_yz(100) = -9999                     !< namelist parameter
1281    INTEGER(iwp) ::  ug_vertical_gradient_level_ind(10) = -9999  !< grid index values of ug_vertical_gradient_level(s)
1282    INTEGER(iwp) ::  vg_vertical_gradient_level_ind(10) = -9999  !< grid index values of vg_vertical_gradient_level(s)
1283    INTEGER(iwp) ::  subs_vertical_gradient_level_i(10) = -9999  !< grid index values of subs_vertical_gradient_level(s)
1284
1285    INTEGER(iwp), DIMENSION(0:1) ::  ntdim_2d_xy  !< number of output intervals for 2d data (xy)
1286    INTEGER(iwp), DIMENSION(0:1) ::  ntdim_2d_xz  !< number of output intervals for 2d data (xz)
1287    INTEGER(iwp), DIMENSION(0:1) ::  ntdim_2d_yz  !< number of output intervals for 2d data (yz)
1288    INTEGER(iwp), DIMENSION(0:1) ::  ntdim_3d     !< number of output intervals for 3d data
1289
1290    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  grid_level_count  !< internal switch for steering the multigrid v- and w-cycles
1291
1292    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_i         !< subdomain grid index of masked output point on x-dimension
1293    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_j         !< subdomain grid index of masked output point on y-dimension
1294    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_k         !< subdomain grid index of masked output point on z-dimension
1295    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_i_global  !< global grid index of masked output point on x-dimension
1296    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_j_global  !< global grid index of masked output point on y-dimension
1297    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_k_global  !< global grid index of masked output point on z-dimension
1298
1299    INTEGER(iwp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_k_over_surface = -1  !< namelist parameter, k index of height over surface
1300
1301    LOGICAL ::  agent_time_unlimited = .FALSE.                   !< namelist parameter
1302    LOGICAL ::  air_chemistry = .FALSE.                          !< chemistry model switch
1303    LOGICAL ::  bc_dirichlet_l                                   !< flag indicating dirichlet boundary condition on left model boundary
1304    LOGICAL ::  bc_dirichlet_n                                   !< flag indicating dirichlet boundary condition on north model boundary
1305    LOGICAL ::  bc_dirichlet_r                                   !< flag indicating dirichlet boundary condition on right model boundary
1306    LOGICAL ::  bc_dirichlet_s                                   !< flag indicating dirichlet boundary condition on south model boundary
1307    LOGICAL ::  bc_lr_cyc =.TRUE.                                !< left-right boundary condition cyclic?
1308    LOGICAL ::  bc_lr_dirrad = .FALSE.                           !< left-right boundary condition dirichlet/radiation?
1309    LOGICAL ::  bc_lr_raddir = .FALSE.                           !< left-right boundary condition radiation/dirichlet?
1310    LOGICAL ::  bc_ns_cyc = .TRUE.                               !< north-south boundary condition cyclic?
1311    LOGICAL ::  bc_ns_dirrad = .FALSE.                           !< north-south boundary condition dirichlet/radiation?
1312    LOGICAL ::  bc_ns_raddir = .FALSE.                           !< north-south boundary condition radiation/dirichlet?
1313    LOGICAL ::  bc_radiation_l = .FALSE.                         !< radiation boundary condition for outflow at left domain boundary
1314    LOGICAL ::  bc_radiation_n = .FALSE.                         !< radiation boundary condition for outflow at north domain boundary
1315    LOGICAL ::  bc_radiation_r = .FALSE.                         !< radiation boundary condition for outflow at right domain boundary
1316    LOGICAL ::  bc_radiation_s = .FALSE.                         !< radiation boundary condition for outflow at south domain boundary
1317    LOGICAL ::  biometeorology = .FALSE.                         !< biometeorology module switch
1318    LOGICAL ::  calc_soil_moisture_during_spinup = .FALSE.       !< namelist parameter
1319    LOGICAL ::  call_psolver_at_all_substeps = .TRUE.            !< namelist parameter
1320    LOGICAL ::  child_domain  = .FALSE.                          !< flag indicating that model is nested in a parent domain
1321    LOGICAL ::  cloud_droplets = .FALSE.                         !< namelist parameter
1322    LOGICAL ::  complex_terrain = .FALSE.                        !< namelist parameter
1323    LOGICAL ::  conserve_volume_flow = .FALSE.                   !< namelist parameter
1324    LOGICAL ::  constant_diffusion = .FALSE.                     !< diffusion coefficient constant?
1325    LOGICAL ::  constant_flux_layer = .TRUE.                     !< namelist parameter
1326    LOGICAL ::  constant_heatflux = .TRUE.                       !< heat flux at all surfaces constant?
1327    LOGICAL ::  constant_top_heatflux = .TRUE.                   !< heat flux at domain top constant?
1328    LOGICAL ::  constant_top_momentumflux = .FALSE.              !< momentum flux at domain topconstant?
1329    LOGICAL ::  constant_top_salinityflux = .TRUE.               !< constant salinity flux at ocean surface
1330    LOGICAL ::  constant_top_scalarflux = .TRUE.                 !< passive-scalar flux at domain top constant?
1331    LOGICAL ::  constant_scalarflux = .TRUE.                     !< passive-scalar flux at surfaces constant?
1332    LOGICAL ::  constant_waterflux = .TRUE.                      !< water flux at all surfaces constant?
1333    LOGICAL ::  create_disturbances = .TRUE.                     !< namelist parameter
1334    LOGICAL ::  data_output_during_spinup = .FALSE.              !< namelist parameter
1335    LOGICAL ::  data_output_2d_on_each_pe = .TRUE.               !< namelist parameter
1336    LOGICAL ::  debug_output = .FALSE.                           !< namelist parameter
1337    LOGICAL ::  debug_output_timestep = .FALSE.                  !< namelist parameter
1338    LOGICAL ::  disturbance_created = .FALSE.                    !< flow disturbance imposed?
1339    LOGICAL ::  do2d_at_begin = .FALSE.                          !< namelist parameter
1340    LOGICAL ::  do3d_at_begin = .FALSE.                          !< namelist parameter
1341    LOGICAL ::  do_output_at_2m = .FALSE.                        !< flag for activating calculation of potential temperature at z = 2 m
1342    LOGICAL ::  do_sum = .FALSE.                                 !< contribute to time average of profile data?
1343    LOGICAL ::  dp_external = .FALSE.                            !< namelist parameter
1344    LOGICAL ::  dp_smooth = .FALSE.                              !< namelist parameter
1345    LOGICAL ::  dt_fixed = .FALSE.                               !< fixed timestep (namelist parameter dt set)?
1346    LOGICAL ::  dt_3d_reached                                    !< internal timestep for particle advection
1347    LOGICAL ::  dt_3d_reached_l                                  !< internal timestep for particle advection
1348    LOGICAL ::  first_call_lpm = .TRUE.                          !< call lpm only once per timestep?
1349    LOGICAL ::  first_call_mas = .TRUE.                          !< call mas only once per timestep
1350    LOGICAL ::  force_print_header = .FALSE.                     !< namelist parameter
1351    LOGICAL ::  galilei_transformation = .FALSE.                 !< namelist parameter
1352    LOGICAL ::  humidity = .FALSE.                               !< namelist parameter
1353    LOGICAL ::  humidity_remote = .FALSE.                        !< switch for receiving near-surface humidity flux (atmosphere-ocean coupling)
1354    LOGICAL ::  indoor_model = .FALSE.                           !< switch for indoor-climate and energy-demand model
1355    LOGICAL ::  large_scale_forcing = .FALSE.                    !< namelist parameter
1356    LOGICAL ::  large_scale_subsidence = .FALSE.                 !< namelist parameter
1357    LOGICAL ::  land_surface = .FALSE.                           !< use land surface model?
1358    LOGICAL ::  les_dynamic = .FALSE.                            !< use dynamic subgrid model as turbulence closure for LES mode
1359    LOGICAL ::  les_mw = .FALSE.                                 !< use Moeng-Wyngaard turbulence closure for LES mode
1360    LOGICAL ::  lsf_exception = .FALSE.                          !< use of lsf with buildings (temporary)?
1361    LOGICAL ::  lsf_surf = .TRUE.                                !< use surface forcing (large scale forcing)?
1362    LOGICAL ::  lsf_vert = .TRUE.                                !< use atmospheric forcing (large scale forcing)?
1363    LOGICAL ::  masking_method = .FALSE.                         !< namelist parameter
1364    LOGICAL ::  mg_switch_to_pe0 = .FALSE.                       !< internal multigrid switch for steering the ghost point exchange in case that data has been collected on PE0
1365    LOGICAL ::  monotonic_limiter_z = .FALSE.                    !< use monotonic flux limiter for vertical scalar advection
1366    LOGICAL ::  nesting_offline = .FALSE.                        !< flag controlling offline nesting in COSMO model 
1367    LOGICAL ::  neutral = .FALSE.                                !< namelist parameter
1368    LOGICAL ::  nudging = .FALSE.                                !< namelist parameter
1369    LOGICAL ::  ocean_mode = .FALSE.                             !< namelist parameter
1370    LOGICAL ::  passive_scalar = .FALSE.                         !< namelist parameter
1371    LOGICAL ::  plant_canopy = .FALSE.                           !< switch for use of plant canopy model
1372    LOGICAL ::  random_heatflux = .FALSE.                        !< namelist parameter
1373    LOGICAL ::  rans_mode = .FALSE.                              !< switch between RANS and LES mode
1374    LOGICAL ::  rans_tke_e = .FALSE.                             !< use TKE-e turbulence closure for RANS mode
1375    LOGICAL ::  rans_tke_l = .FALSE.                             !< use TKE-l turbulence closure for RANS mode
1376    LOGICAL ::  read_svf = .FALSE.                               !< ENVPAR namelist parameter to steer input of svf (ENVPAR is provided by palmrun)
1377    LOGICAL ::  recycling_yshift = .FALSE.                       !< namelist parameter
1378    LOGICAL ::  run_control_header = .FALSE.                     !< onetime output of RUN_CONTROL header
1379    LOGICAL ::  run_coupled = .TRUE.                             !< internal switch telling PALM to run in coupled mode (i.e. to exchange surface data) in case of atmosphere-ocean coupling
1380    LOGICAL ::  salsa = .FALSE.                                  !< switch for the sectional aerosol module salsa
1381    LOGICAL ::  scalar_rayleigh_damping = .TRUE.                 !< namelist parameter
1382    LOGICAL ::  sloping_surface = .FALSE.                        !< use sloped surface? (namelist parameter alpha_surface)
1383    LOGICAL ::  spinup = .FALSE.                                 !< perform model spinup without atmosphere code?
1384    LOGICAL ::  surface_output = .FALSE.                         !< output of surface data
1385    LOGICAL ::  stop_dt = .FALSE.                                !< internal switch to stop the time stepping
1386    LOGICAL ::  synchronous_exchange = .FALSE.                   !< namelist parameter
1387    LOGICAL ::  syn_turb_gen = .FALSE.                           !< flag for synthetic turbulence generator module
1388    LOGICAL ::  terminate_run = .FALSE.                          !< terminate run (cpu-time limit, restarts)?
1389    LOGICAL ::  topo_no_distinct = .FALSE.                       !< flag controlling classification of topography surfaces
1390    LOGICAL ::  transpose_compute_overlap = .FALSE.              !< namelist parameter
1391    LOGICAL ::  turbulent_inflow = .FALSE.                       !< namelist parameter
1392    LOGICAL ::  turbulent_outflow = .FALSE.                      !< namelist parameter
1393    LOGICAL ::  urban_surface = .FALSE.                          !< use urban surface model?
1394    LOGICAL ::  use_cmax = .TRUE.                                !< namelist parameter
1395    LOGICAL ::  use_free_convection_scaling = .FALSE.            !< namelist parameter to switch on free convection velocity scale in calculation of horizontal wind speed (surface_layer_fluxes)
1396    LOGICAL ::  use_initial_profile_as_reference = .FALSE.       !< use of initial profiles as reference state?
1397    LOGICAL ::  use_prescribed_profile_data = .FALSE.            !< use of prescribed wind profiles?
1398                                                                 !< (namelist parameters u_profile, v_profile)
1399    LOGICAL ::  use_single_reference_value = .FALSE.             !< use of single value as reference state?
1400    LOGICAL ::  use_subsidence_tendencies = .FALSE.              !< namelist parameter
1401    LOGICAL ::  use_surface_fluxes = .FALSE.                     !< namelist parameter
1402    LOGICAL ::  use_top_fluxes = .FALSE.                         !< namelist parameter
1403    LOGICAL ::  use_ug_for_galilei_tr = .TRUE.                   !< namelist parameter
1404    LOGICAL ::  use_upstream_for_tke = .FALSE.                   !< namelist parameter
1405    LOGICAL ::  virtual_flight = .FALSE.                         !< use virtual flight model
1406    LOGICAL ::  virtual_measurement = .FALSE.                    !< control parameter to switch-on virtual measurements
1407    LOGICAL ::  wall_adjustment = .TRUE.                         !< namelist parameter
1408    LOGICAL ::  wind_turbine = .FALSE.                           !< flag for use of wind turbine model
1409    LOGICAL ::  write_binary = .FALSE.                           !< ENVPAR namelist parameter to steer restart I/O (ENVPAR is provided by palmrun)
1410    LOGICAL ::  write_svf = .FALSE.                              !< ENVPAR namelist parameter to steer output of svf (ENVPAR is provided by palmrun)
1411    LOGICAL ::  ws_scheme_sca = .FALSE.                          !< use Wicker-Skamarock scheme (scalar advection)?
1412    LOGICAL ::  ws_scheme_mom = .FALSE.                          !< use Wicker-Skamarock scheme (momentum advection)?
1413
1414    LOGICAL ::  data_output_xy(0:1) = .FALSE.                !< output of xy cross-section data?
1415    LOGICAL ::  data_output_xz(0:1) = .FALSE.                !< output of xz cross-section data?
1416    LOGICAL ::  data_output_yz(0:1) = .FALSE.                !< output of yz cross-section data?
1417
1418    LOGICAL, DIMENSION(max_masks) ::  mask_surface = .FALSE.      !< flag for surface-following masked output
1419
1420    REAL(wp) ::  advected_distance_x = 0.0_wp                  !< advected distance of model domain along x
1421                                                               !< (galilei transformation)
1422    REAL(wp) ::  advected_distance_y = 0.0_wp                  !< advected distance of model domain along y
1423                                                               !< (galilei transformation)
1424    REAL(wp) ::  alpha_surface = 0.0_wp                        !< namelist parameter
1425    REAL(wp) ::  atmos_ocean_sign = 1.0_wp                     !< vertical-grid conversion factor
1426                                                               !< (=1.0 in atmosphere, =-1.0 in ocean)
1427    REAL(wp) ::  averaging_interval = 0.0_wp                   !< namelist parameter
1428    REAL(wp) ::  averaging_interval_pr = 9999999.9_wp          !< namelist parameter
1429    REAL(wp) ::  bc_pt_t_val                                   !< vertical gradient of pt near domain top
1430    REAL(wp) ::  bc_q_t_val                                    !< vertical gradient of humidity near domain top
1431    REAL(wp) ::  bc_s_t_val                                    !< vertical gradient of passive scalar near domain top
1432    REAL(wp) ::  bottom_salinityflux = 0.0_wp                  !< namelist parameter
1433    REAL(wp) ::  building_height = 50.0_wp                     !< namelist parameter
1434    REAL(wp) ::  building_length_x = 50.0_wp                   !< namelist parameter
1435    REAL(wp) ::  building_length_y = 50.0_wp                   !< namelist parameter
1436    REAL(wp) ::  building_wall_left = 9999999.9_wp             !< namelist parameter
1437    REAL(wp) ::  building_wall_south = 9999999.9_wp            !< namelist parameter
1438    REAL(wp) ::  canyon_height = 50.0_wp                       !< namelist parameter
1439    REAL(wp) ::  canyon_width_x = 9999999.9_wp                 !< namelist parameter
1440    REAL(wp) ::  canyon_width_y = 9999999.9_wp                 !< namelist parameter
1441    REAL(wp) ::  canyon_wall_left = 9999999.9_wp               !< namelist parameter
1442    REAL(wp) ::  canyon_wall_south = 9999999.9_wp              !< namelist parameter
1443    REAL(wp) ::  cfl_factor = -1.0_wp                          !< namelist parameter
1444    REAL(wp) ::  cos_alpha_surface                             !< cosine of alpha_surface
1445    REAL(wp) ::  coupling_start_time = 0.0_wp                  !< namelist parameter
1446    REAL(wp) ::  days_since_reference_point = 0.0_wp           !< days after atmosphere-ocean coupling has been activated,
1447                                                               !< or after spinup phase of LSM has been finished
1448    REAL(wp) ::  disturbance_amplitude = 0.25_wp               !< namelist parameter
1449    REAL(wp) ::  disturbance_energy_limit = 0.01_wp            !< namelist parameter
1450    REAL(wp) ::  disturbance_level_b = -9999999.9_wp           !< namelist parameter
1451    REAL(wp) ::  disturbance_level_t = -9999999.9_wp           !< namelist parameter
1452    REAL(wp) ::  dp_level_b = 0.0_wp                           !< namelist parameter
1453    REAL(wp) ::  dt = -1.0_wp                                  !< namelist parameter
1454    REAL(wp) ::  dt_averaging_input = 0.0_wp                   !< namelist parameter
1455    REAL(wp) ::  dt_averaging_input_pr = 9999999.9_wp          !< namelist parameter
1456    REAL(wp) ::  dt_coupling = 9999999.9_wp                    !< namelist parameter
1457    REAL(wp) ::  dt_data_output = 9999999.9_wp                 !< namelist parameter
1458    REAL(wp) ::  dt_data_output_av = 9999999.9_wp              !< namelist parameter
1459    REAL(wp) ::  dt_disturb = 9999999.9_wp                     !< namelist parameter
1460    REAL(wp) ::  dt_dopr = 9999999.9_wp                        !< namelist parameter
1461    REAL(wp) ::  dt_dopr_listing = 9999999.9_wp                !< namelist parameter
1462    REAL(wp) ::  dt_dopts = 9999999.9_wp                       !< namelist parameter
1463    REAL(wp) ::  dt_dots = 9999999.9_wp                        !< namelist parameter
1464    REAL(wp) ::  dt_do2d_xy = 9999999.9_wp                     !< namelist parameter
1465    REAL(wp) ::  dt_do2d_xz = 9999999.9_wp                     !< namelist parameter
1466    REAL(wp) ::  dt_do2d_yz = 9999999.9_wp                     !< namelist parameter
1467    REAL(wp) ::  dt_do3d = 9999999.9_wp                        !< namelist parameter
1468    REAL(wp) ::  dt_max = 20.0_wp                              !< namelist parameter
1469    REAL(wp) ::  dt_restart = 9999999.9_wp                     !< namelist parameter
1470    REAL(wp) ::  dt_run_control = 60.0_wp                      !< namelist parameter
1471    REAL(wp) ::  dt_spinup = 60.0_wp                           !< namelist parameter
1472    REAL(wp) ::  dt_write_agent_data = 9999999.9_wp            !< namelist parameter
1473    REAL(wp) ::  dt_3d = 0.01_wp                               !< time step
1474    REAL(wp) ::  dz_max = 999.0_wp                             !< namelist parameter
1475    REAL(wp) ::  dz_stretch_factor = 1.08_wp                   !< namelist parameter
1476    REAL(wp) ::  dz_stretch_level = -9999999.9_wp              !< namelist parameter
1477    REAL(wp) ::  e_init = 0.0_wp                               !< namelist parameter
1478    REAL(wp) ::  e_min = 0.0_wp                                !< namelist parameter
1479    REAL(wp) ::  end_time = 0.0_wp                             !< namelist parameter
1480    REAL(wp) ::  f = 0.0_wp                                    !< Coriolis parameter
1481    REAL(wp) ::  fs = 0.0_wp                                   !< Coriolis parameter
1482    REAL(wp) ::  inflow_damping_height = 9999999.9_wp          !< namelist parameter
1483    REAL(wp) ::  inflow_damping_width = 9999999.9_wp           !< namelist parameter
1484    REAL(wp) ::  km_constant = -1.0_wp                         !< namelist parameter
1485    REAL(wp) ::  latitude = 55.0_wp                            !< namelist parameter
1486    REAL(wp) ::  longitude = 0.0_wp                            !< namelist parameter
1487    REAL(wp) ::  mask_scale_x = 1.0_wp                         !< namelist parameter
1488    REAL(wp) ::  mask_scale_y = 1.0_wp                         !< namelist parameter
1489    REAL(wp) ::  mask_scale_z = 1.0_wp                         !< namelist parameter
1490    REAL(wp) ::  maximum_cpu_time_allowed = 0.0_wp             !< given wall time for run
1491    REAL(wp) ::  molecular_viscosity = 1.461E-5_wp             !< molecular viscosity (used in lsm and lpm)
1492    REAL(wp) ::  multi_agent_system_end   = 9999999.9_wp       !< namelist parameter (see documentation)
1493    REAL(wp) ::  multi_agent_system_start = 0.0_wp             !< namelist parameter (see documentation)
1494    REAL(wp) ::  old_dt = 1.0E-10_wp                           !< length of previous timestep
1495    REAL(wp) ::  omega = 7.29212E-5_wp                         !< namelist parameter
1496    REAL(wp) ::  omega_sor = 1.8_wp                            !< namelist parameter
1497    REAL(wp) ::  outflow_source_plane = -9999999.9_wp          !< namelist parameter
1498    REAL(wp) ::  particle_maximum_age = 9999999.9_wp           !< namelist parameter
1499    REAL(wp) ::  prandtl_number = 1.0_wp                       !< namelist parameter
1500    REAL(wp) ::  pt_damping_factor = 0.0_wp                    !< namelist parameter
1501    REAL(wp) ::  pt_damping_width = 0.0_wp                     !< namelist parameter
1502    REAL(wp) ::  pt_reference = 9999999.9_wp                   !< namelist parameter
1503    REAL(wp) ::  pt_slope_offset = 0.0_wp                      !< temperature difference between left and right
1504                                                               !< boundary of total domain
1505    REAL(wp) ::  pt_surface = 300.0_wp                         !< namelist parameter
1506    REAL(wp) ::  pt_surface_initial_change = 0.0_wp            !< namelist parameter
1507    REAL(wp) ::  q_surface = 0.0_wp                            !< namelist parameter
1508    REAL(wp) ::  q_surface_initial_change = 0.0_wp             !< namelist parameter
1509    REAL(wp) ::  rayleigh_damping_factor = -1.0_wp             !< namelist parameter
1510    REAL(wp) ::  rayleigh_damping_height = -1.0_wp             !< namelist parameter
1511    REAL(wp) ::  recycling_width = 9999999.9_wp                !< namelist parameter
1512    REAL(wp) ::  residual_limit = 1.0E-4_wp                    !< namelist parameter
1513    REAL(wp) ::  restart_time = 9999999.9_wp                   !< namelist parameter
1514    REAL(wp) ::  rho_reference                                 !< reference state of density
1515    REAL(wp) ::  rho_surface                                   !< surface value of density
1516    REAL(wp) ::  roughness_length = 0.1_wp                     !< namelist parameter
1517    REAL(wp) ::  simulated_time = 0.0_wp                       !< elapsed simulated time
1518    REAL(wp) ::  simulated_time_at_begin                       !< elapsed simulated time of previous run (job chain)
1519    REAL(wp) ::  sin_alpha_surface                             !< sine of alpha_surface (sloped surface)
1520    REAL(wp) ::  skip_time_data_output = 0.0_wp                !< namelist parameter
1521    REAL(wp) ::  skip_time_data_output_av = 9999999.9_wp       !< namelist parameter
1522    REAL(wp) ::  skip_time_dopr = 9999999.9_wp                 !< namelist parameter
1523    REAL(wp) ::  skip_time_do2d_xy = 9999999.9_wp              !< namelist parameter
1524    REAL(wp) ::  skip_time_do2d_xz = 9999999.9_wp              !< namelist parameter
1525    REAL(wp) ::  skip_time_do2d_yz = 9999999.9_wp              !< namelist parameter
1526    REAL(wp) ::  skip_time_do3d = 9999999.9_wp                 !< namelist parameter
1527    REAL(wp) ::  spinup_pt_amplitude = 9999999.9_wp            !< namelist parameter
1528    REAL(wp) ::  spinup_pt_mean = 9999999.9_wp                 !< namelist parameter
1529    REAL(wp) ::  spinup_time = 0.0_wp                          !< namelist parameter
1530    REAL(wp) ::  surface_heatflux = 9999999.9_wp               !< namelist parameter
1531    REAL(wp) ::  surface_pressure = 1013.25_wp                 !< namelist parameter
1532    REAL(wp) ::  surface_scalarflux = 9999999.9_wp             !< namelist parameter
1533    REAL(wp) ::  surface_waterflux = 9999999.9_wp              !< namelist parameter
1534    REAL(wp) ::  s_surface = 0.0_wp                            !< namelist parameter
1535    REAL(wp) ::  s_surface_initial_change = 0.0_wp             !< namelist parameter
1536    REAL(wp) ::  termination_time_needed = 35.0_wp             !< namelist parameter
1537    REAL(wp) ::  time_coupling = 0.0_wp                        !< time since last coupling (surface_coupler)
1538    REAL(wp) ::  time_disturb = 0.0_wp                         !< time since last flow disturbance
1539    REAL(wp) ::  time_dopr = 0.0_wp                            !< time since last profile output
1540    REAL(wp) ::  time_dopr_av = 0.0_wp                         !< time since last averaged profile output
1541    REAL(wp) ::  time_dopr_listing = 0.0_wp                    !< time since last profile output (ASCII) on file
1542    REAL(wp) ::  time_dopts = 0.0_wp                           !< time since last particle timeseries output
1543    REAL(wp) ::  time_dosp = 0.0_wp                            !< time since last spectra output
1544    REAL(wp) ::  time_dosp_av = 0.0_wp                         !< time since last averaged spectra output
1545    REAL(wp) ::  time_dots = 0.0_wp                            !< time since last timeseries output
1546    REAL(wp) ::  time_do2d_xy = 0.0_wp                         !< time since last xy cross-section output
1547    REAL(wp) ::  time_do2d_xz = 0.0_wp                         !< time since last xz cross-section output
1548    REAL(wp) ::  time_do2d_yz = 0.0_wp                         !< time since last yz cross-section output
1549    REAL(wp) ::  time_do3d = 0.0_wp                            !< time since last 3d output
1550    REAL(wp) ::  time_do_av = 0.0_wp                           !< time since last averaged-data output
1551    REAL(wp) ::  time_do_sla = 0.0_wp                          !< time since last
1552    REAL(wp) ::  time_restart = 9999999.9_wp                   !< time at which run shall be terminated and restarted
1553    REAL(wp) ::  time_run_control = 0.0_wp                     !< time since last RUN_CONTROL output
1554    REAL(wp) ::  time_since_reference_point = 0.0_wp           !< time after atmosphere-ocean coupling has been activated, or time after spinup phase of LSM has been finished
1555    REAL(wp) ::  top_heatflux = 9999999.9_wp                   !< namelist parameter
1556    REAL(wp) ::  top_momentumflux_u = 9999999.9_wp             !< namelist parameter
1557    REAL(wp) ::  top_momentumflux_v = 9999999.9_wp             !< namelist parameter
1558    REAL(wp) ::  top_salinityflux = 9999999.9_wp               !< namelist parameter
1559    REAL(wp) ::  top_scalarflux = 9999999.9_wp                 !< namelist parameter
1560    REAL(wp) ::  tunnel_height = 9999999.9_wp                  !< namelist parameter
1561    REAL(wp) ::  tunnel_length = 9999999.9_wp                  !< namelist parameter
1562    REAL(wp) ::  tunnel_width_x = 9999999.9_wp                 !< namelist parameter
1563    REAL(wp) ::  tunnel_width_y = 9999999.9_wp                 !< namelist parameter
1564    REAL(wp) ::  tunnel_wall_depth = 9999999.9_wp              !< namelist parameter
1565    REAL(wp) ::  ug_surface = 0.0_wp                           !< namelist parameter
1566    REAL(wp) ::  u_bulk = 0.0_wp                               !< namelist parameter
1567    REAL(wp) ::  u_gtrans = 0.0_wp                             !< transformed wind component (galilei transformation)
1568    REAL(wp) ::  vg_surface = 0.0_wp                           !< namelist parameter
1569    REAL(wp) ::  vpt_reference = 9999999.9_wp                  !< reference state of virtual potential temperature
1570    REAL(wp) ::  v_bulk = 0.0_wp                               !< namelist parameter
1571    REAL(wp) ::  v_gtrans = 0.0_wp                             !< transformed wind component (galilei transformation)
1572    REAL(wp) ::  wall_adjustment_factor = 1.8_wp               !< adjustment factor for mixing length l
1573    REAL(wp) ::  zeta_max = 20.0_wp                            !< namelist parameter
1574    REAL(wp) ::  zeta_min = -20.0_wp                           !< namelist parameter
1575    REAL(wp) ::  z0h_factor = 1.0_wp                           !< namelist parameter
1576
1577    REAL(wp) ::  do2d_xy_last_time(0:1) = -1.0_wp                  !< time of previous xy output
1578    REAL(wp) ::  do2d_xz_last_time(0:1) = -1.0_wp                  !< time of previous xz output
1579    REAL(wp) ::  do2d_yz_last_time(0:1) = -1.0_wp                  !< time of previous yz output
1580    REAL(wp) ::  dpdxy(1:2) = 0.0_wp                               !< namelist parameter
1581    REAL(wp) ::  dt_domask(max_masks) = 9999999.9_wp               !< namelist parameter
1582    REAL(wp) ::  dz(10) = -1.0_wp                                  !< namelist parameter
1583    REAL(wp) ::  dz_stretch_level_start(9) = -9999999.9_wp         !< namelist parameter
1584    REAL(wp) ::  dz_stretch_level_end(9) = 9999999.9_wp            !< namelist parameter
1585    REAL(wp) ::  dz_stretch_factor_array(9) = 1.08_wp              !< namelist parameter
1586    REAL(wp) ::  mask_scale(3)                                     !< collective array for mask_scale_x/y/z
1587    REAL(wp) ::  pt_vertical_gradient(10) = 0.0_wp                 !< namelist parameter
1588    REAL(wp) ::  pt_vertical_gradient_level(10) = -999999.9_wp   !< namelist parameter
1589    REAL(wp) ::  q_vertical_gradient(10) = 0.0_wp                  !< namelist parameter
1590    REAL(wp) ::  q_vertical_gradient_level(10) = -999999.9_wp    !< namelist parameter
1591    REAL(wp) ::  s_vertical_gradient(10) = 0.0_wp                  !< namelist parameter
1592    REAL(wp) ::  s_vertical_gradient_level(10) = -999999.9_wp    !< namelist parameter
1593    REAL(wp) ::  skip_time_domask(max_masks) = 9999999.9_wp        !< namelist parameter
1594    REAL(wp) ::  threshold(20) = 0.0_wp                            !< namelist parameter
1595    REAL(wp) ::  time_domask(max_masks) = 0.0_wp                   !< namelist parameter
1596    REAL(wp) ::  tsc(10) = (/ 1.0_wp, 1.0_wp, 0.0_wp, 0.0_wp, &    !< array used for controlling time-integration at different substeps
1597                 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp /)
1598    REAL(wp) ::  u_profile(200) = 9999999.9_wp                     !< namelist parameter
1599    REAL(wp) ::  uv_heights(200) = 9999999.9_wp                    !< namelist parameter
1600    REAL(wp) ::  v_profile(200) = 9999999.9_wp                     !< namelist parameter
1601    REAL(wp) ::  ug_vertical_gradient(10) = 0.0_wp                 !< namelist parameter
1602    REAL(wp) ::  ug_vertical_gradient_level(10) = -9999999.9_wp    !< namelist parameter
1603    REAL(wp) ::  vg_vertical_gradient(10) = 0.0_wp                 !< namelist parameter
1604    REAL(wp) ::  vg_vertical_gradient_level(10) = -9999999.9_wp    !< namelist parameter
1605    REAL(wp) ::  volume_flow(1:3) = 0.0_wp                         !< volume flow through 1:yz-plane, 2: xz-plane, 3: xy-plane (nest childs only)
1606    REAL(wp) ::  volume_flow_area(1:3) = 0.0_wp                    !< area of the respective volume flow planes
1607    REAL(wp) ::  volume_flow_initial(1:3) = 0.0_wp                 !< initial volume flow (t=0) through the respective volume flow planes
1608    REAL(wp) ::  wall_heatflux(0:5) = 0.0_wp                       !< namelist parameter
1609    REAL(wp) ::  wall_humidityflux(0:5) = 0.0_wp                   !< namelist parameter
1610    REAL(wp) ::  wall_salinityflux(0:5) = 0.0_wp                   !< namelist parameter
1611    REAL(wp) ::  wall_scalarflux(0:5) = 0.0_wp                     !< namelist parameter
1612    REAL(wp) ::  subs_vertical_gradient(10) = 0.0_wp               !< namelist parameter
1613    REAL(wp) ::  subs_vertical_gradient_level(10) = -9999999.9_wp  !< namelist parameter
1614
1615    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dp_smooth_factor  !< smoothing factor for external pressure gradient forcing
1616
1617    REAL(wp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_x = -1.0_wp  !< namelist parameter
1618    REAL(wp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_y = -1.0_wp  !< namelist parameter
1619    REAL(wp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_z = -1.0_wp  !< namelist parameter
1620   
1621    REAL(wp), DIMENSION(max_masks,3) ::  mask_x_loop = -1.0_wp  !< namelist parameter
1622    REAL(wp), DIMENSION(max_masks,3) ::  mask_y_loop = -1.0_wp  !< namelist parameter
1623    REAL(wp), DIMENSION(max_masks,3) ::  mask_z_loop = -1.0_wp  !< namelist parameter
1624   
1625!
1626!--    internal mask arrays ("mask,dimension,selection")
1627       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  mask       !< collective array for mask_x/y/z
1628       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  mask_loop  !< collective array for mask_x/y/z_loop
1629
1630    SAVE
1631
1632 END MODULE control_parameters
1633
1634
1635!------------------------------------------------------------------------------!
1636! Description:
1637! ------------
1638!> Definition of grid spacings.
1639!------------------------------------------------------------------------------!
1640 MODULE grid_variables
1641
1642    USE kinds
1643
1644    REAL(wp) ::  ddx          !< 1/dx
1645    REAL(wp) ::  ddx2         !< 1/dx2
1646    REAL(wp) ::  dx = 1.0_wp  !< horizontal grid size (along x-direction)
1647    REAL(wp) ::  dx2          !< dx*dx
1648    REAL(wp) ::  ddy          !< 1/dy
1649    REAL(wp) ::  ddy2         !< 1/dy2
1650    REAL(wp) ::  dy = 1.0_wp  !< horizontal grid size (along y-direction)
1651    REAL(wp) ::  dy2          !< dy*dy
1652
1653    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddx2_mg  !< 1/dx_l**2 (dx_l: grid spacing along x on different multigrid level)
1654    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddy2_mg  !< 1/dy_l**2 (dy_l: grid spacing along y on different multigrid level)
1655
1656    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zu_s_inner  !< height of topography top on scalar grid
1657    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_w_inner  !< height of topography top on w grid
1658                                             
1659    SAVE
1660
1661 END MODULE grid_variables
1662
1663
1664!------------------------------------------------------------------------------!
1665! Description:
1666! ------------
1667!> Definition of array bounds, number of gridpoints, and wall flag arrays.
1668!------------------------------------------------------------------------------!
1669 MODULE indices
1670
1671    USE kinds
1672
1673    INTEGER(iwp) ::  nbgp = 3       !< number of boundary ghost points
1674    INTEGER(iwp) ::  ngp_sums       !< number of vertical profile grid points time number of output profiles - used for allreduce statements in MPI calls
1675    INTEGER(iwp) ::  ngp_sums_ls    !< number of vertical profile grid points time number of large-scale forcing profiles - used for allreduce statements in MPI calls
1676    INTEGER(iwp) ::  nnx            !< number of subdomain grid points in x-direction
1677    INTEGER(iwp) ::  nx = 0         !< nx+1 = total number of grid points in x-direction
1678    INTEGER(iwp) ::  nx_a           !< in coupled atmosphere-ocean runs: total number of grid points along x (atmosphere)
1679    INTEGER(iwp) ::  nx_o           !< in coupled atmosphere-ocean runs: total number of grid points along x (ocean)
1680    INTEGER(iwp) ::  nxl            !< left-most grid index of subdomain (excluding ghost points)
1681    INTEGER(iwp) ::  nxlg           !< left-most grid index of subdomain (including ghost points)
1682    INTEGER(iwp) ::  nxlu           !< =nxl+1 (at left domain boundary with inflow from left), else =nxl (used for u-velocity component)
1683    INTEGER(iwp) ::  nxr            !< right-most grid index of subdomain (excluding ghost points)
1684    INTEGER(iwp) ::  nxrg           !< right-most grid index of subdomain (including ghost points)
1685    INTEGER(iwp) ::  nx_on_file     !< nx of previous run in job chain
1686    INTEGER(iwp) ::  nny            !< number of subdomain grid points in y-direction
1687    INTEGER(iwp) ::  ny = 0         !< ny+1 = total number of grid points in y-direction
1688    INTEGER(iwp) ::  ny_a           !< in coupled atmosphere-ocean runs: total number of grid points along y (atmosphere)
1689    INTEGER(iwp) ::  ny_o           !< in coupled atmosphere-ocean runs: total number of grid points along y (ocean)
1690    INTEGER(iwp) ::  nyn            !< north-most grid index of subdomain (excluding ghost points)
1691    INTEGER(iwp) ::  nyng           !< north-most grid index of subdomain (including ghost points)
1692    INTEGER(iwp) ::  nys            !< south-most grid index of subdomain (excluding ghost points)
1693    INTEGER(iwp) ::  nysg           !< south-most grid index of subdomain (including ghost points)
1694    INTEGER(iwp) ::  nysv           !< =nys+1 (at south domain boundary with inflow from south), else =nys (used for v-velocity component)
1695    INTEGER(iwp) ::  ny_on_file     !< ny of previous run in job chain
1696    INTEGER(iwp) ::  nnz            !< number of subdomain grid points in z-direction
1697    INTEGER(iwp) ::  nz = 0         !< total number of grid points in z-direction
1698    INTEGER(iwp) ::  nzb            !< bottom grid index of computational domain
1699    INTEGER(iwp) ::  nzb_diff       !< will be removed
1700    INTEGER(iwp) ::  nzb_max        !< vertical index of topography top
1701    INTEGER(iwp) ::  nzt            !< nzt+1 = top grid index of computational domain
1702    INTEGER(iwp) ::  topo_min_level !< minimum topography-top index (usually equal to nzb)
1703
1704    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d        !< number of grid points of the total domain
1705    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner  !< ! need to have 64 bit for grids > 2E9
1706                   
1707    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_2dh  !< number of grid points of a horizontal cross section through the total domain
1708    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxl_mg   !< left-most grid index of subdomain on different multigrid level
1709    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxr_mg   !< right-most grid index of subdomain on different multigrid level
1710    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nyn_mg   !< north-most grid index of subdomain on different multigrid level
1711    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nys_mg   !< south-most grid index of subdomain on different multigrid level
1712    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nzt_mg   !< top-most grid index of subdomain on different multigrid level
1713
1714
1715    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_outer     !< number of horizontal grid points which are non-topography and non-surface-bounded
1716    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_s_inner   !< number of horizontal grid points which are non-topography
1717    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mg_loc_ind        !< internal array to store index bounds of all PEs of that multigrid level where data is collected to PE0
1718    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_diff_s_inner  !< will be removed
1719    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_diff_s_outer  !< will be removed
1720    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_inner         !< will be removed
1721    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_outer         !< will be removed
1722    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_s_inner       !< will be removed
1723    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_s_outer       !< will be removed
1724    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_u_inner       !< will be removed
1725    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_u_outer       !< will be removed
1726    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_v_inner       !< will be removed
1727    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_v_outer       !< will be removed
1728    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_w_inner       !< will be removed
1729    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_w_outer       !< will be removed
1730
1731    INTEGER(iwp), DIMENSION(:,:,:), POINTER ::  flags  !< pointer to wall_flags_1-10
1732
1733    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_1   !< topograpyh masking flag on multigrid level 1
1734    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_2   !< topograpyh masking flag on multigrid level 2
1735    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_3   !< topograpyh masking flag on multigrid level 3
1736    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_4   !< topograpyh masking flag on multigrid level 4
1737    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_5   !< topograpyh masking flag on multigrid level 5
1738    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_6   !< topograpyh masking flag on multigrid level 6
1739    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_7   !< topograpyh masking flag on multigrid level 7
1740    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_8   !< topograpyh masking flag on multigrid level 8
1741    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_9   !< topograpyh masking flag on multigrid level 9
1742    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_10  !< topograpyh masking flag on multigrid level 10
1743
1744    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_1            !< flags used to degrade order of advection scheme
1745    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_2            !< flags used to degrade order of advection scheme
1746    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  wall_flags_0            !< flags to mask topography and surface-bounded grid points
1747
1748    SAVE
1749
1750 END MODULE indices
1751
1752
1753!------------------------------------------------------------------------------!
1754! Description:
1755! ------------
1756!> Interfaces for special subroutines which use optional parameters.
1757!------------------------------------------------------------------------------!
1758 MODULE interfaces
1759
1760    INTERFACE
1761
1762!------------------------------------------------------------------------------!
1763! Description:
1764! ------------
1765!> @todo Missing subroutine description.
1766!------------------------------------------------------------------------------!
1767       SUBROUTINE global_min_max ( i1, i2, j1, j2, k1, k2, array, mode, offset, &
1768                                   result, result_ijk, result1, result1_ijk )
1769
1770          USE kinds
1771
1772          CHARACTER (LEN=*), INTENT(IN) ::  mode                      !< mode of global min/max function: can be 'min', 'max', 'minmax', 'abs', or 'absoff'
1773          INTEGER(iwp), INTENT(IN)      ::  i1                        !< internal index of min/max function
1774          INTEGER(iwp), INTENT(IN)      ::  i2                        !< internal index of min/max function
1775          INTEGER(iwp), INTENT(IN)      ::  j1                        !< internal index of min/max function
1776          INTEGER(iwp), INTENT(IN)      ::  j2                        !< internal index of min/max function
1777          INTEGER(iwp), INTENT(IN)      ::  k1                        !< internal index of min/max function
1778          INTEGER(iwp), INTENT(IN)      ::  k2                        !< internal index of min/max function
1779          INTEGER(iwp)                  ::  result_ijk(3)             !< grid index result of min/max function
1780          INTEGER(iwp), OPTIONAL        ::  result1_ijk(3)            !< optional grid index result of min/max function
1781          REAL(wp)                      ::  offset                    !< min/max function calculates absolute value with respect to an offset
1782          REAL(wp)                      ::  result                    !< result of min/max function
1783          REAL(wp), OPTIONAL            ::  result1                   !< optional result of min/max function
1784          REAL(wp), INTENT(IN)          ::  array(i1:i2,j1:j2,k1:k2)  !< input array of min/max function
1785
1786       END SUBROUTINE global_min_max
1787
1788    END INTERFACE
1789
1790    SAVE
1791
1792 END MODULE interfaces
1793
1794
1795!------------------------------------------------------------------------------!
1796! Description:
1797! ------------
1798!> Interfaces for subroutines with pointer arguments called in
1799!> prognostic_equations.
1800!------------------------------------------------------------------------------!
1801 MODULE pointer_interfaces
1802
1803    INTERFACE
1804
1805!------------------------------------------------------------------------------!
1806! Description:
1807! ------------
1808!> @todo Missing subroutine description.
1809!------------------------------------------------------------------------------!
1810       SUBROUTINE advec_s_bc( sk, sk_char )
1811
1812          USE kinds
1813
1814          CHARACTER (LEN=*), INTENT(IN) ::  sk_char  !< string for treated scalar in Bott-Chlond scheme
1815
1816          REAL(wp), DIMENSION(:,:,:), POINTER ::  sk  !< treated scalar array in Bott-Chlond scheme
1817
1818       END SUBROUTINE advec_s_bc
1819
1820    END INTERFACE
1821
1822    SAVE
1823
1824 END MODULE pointer_interfaces
1825
1826
1827!------------------------------------------------------------------------------!
1828! Description:
1829! ------------
1830!> Definition of variables which define processor topology and the exchange of
1831!> ghost point layers. This module must be placed in all routines containing
1832!> MPI-calls.
1833!------------------------------------------------------------------------------!
1834 MODULE pegrid
1835
1836    USE kinds
1837
1838#if defined( __parallel )
1839#if defined( __mpifh )
1840    INCLUDE "mpif.h"
1841#else
1842    USE MPI
1843#endif
1844#endif
1845    CHARACTER(LEN=2) ::  send_receive = 'al'     !<
1846    CHARACTER(LEN=7) ::  myid_char = ''          !< character string containing processor id number
1847   
1848    INTEGER(iwp) ::  comm1dx                     !< communicator for domain decomposition along x
1849    INTEGER(iwp) ::  comm1dy                     !< communicator for domain decomposition along y
1850    INTEGER(iwp) ::  comm2d                      !< standard 2d (xy) communicator used in PALM for the process group the PE belongs to
1851    INTEGER(iwp) ::  comm_inter                  !< intercommunicator that connects atmosphere/ocean process groups
1852    INTEGER(iwp) ::  comm_palm                   !< internal communicator used during the MPI setup at the beginning of a run
1853    INTEGER(iwp) ::  id_inflow = 0               !< myidx of procs at inflow (turbulent inflow method)
1854    INTEGER(iwp) ::  id_outflow = 0              !< myidx of procs at outflow (turbulent outflow method)
1855    INTEGER(iwp) ::  id_outflow_source = 0       !< myidx of procs including ouflow source plane (turbulent outflow method)
1856    INTEGER(iwp) ::  id_recycling = 0            !< myidx of procs containing the recycling plane (turbulence recycling method)
1857    INTEGER(iwp) ::  ierr                        !< standard error parameter in MPI calls
1858    INTEGER(iwp) ::  myid = 0                    !< id number of processor element
1859    INTEGER(iwp) ::  myidx = 0                   !< id number of processor elements with same position along x-direction
1860    INTEGER(iwp) ::  myidy = 0                   !< id number of processor elements with same position along y-direction
1861    INTEGER(iwp) ::  ndim = 2                    !< dimension of the virtual PE grid
1862    INTEGER(iwp) ::  ngp_a                       !< used in atmosphere/ocean coupling: total number of horizontal grid points (atmosphere)
1863    INTEGER(iwp) ::  ngp_o                       !< used in atmosphere/ocean coupling: total number of horizontal grid points (ocean)
1864    INTEGER(iwp) ::  ngp_xy                      !< used in atmosphere/ocean coupling: number of grid points of the subdomain
1865    INTEGER(iwp) ::  ngp_y                       !< number of subdomain grid points along y including ghost points
1866    INTEGER(iwp) ::  npex = -1                   !< number of processor elements in x-direction
1867    INTEGER(iwp) ::  npey = -1                   !< number of processor elements in y-direction
1868    INTEGER(iwp) ::  numprocs = 1                !< total number of appointed processor elements
1869    INTEGER(iwp) ::  numprocs_previous_run = -1  !< total number of appointed processor elements in previous run (job chain)
1870    INTEGER(iwp) ::  pleft                       !< MPI-address of the processor left of the current one
1871    INTEGER(iwp) ::  pnorth                      !< MPI-address of the processor north of the current one
1872    INTEGER(iwp) ::  pright                      !< MPI-address of the processor right of the current one
1873    INTEGER(iwp) ::  psouth                      !< MPI-address of the processor south of the current one
1874    INTEGER(iwp) ::  req_count = 0               !< MPI return variable - checks if Send-Receive operation is already finished
1875    INTEGER(iwp) ::  sendrecvcount_xy            !< number of subdomain gridpoints to be exchanged in direct transpositions (y --> x, or x --> y) or second (2d) transposition x --> y
1876    INTEGER(iwp) ::  sendrecvcount_yz            !< number of subdomain gridpoints to be exchanged in third (2d) transposition y --> z
1877    INTEGER(iwp) ::  sendrecvcount_zx            !< number of subdomain gridpoints to be exchanged in first (2d) transposition z --> x
1878    INTEGER(iwp) ::  sendrecvcount_zyd           !< number of subdomain gridpoints to be exchanged in direct transpositions z --> y (used for calculating spectra)
1879    INTEGER(iwp) ::  target_id                   !< in atmosphere/ocean coupling: id of the ocean/atmosphere counterpart PE with whom the atmosphere/ocean PE exchanges data
1880    INTEGER(iwp) ::  tasks_per_node = -9999      !< MPI tasks per compute node
1881    INTEGER(iwp) ::  threads_per_task = 1        !< number of OPENMP threads per MPI task
1882    INTEGER(iwp) ::  type_x                      !< derived MPI datatype for 2-D ghost-point exchange - north / south
1883    INTEGER(iwp) ::  type_xy                     !< derived MPI datatype for 2-D ghost-point exchange - north / south
1884    INTEGER(iwp) ::  type_y                      !< derived MPI datatype for 2-D exchange in atmosphere-ocean coupler
1885
1886    INTEGER(iwp) ::  pdims(2) = 1  !< number of processors along x-y dimension
1887    INTEGER(iwp) ::  req(100)      !< MPI return variable indicating if send-receive operation is finished
1888
1889    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds               !< horizontal index bounds
1890    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds_previous_run  !< horizontal index bounds of previous run
1891
1892    LOGICAL ::  collective_wait = .FALSE.          !< switch to set an explicit MPI barrier in front of all collective MPI calls
1893
1894#if defined( __parallel )
1895    INTEGER(iwp) ::  ibuf(12)                 !< internal buffer for calculating MPI settings
1896    INTEGER(iwp) ::  pcoord(2)                !< PE coordinates along x and y
1897    INTEGER(iwp) ::  status(MPI_STATUS_SIZE)  !< MPI status variable used in various MPI calls
1898   
1899    INTEGER(iwp), DIMENSION(MPI_STATUS_SIZE,100) ::  wait_stat  !< MPI status variable used in various MPI calls
1900   
1901    INTEGER(iwp) ::  type_x_byte !< derived MPI datatype for 2-D 8-bit integer ghost-point exchange - north / south
1902    INTEGER(iwp) ::  type_y_byte !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
1903   
1904    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz      !< number of ghost points in xz-plane on different multigrid level
1905    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz_int  !< number of ghost points in xz-plane on different multigrid level
1906    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz      !< number of ghost points in yz-plane on different multigrid level
1907    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz_int  !< number of ghost points in yz-plane on different multigrid level
1908    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_x_int  !< derived MPI datatype for 2-D integer ghost-point exchange - north / south
1909    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz     !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
1910    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz_int !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
1911    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_y_int  !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
1912    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
1913    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz_int !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
1914
1915    LOGICAL ::  left_border_pe  = .FALSE.  !< = .TRUE. if PE is on left border of computational domain
1916    LOGICAL ::  north_border_pe = .FALSE.  !< = .TRUE. if PE is on north border of computational domain
1917    LOGICAL ::  reorder = .TRUE.           !< switch to allow MPI the reorder of ranking (e.g. row-major or column-major)
1918    LOGICAL ::  right_border_pe = .FALSE.  !< = .TRUE. if PE is on right border of computational domain
1919    LOGICAL ::  south_border_pe = .FALSE.  !< = .TRUE. if PE is on south border of computational domain
1920
1921    LOGICAL, DIMENSION(2) ::  cyclic = (/ .TRUE. , .TRUE. /)  !< boundary conditions of the virtual PE grid
1922    LOGICAL, DIMENSION(2) ::  remain_dims                     !< internal array used to determine sub-topologies for transpositions
1923#endif
1924
1925    SAVE
1926
1927 END MODULE pegrid
1928
1929
1930!------------------------------------------------------------------------------!
1931! Description:
1932! ------------
1933!> Definition of variables which control PROFIL-output.
1934!------------------------------------------------------------------------------!
1935 MODULE profil_parameter
1936
1937    USE kinds
1938
1939    INTEGER(iwp), PARAMETER ::  crmax = 100  !< maximum number of coordinate systems for profile output
1940
1941    CHARACTER (LEN=27), DIMENSION(20) ::  cross_ts_profiles = &  !< time series to be plotted into one coordinate system, respectively
1942                           (/ ' E E*                      ', &
1943                              ' dt                        ', &
1944                              ' u* w*                     ', &
1945                              ' th*                       ', &
1946                              ' umax vmax wmax            ', &
1947                              ' div_old div_new           ', &
1948                              ' zi_wtheta zi_theta        ', &
1949                              ' w"theta"0 w"theta" wtheta ', &
1950                              ' theta(0) theta(zp)        ', &
1951                              ' splux spluy spluz         ', &
1952                              ' L                         ', &
1953                            ( '                           ', i9 = 1, 9 ) /)
1954
1955    CHARACTER (LEN=100), DIMENSION(crmax) ::  cross_profiles = &  !< quantities to be plotted into one coordinate system, respectively
1956                          (/ ' u v                                          ', &
1957                             ' pt                                           ', &
1958                             ' w"theta" w*theta* w*theta*BC wtheta wthetaBC ', &
1959                             ' w"u" w*u* wu w"v" w*v* wv                    ', &
1960                             ' km kh                                        ', &
1961                             ' l                                            ', &
1962             ( '                                              ', i9 = 1, 94 ) /)
1963
1964    INTEGER(iwp) ::  profile_columns = 2  !< number of coordinate systems on a profile plot per column
1965    INTEGER(iwp) ::  profile_rows = 3     !< number of coordinate systems on a profile plot per row
1966
1967    INTEGER(iwp) ::  dopr_index(300) = 0                !< index number of respective profile quantity
1968    INTEGER(iwp) ::  dopr_initial_index(300) = 0        !< index number of initial profiles to be output
1969               
1970    SAVE
1971
1972 END MODULE profil_parameter
1973
1974!------------------------------------------------------------------------------!
1975! Description:
1976! ------------
1977!> Definition of statistical quantities, e.g. global sums.
1978!------------------------------------------------------------------------------!
1979 MODULE statistics
1980
1981    USE kinds
1982
1983    CHARACTER (LEN=40) ::  region(0:9) =  &  !< label for statistic region
1984                           'total domain                            '
1985 
1986    INTEGER(iwp) ::  pr_palm = 200          !< maximum number of output profiles
1987    INTEGER(iwp) ::  statistic_regions = 0  !< identifier for statistic regions
1988
1989    INTEGER(iwp) ::  u_max_ijk(3) = -1  !< index values (i,j,k) of location where u_max occurs
1990    INTEGER(iwp) ::  v_max_ijk(3) = -1  !< index values (i,j,k) of location where v_max occurs
1991    INTEGER(iwp) ::  w_max_ijk(3) = -1  !< index values (i,j,k) of location where w_max occurs
1992   
1993    LOGICAL ::  flow_statistics_called = .FALSE.  !< flag that tells other routines if flow statistics was executed
1994                                                  !< (after each timestep)
1995   
1996    REAL(wp) ::  u_max = 0.0_wp  !< maximum of absolute u-veloctiy in entire domain
1997    REAL(wp) ::  v_max = 0.0_wp  !< maximum of absolute v-veloctiy in entire domain
1998    REAL(wp) ::  w_max = 0.0_wp  !< maximum of absolute w-veloctiy in entire domain
1999
2000    REAL(wp), DIMENSION(2) ::  z_i  !< inversion height
2001   
2002    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mean_surface_level_height  !< mean surface level height for the different statistic regions
2003    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divnew_l              !< subdomain sum (_l) of divergence after pressure
2004                                                                       !< solver call (new)
2005    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divold_l              !< subdomain sum (_l) of divergence before pressure
2006                                                                       !< solver call (old)
2007    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_substep             !< weighting factor for substeps in timestepping
2008    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_pres                !< substep weighting factor for pressure solver
2009   
2010    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums             !< global sum array for the various output quantities
2011    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l  !< subdomain sum of vertical salsa flux w's' (5th-order advection scheme only)
2012    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsts_bc_l   !< subdomain sum of sensible heat flux in Bott-Chlond scheme
2013    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ts_value         !< timeseries output array for the various output quantities
2014    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsus_ws_l   !< subdomain sum of vertical momentum flux w'u' (5th-order advection scheme only)
2015    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsvs_ws_l   !< subdomain sum of vertical momentum flux w'v' (5th-order advection scheme only)
2016    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_us2_ws_l    !< subdomain sum of horizontal momentum flux u'u' (5th-order advection scheme only)
2017    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_vs2_ws_l    !< subdomain sum of horizontal momentum flux v'v' (5th-order advection scheme only)
2018    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ws2_ws_l    !< subdomain sum of vertical momentum flux w'w' (5th-order advection scheme only)
2019    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsncs_ws_l  !< subdomain sum of vertical clouddrop-number concentration flux w'nc' (5th-order advection scheme only)
2020    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnrs_ws_l  !< subdomain sum of vertical raindrop-number concentration flux w'nr' (5th-order advection scheme only)
2021    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wspts_ws_l  !< subdomain sum of vertical sensible heat flux w'pt' (5th-order advection scheme only)
2022    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqs_ws_l   !< subdomain sum of vertical latent heat flux w'q' (5th-order advection scheme only)
2023    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqcs_ws_l  !< subdomain sum of vertical cloudwater flux w'qc' (5th-order advection scheme only)
2024    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqrs_ws_l  !< subdomain sum of vertical rainwater flux w'qr' (5th-order advection scheme only)
2025    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wssas_ws_l  !< subdomain sum of vertical salinity flux w'sa' (5th-order advection scheme only)
2026    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsss_ws_l   !< subdomain sum of vertical passive scalar flux w's' (5th-order advection scheme only)
2027    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ls_l        !< subdomain sum of large scale forcing and nudging tendencies
2028                                             
2029    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  hom_sum             !< sum array for horizontal mean
2030    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rmask               !< REAL flag array (0.0 or 1.0) for statistic regions
2031    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sums_l              !< subdomain sum (_l) gathered for various quantities
2032    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sums_l_l            !< subdomain sum (_l) of mixing length from diffusivities
2033   
2034    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom  !< horizontal mean of various quantities (profiles/timeseries)
2035
2036    SAVE
2037
2038 END MODULE statistics
2039
2040
2041
2042!------------------------------------------------------------------------------!
2043! Description:
2044! ------------
2045!> Definition of indices for transposed arrays.
2046!------------------------------------------------------------------------------!
2047 MODULE transpose_indices
2048
2049    USE kinds
2050
2051    INTEGER(iwp) ::  nxl_y   !< internal index bound for transpositions
2052    INTEGER(iwp) ::  nxl_yd  !< internal index bound for transpositions
2053    INTEGER(iwp) ::  nxl_z   !< internal index bound for transpositions
2054    INTEGER(iwp) ::  nxr_y   !< internal index bound for transpositions
2055    INTEGER(iwp) ::  nxr_yd  !< internal index bound for transpositions
2056    INTEGER(iwp) ::  nxr_z   !< internal index bound for transpositions
2057    INTEGER(iwp) ::  nyn_x   !< internal index bound for transpositions
2058    INTEGER(iwp) ::  nyn_z   !< internal index bound for transpositions
2059    INTEGER(iwp) ::  nys_x   !< internal index bound for transpositions
2060    INTEGER(iwp) ::  nys_z   !< internal index bound for transpositions
2061    INTEGER(iwp) ::  nzb_x   !< internal index bound for transpositions
2062    INTEGER(iwp) ::  nzb_y   !< internal index bound for transpositions
2063    INTEGER(iwp) ::  nzb_yd  !< internal index bound for transpositions
2064    INTEGER(iwp) ::  nzt_x   !< internal index bound for transpositions
2065    INTEGER(iwp) ::  nzt_y   !< internal index bound for transpositions
2066    INTEGER(iwp) ::  nzt_yd  !< internal index bound for transpositions
2067               
2068    SAVE
2069
2070 END MODULE transpose_indices
Note: See TracBrowser for help on using the repository browser.