source: palm/trunk/SOURCE/check_parameters.f90 @ 2839

Last change on this file since 2839 was 2836, checked in by Giersch, 6 years ago

Bugfix in interpolation of lift and drag coefficients during initialization, default value of dt_dopr_listing is set to zero to allow header output

  • Property svn:keywords set to Id
  • Property svn:mergeinfo set to False
    /palm/branches/forwind/SOURCE/check_parameters.f901564-1913
    /palm/branches/palm4u/SOURCE/check_parameters.f902540-2692
File size: 176.7 KB
Line 
1!> @file check_parameters.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-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: check_parameters.f90 2836 2018-02-26 13:40:05Z schwenkel $
27! dt_dopr_listing is set to the default value zero
28!
29! 2817 2018-02-19 16:32:21Z knoop
30! Preliminary gust module interface implemented
31!
32! 2798 2018-02-09 17:16:39Z suehring
33! Consider also default-type surfaces for surface temperature output.
34!
35! 2797 2018-02-08 13:24:35Z suehring
36! Enable output of ground-heat flux also at urban surfaces.
37!
38! 2776 2018-01-31 10:44:42Z Giersch
39! Variable synthetic_turbulence_generator has been abbreviated
40!
41! 2773 2018-01-30 14:12:54Z suehring
42! Check for consistent initialization in nesting mode added.
43!
44! 2766 2018-01-22 17:17:47Z kanani
45! Removed preprocessor directive __chem
46!
47! 2765 2018-01-22 11:34:58Z maronga
48! Renamed simulation_time_since_reference to
49! time_to_be_simulated_from_reference_point
50!
51! 2746 2018-01-15 12:06:04Z suehring
52! Move flag plant canopy to modules
53!
54! 2743 2018-01-12 16:03:39Z suehring
55! In case of natural- and urban-type surfaces output surfaces fluxes in W/m2.
56!
57! 2742 2018-01-12 14:59:47Z suehring
58! Enable output of surface temperature
59!
60! 2735 2018-01-11 12:01:27Z suehring
61! output of r_a moved from land-surface to consider also urban-type surfaces
62!
63! 2718 2018-01-02 08:49:38Z maronga
64! Corrected "Former revisions" section
65!
66! 2696 2017-12-14 17:12:51Z kanani
67! Change in file header (GPL part)
68! Implementation of uv exposure model (FK)
69! + new possible value for dissipation_1d
70! Added checks for turbulence_closure_mod (TG)
71! Implementation of chemistry module (FK)
72!
73! 2689 2017-12-12 17:46:55Z Giersch
74! Bugfix in if query
75!
76! 2688 2017-12-12 17:27:04Z Giersch
77! Check if humidity is set to TRUE in the _p3d file for coupled runs
78!
79! 2669 2017-12-06 16:03:27Z raasch
80! mrun-string replaced by palmrun
81!
82! 2628 2017-11-20 12:40:38Z schwenkel
83! Enabled particle advection with grid stretching -> Removed parameter check
84!
85! 2575 2017-10-24 09:57:58Z maronga
86! Renamed phi --> latitude
87!
88! 2564 2017-10-19 15:56:56Z Giersch
89! Variable wind_turbine was added to control_parameters.
90!
91! 2550 2017-10-16 17:12:01Z boeske
92! Added checks for complex terrain simulations
93!
94! 2513 2017-10-04 09:24:39Z kanani
95! Bugfix for some dopr(_initial)_index values and units connected to
96! passive-scalar output
97!
98! 2508 2017-10-02 08:57:09Z suehring
99! Bugfix, change default value of vertical_gradient level in order to consider
100! also ocean runs
101!
102! 2422 2017-09-08 08:25:41Z raasch
103! error message in case of missing "restart" file activation string
104!
105! 2375 2017-08-29 14:10:28Z schwenkel
106! Added aerosol for bulk microphysics
107!
108! 2365 2017-08-21 14:59:59Z kanani
109! Vertical grid nesting implemented: Check coupling mode. Generate file header
110! (SadiqHuq)
111!
112! 2354 2017-08-17 10:49:36Z schwenkel
113! Bugfix correlated to lsm_check_data_output_pr.
114! If-statement for following checks is essential, otherwise units for lsm output
115! are set to 'illegal' and palm will be aborted.
116!
117! 2348 2017-08-10 10:40:10Z kanani
118! New: Check for simultaneous use of geostrophic wind and u_profile/v_profile
119!
120! 2345 2017-08-09 11:50:30Z Giersch
121! Remove error message PA0156 and the conserve_volume_flow_mode option
122! inflow_profile
123!
124! 2339 2017-08-07 13:55:26Z raasch
125! corrected timestamp in header
126!
127! 2338 2017-08-07 12:15:38Z gronemeier
128! Modularize 1D model
129!
130! 2329 2017-08-03 14:24:56Z knoop
131! Bugfix: index corrected for rho_air and rho_air_zw output
132!
133! 2320 2017-07-21 12:47:43Z suehring
134! Modularize large-scale forcing and nudging
135!
136! 2312 2017-07-14 20:26:51Z hoffmann
137! PA0349 and PA0420 removed.
138!
139! 2300 2017-06-29 13:31:14Z raasch
140! host-specific settings and checks removed
141!
142! 2292 2017-06-20 09:51:42Z schwenkel
143! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
144! includes two more prognostic equations for cloud drop concentration (nc)
145! and cloud water content (qc).
146!
147! 2274 2017-06-09 13:27:48Z Giersch
148! Changed error messages
149!
150! 2271 2017-06-09 12:34:55Z sward
151! roughness-length check altered
152! Error messages fixed
153!
154! 2270 2017-06-09 12:18:47Z maronga
155! Revised numbering (removed 2 timeseries)
156!
157! 2259 2017-06-08 09:09:11Z gronemeier
158! Implemented synthetic turbulence generator
159!
160! 2251 2017-06-06 15:10:46Z Giersch
161!
162! 2250 2017-06-06 15:07:12Z Giersch
163! Doxygen comment added
164!
165! 2248 2017-06-06 13:52:54Z sward
166! Error message fixed
167!
168! 2209 2017-04-19 09:34:46Z kanani
169! Check for plant canopy model output
170!
171! 2200 2017-04-11 11:37:51Z suehring
172! monotonic_adjustment removed
173!
174! 2178 2017-03-17 11:07:39Z hellstea
175! Index limits for perturbations are now set also in case of nested
176! boundary conditions
177!
178! 2169 2017-03-06 18:16:35Z suehring
179! Bugfix, move setting for topography grid convention to init_grid
180!
181! 2118 2017-01-17 16:38:49Z raasch
182! OpenACC related parts of code removed
183!
184! 2088 2016-12-19 16:30:25Z suehring
185! Bugfix in initial salinity profile
186!
187! 2084 2016-12-09 15:59:42Z knoop
188! Removed anelastic + multigrid error message
189!
190! 2052 2016-11-08 15:14:59Z gronemeier
191! Bugfix: remove setting of default value for recycling_width
192!
193! 2050 2016-11-08 15:00:55Z gronemeier
194! Implement turbulent outflow condition
195!
196! 2044 2016-11-02 16:44:25Z knoop
197! Added error code for anelastic approximation
198!
199! 2042 2016-11-02 13:47:31Z suehring
200! Additional checks for wall_heatflux, wall_humidityflux and wall_scalarflux.
201! Bugfix, check for constant_scalarflux.
202!
203! 2040 2016-10-26 16:58:09Z gronemeier
204! Removed check for statistic_regions > 9.
205!
206! 2037 2016-10-26 11:15:40Z knoop
207! Anelastic approximation implemented
208!
209! 2031 2016-10-21 15:11:58Z knoop
210! renamed variable rho to rho_ocean
211!
212! 2026 2016-10-18 10:27:02Z suehring
213! Bugfix, enable output of s*2
214!
215! 2024 2016-10-12 16:42:37Z kanani
216! Added missing CASE, error message and unit for ssws*,
217! increased number of possible output quantities to 500.
218!
219! 2011 2016-09-19 17:29:57Z kanani
220! Flag urban_surface is now defined in module control_parameters,
221! changed prefix for urban surface model output to "usm_",
222! added flag lsf_exception (inipar-Namelist parameter) to allow explicit
223! enabling of large scale forcing together with buildings on flat terrain,
224! introduced control parameter varnamelength for LEN of var.
225!
226! 2007 2016-08-24 15:47:17Z kanani
227! Added checks for the urban surface model,
228! increased counter in DO WHILE loop over data_output (for urban surface output)
229!
230! 2000 2016-08-20 18:09:15Z knoop
231! Forced header and separation lines into 80 columns
232!
233! 1994 2016-08-15 09:52:21Z suehring
234! Add missing check for cloud_physics and cloud_droplets
235!
236! 1992 2016-08-12 15:14:59Z suehring
237! New checks for top_scalarflux
238! Bugfixes concerning data output of profiles in case of passive_scalar
239!
240! 1984 2016-08-01 14:48:05Z suehring
241! Bugfix: checking for bottom and top boundary condition for humidity and scalars
242!
243! 1972 2016-07-26 07:52:02Z maronga
244! Removed check of lai* (done in land surface module)
245!
246! 1970 2016-07-18 14:27:12Z suehring
247! Bugfix, check for ibc_q_b and constant_waterflux in case of land-surface scheme
248!
249! 1962 2016-07-13 09:16:44Z suehring
250! typo removed
251!
252! 1960 2016-07-12 16:34:24Z suehring
253! Separate checks and calculations for humidity and passive scalar. Therefore,
254! a subroutine to calculate vertical gradients is introduced, in order  to reduce
255! redundance.
256! Additional check - large-scale forcing is not implemented for passive scalars
257! so far.
258!
259! 1931 2016-06-10 12:06:59Z suehring
260! Rename multigrid into multigrid_noopt and multigrid_fast into multigrid
261!
262! 1929 2016-06-09 16:25:25Z suehring
263! Bugfix in check for use_upstream_for_tke
264!
265! 1918 2016-05-27 14:35:57Z raasch
266! setting of a fixed reference state ('single_value') for ocean runs removed
267!
268! 1914 2016-05-26 14:44:07Z witha
269! Added checks for the wind turbine model
270!
271! 1841 2016-04-07 19:14:06Z raasch
272! redundant location message removed
273!
274! 1833 2016-04-07 14:23:03Z raasch
275! check of spectra quantities moved to spectra_mod
276!
277! 1829 2016-04-07 12:16:29Z maronga
278! Bugfix: output of user defined data required reset of the string 'unit'
279!
280! 1826 2016-04-07 12:01:39Z maronga
281! Moved checks for radiation model to the respective module.
282! Moved checks for plant canopy model to the respective module.
283! Bugfix for check of too large roughness_length
284!
285! 1824 2016-04-07 09:55:29Z gronemeier
286! Check if roughness_length < dz/2. Moved location_message(finished) to the end.
287!
288! 1822 2016-04-07 07:49:42Z hoffmann
289! PALM collision kernel deleted. Collision algorithms are checked for correct
290! spelling.
291!
292! Tails removed.
293! !
294! Checks for use_sgs_for_particles adopted for the use of droplets with
295! use_sgs_for_particles adopted.
296!
297! Unused variables removed.
298!
299! 1817 2016-04-06 15:44:20Z maronga
300! Moved checks for land_surface model to the respective module
301!
302! 1806 2016-04-05 18:55:35Z gronemeier
303! Check for recycling_yshift
304!
305! 1804 2016-04-05 16:30:18Z maronga
306! Removed code for parameter file check (__check)
307!
308! 1795 2016-03-18 15:00:53Z raasch
309! Bugfix: setting of initial scalar profile in ocean
310!
311! 1788 2016-03-10 11:01:04Z maronga
312! Added check for use of most_method = 'lookup' in combination with water
313! surface presribed in the land surface model. Added output of z0q.
314! Syntax layout improved.
315!
316! 1786 2016-03-08 05:49:27Z raasch
317! cpp-direktives for spectra removed, check of spectra level removed
318!
319! 1783 2016-03-06 18:36:17Z raasch
320! netcdf variables and module name changed,
321! check of netcdf precision removed (is done in the netcdf module)
322!
323! 1764 2016-02-28 12:45:19Z raasch
324! output of nest id in run description header,
325! bugfix: check of validity of lateral boundary conditions moved to parin
326!
327! 1762 2016-02-25 12:31:13Z hellstea
328! Introduction of nested domain feature
329!
330! 1745 2016-02-05 13:06:51Z gronemeier
331! Bugfix: check data output intervals to be /= 0.0 in case of parallel NetCDF4
332!
333! 1701 2015-11-02 07:43:04Z maronga
334! Bugfix: definition of rad_net timeseries was missing
335!
336! 1691 2015-10-26 16:17:44Z maronga
337! Added output of Obukhov length (ol) and radiative heating rates for RRTMG.
338! Added checks for use of radiation / lsm with topography.
339!
340! 1682 2015-10-07 23:56:08Z knoop
341! Code annotations made doxygen readable
342!
343! 1606 2015-06-29 10:43:37Z maronga
344! Added check for use of RRTMG without netCDF.
345!
346! 1587 2015-05-04 14:19:01Z maronga
347! Added check for set of albedos when using RRTMG
348!
349! 1585 2015-04-30 07:05:52Z maronga
350! Added support for RRTMG
351!
352! 1575 2015-03-27 09:56:27Z raasch
353! multigrid_fast added as allowed pressure solver
354!
355! 1573 2015-03-23 17:53:37Z suehring
356! Bugfix: check for advection schemes in case of non-cyclic boundary conditions
357!
358! 1557 2015-03-05 16:43:04Z suehring
359! Added checks for monotonic limiter
360!
361! 1555 2015-03-04 17:44:27Z maronga
362! Added output of r_a and r_s. Renumbering of LSM PA-messages.
363!
364! 1553 2015-03-03 17:33:54Z maronga
365! Removed check for missing soil temperature profile as default values were added.
366!
367! 1551 2015-03-03 14:18:16Z maronga
368! Added various checks for land surface and radiation model. In the course of this
369! action, the length of the variable var has to be increased
370!
371! 1504 2014-12-04 09:23:49Z maronga
372! Bugfix: check for large_scale forcing got lost.
373!
374! 1500 2014-12-03 17:42:41Z maronga
375! Boundary conditions changed to dirichlet for land surface model
376!
377! 1496 2014-12-02 17:25:50Z maronga
378! Added checks for the land surface model
379!
380! 1484 2014-10-21 10:53:05Z kanani
381! Changes due to new module structure of the plant canopy model:
382!   module plant_canopy_model_mod added,
383!   checks regarding usage of new method for leaf area density profile
384!   construction added,
385!   lad-profile construction moved to new subroutine init_plant_canopy within
386!   the module plant_canopy_model_mod,
387!   drag_coefficient renamed to canopy_drag_coeff.
388! Missing KIND-attribute for REAL constant added
389!
390! 1455 2014-08-29 10:47:47Z heinze
391! empty time records in volume, cross-section and masked data output prevented
392! in case of non-parallel netcdf-output in restart runs
393!
394! 1429 2014-07-15 12:53:45Z knoop
395! run_description_header exended to provide ensemble_member_nr if specified
396!
397! 1425 2014-07-05 10:57:53Z knoop
398! bugfix: perturbation domain modified for parallel random number generator
399!
400! 1402 2014-05-09 14:25:13Z raasch
401! location messages modified
402!
403! 1400 2014-05-09 14:03:54Z knoop
404! Check random generator extended by option random-parallel
405!
406! 1384 2014-05-02 14:31:06Z raasch
407! location messages added
408!
409! 1365 2014-04-22 15:03:56Z boeske
410! Usage of large scale forcing for pt and q enabled:
411! output for profiles of large scale advection (td_lsa_lpt, td_lsa_q),
412! large scale subsidence (td_sub_lpt, td_sub_q)
413! and nudging tendencies (td_nud_lpt, td_nud_q, td_nud_u and td_nud_v) added,
414! check if use_subsidence_tendencies is used correctly
415!
416! 1361 2014-04-16 15:17:48Z hoffmann
417! PA0363 removed
418! PA0362 changed
419!
420! 1359 2014-04-11 17:15:14Z hoffmann
421! Do not allow the execution of PALM with use_particle_tails, since particle
422! tails are currently not supported by our new particle structure.
423!
424! PA0084 not necessary for new particle structure
425!
426! 1353 2014-04-08 15:21:23Z heinze
427! REAL constants provided with KIND-attribute
428!
429! 1330 2014-03-24 17:29:32Z suehring
430! In case of SGS-particle velocity advection of TKE is also allowed with
431! dissipative 5th-order scheme.
432!
433! 1327 2014-03-21 11:00:16Z raasch
434! "baroclinicity" renamed "baroclinity", "ocean version" replaced by "ocean mode"
435! bugfix: duplicate error message 56 removed,
436! check of data_output_format and do3d_compress removed
437!
438! 1322 2014-03-20 16:38:49Z raasch
439! some REAL constants defined as wp-kind
440!
441! 1320 2014-03-20 08:40:49Z raasch
442! Kind-parameters added to all INTEGER and REAL declaration statements,
443! kinds are defined in new module kinds,
444! revision history before 2012 removed,
445! comment fields (!:) to be used for variable explanations added to
446! all variable declaration statements
447!
448! 1308 2014-03-13 14:58:42Z fricke
449! +netcdf_data_format_save
450! Calculate fixed number of output time levels for parallel netcdf output.
451! For masked data, parallel netcdf output is not tested so far, hence
452! netcdf_data_format is switched back to non-paralell output.
453!
454! 1299 2014-03-06 13:15:21Z heinze
455! enable usage of large_scale subsidence in combination with large_scale_forcing
456! output for profile of large scale vertical velocity w_subs added
457!
458! 1276 2014-01-15 13:40:41Z heinze
459! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
460!
461! 1241 2013-10-30 11:36:58Z heinze
462! output for profiles of ug and vg added
463! set surface_heatflux and surface_waterflux also in dependence on
464! large_scale_forcing
465! checks for nudging and large scale forcing from external file
466!
467! 1236 2013-09-27 07:21:13Z raasch
468! check number of spectra levels
469!
470! 1216 2013-08-26 09:31:42Z raasch
471! check for transpose_compute_overlap (temporary)
472!
473! 1214 2013-08-21 12:29:17Z kanani
474! additional check for simultaneous use of vertical grid stretching
475! and particle advection
476!
477! 1212 2013-08-15 08:46:27Z raasch
478! checks for poisfft_hybrid removed
479!
480! 1210 2013-08-14 10:58:20Z raasch
481! check for fftw
482!
483! 1179 2013-06-14 05:57:58Z raasch
484! checks and settings of buoyancy parameters and switches revised,
485! initial profile for rho_ocean added to hom (id=77)
486!
487! 1174 2013-05-31 10:28:08Z gryschka
488! Bugfix in computing initial profiles for ug, vg, lad, q in case of Atmosphere
489!
490! 1159 2013-05-21 11:58:22Z fricke
491! bc_lr/ns_dirneu/neudir removed
492!
493! 1115 2013-03-26 18:16:16Z hoffmann
494! unused variables removed
495! drizzle can be used without precipitation
496!
497! 1111 2013-03-08 23:54:10Z raasch
498! ibc_p_b = 2 removed
499!
500! 1103 2013-02-20 02:15:53Z raasch
501! Bugfix: turbulent inflow must not require cyclic fill in restart runs
502!
503! 1092 2013-02-02 11:24:22Z raasch
504! unused variables removed
505!
506! 1069 2012-11-28 16:18:43Z maronga
507! allow usage of topography in combination with cloud physics
508!
509! 1065 2012-11-22 17:42:36Z hoffmann
510! Bugfix: It is not allowed to use cloud_scheme = seifert_beheng without
511!         precipitation in order to save computational resources.
512!
513! 1060 2012-11-21 07:19:51Z raasch
514! additional check for parameter turbulent_inflow
515!
516! 1053 2012-11-13 17:11:03Z hoffmann
517! necessary changes for the new two-moment cloud physics scheme added:
518! - check cloud physics scheme (Kessler or Seifert and Beheng)
519! - plant_canopy is not allowed
520! - currently, only cache loop_optimization is allowed
521! - initial profiles of nr, qr
522! - boundary condition of nr, qr
523! - check output quantities (qr, nr, prr)
524!
525! 1036 2012-10-22 13:43:42Z raasch
526! code put under GPL (PALM 3.9)
527!
528! 1031/1034 2012-10-22 11:32:49Z raasch
529! check of netcdf4 parallel file support
530!
531! 1019 2012-09-28 06:46:45Z raasch
532! non-optimized version of prognostic_equations not allowed any more
533!
534! 1015 2012-09-27 09:23:24Z raasch
535! acc allowed for loop optimization,
536! checks for adjustment of mixing length to the Prandtl mixing length removed
537!
538! 1003 2012-09-14 14:35:53Z raasch
539! checks for cases with unequal subdomain sizes removed
540!
541! 1001 2012-09-13 14:08:46Z raasch
542! all actions concerning leapfrog- and upstream-spline-scheme removed
543!
544! 996 2012-09-07 10:41:47Z raasch
545! little reformatting
546
547! 978 2012-08-09 08:28:32Z fricke
548! setting of bc_lr/ns_dirneu/neudir
549! outflow damping layer removed
550! check for z0h*
551! check for pt_damping_width
552!
553! 964 2012-07-26 09:14:24Z raasch
554! check of old profil-parameters removed
555!
556! 940 2012-07-09 14:31:00Z raasch
557! checks for parameter neutral
558!
559! 924 2012-06-06 07:44:41Z maronga
560! Bugfix: preprocessor directives caused error during compilation
561!
562! 892 2012-05-02 13:51:44Z maronga
563! Bugfix for parameter file check ( excluding __netcdf4 )
564!
565! 866 2012-03-28 06:44:41Z raasch
566! use only 60% of the geostrophic wind as translation speed in case of Galilean
567! transformation and use_ug_for_galilei_tr = .T. in order to mimimize the
568! timestep
569!
570! 861 2012-03-26 14:18:34Z suehring
571! Check for topography and ws-scheme removed.
572! Check for loop_optimization = 'vector' and ws-scheme removed.
573!
574! 845 2012-03-07 10:23:05Z maronga
575! Bugfix: exclude __netcdf4 directive part from namelist file check compilation
576!
577! 828 2012-02-21 12:00:36Z raasch
578! check of collision_kernel extended
579!
580! 825 2012-02-19 03:03:44Z raasch
581! check for collision_kernel and curvature_solution_effects
582!
583! 809 2012-01-30 13:32:58Z maronga
584! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives
585!
586! 807 2012-01-25 11:53:51Z maronga
587! New cpp directive "__check" implemented which is used by check_namelist_files
588!
589! Revision 1.1  1997/08/26 06:29:23  raasch
590! Initial revision
591!
592!
593! Description:
594! ------------
595!> Check control parameters and deduce further quantities.
596!------------------------------------------------------------------------------!
597 SUBROUTINE check_parameters
598
599
600    USE arrays_3d
601    USE chemistry_model_mod,                                                   &
602        ONLY:  chem_boundary_conds, chem_check_data_output,                    &
603               chem_check_data_output_pr, chem_species                 
604    USE chem_modules
605    USE cloud_parameters
606    USE constants
607    USE control_parameters
608    USE dvrp_variables
609    USE grid_variables
610    USE gust_mod,                                                              &
611        ONLY: gust_check_data_output, gust_check_data_output_pr,               &
612              gust_check_parameters, gust_module_enabled
613    USE indices
614    USE land_surface_model_mod,                                                &
615        ONLY: lsm_check_data_output, lsm_check_data_output_pr,                 &
616              lsm_check_parameters
617
618    USE lsf_nudging_mod,                                                       &
619        ONLY:  lsf_nudging_check_parameters, lsf_nudging_check_data_output_pr, &
620               qsws_surf, shf_surf
621
622    USE kinds
623
624    USE model_1d_mod,                                                          &
625        ONLY:  damp_level_1d, damp_level_ind_1d
626
627    USE netcdf_data_input_mod,                                                 &
628        ONLY:  init_model, input_pids_static, netcdf_data_input_check_dynamic, &
629               netcdf_data_input_check_static
630
631    USE netcdf_interface,                                                      &
632        ONLY:  dopr_unit, do2d_unit, do3d_unit, netcdf_data_format,            &
633               netcdf_data_format_string, dots_unit, heatflux_output_unit,     &
634               waterflux_output_unit, momentumflux_output_unit
635
636    USE particle_attributes
637    USE pegrid
638    USE plant_canopy_model_mod,                                                &
639        ONLY:  pcm_check_data_output, pcm_check_parameters
640
641    USE pmc_interface,                                                         &
642        ONLY:  cpl_id, nested_run
643
644    USE profil_parameter
645    USE radiation_model_mod,                                                   &
646        ONLY:  radiation, radiation_check_data_output,                         &
647               radiation_check_data_output_pr, radiation_check_parameters
648    USE spectra_mod,                                                           &
649        ONLY:  calculate_spectra, spectra_check_parameters
650    USE statistics
651    USE subsidence_mod
652    USE statistics
653    USE synthetic_turbulence_generator_mod,                                    &
654        ONLY:  stg_check_parameters
655    USE transpose_indices
656    USE turbulence_closure_mod,                                                &
657        ONLY:  tcm_check_data_output, tcm_check_parameters
658    USE urban_surface_mod,                                                     &
659        ONLY:  usm_check_data_output, usm_check_parameters
660    USE uv_exposure_model_mod,                                                 &
661        ONLY:  uvem_check_data_output
662    USE wind_turbine_model_mod,                                                &
663        ONLY:  wtm_check_parameters
664    USE vertical_nesting_mod,                                                  &
665        ONLY:  vnested, vnest_check_parameters
666
667
668    IMPLICIT NONE
669
670    CHARACTER (LEN=1)   ::  sq                       !<
671    CHARACTER (LEN=varnamelength)  ::  var           !<
672    CHARACTER (LEN=7)   ::  unit                     !<
673    CHARACTER (LEN=8)   ::  date                     !<
674    CHARACTER (LEN=10)  ::  time                     !<
675    CHARACTER (LEN=20)  ::  ensemble_string          !<
676    CHARACTER (LEN=15)  ::  nest_string              !<
677    CHARACTER (LEN=40)  ::  coupling_string          !<
678    CHARACTER (LEN=100) ::  action                   !<
679
680    INTEGER(iwp) ::  i                               !<
681    INTEGER(iwp) ::  ilen                            !<
682    INTEGER(iwp) ::  j                               !<
683    INTEGER(iwp) ::  k                               !<
684    INTEGER(iwp) ::  kk                              !<
685    INTEGER(iwp) ::  netcdf_data_format_save         !<
686    INTEGER(iwp) ::  position                        !<
687    INTEGER(iwp) ::  lsp                             !< running index for chem spcs.
688
689    LOGICAL     ::  check_nest                       !< flag used to check initialization in case of nesting
690    LOGICAL     ::  found                            !<
691
692    REAL(wp)    ::  dum                              !<
693    REAL(wp)    ::  gradient                         !<
694    REAL(wp)    ::  remote = 0.0_wp                  !<
695    REAL(wp)    ::  time_to_be_simulated_from_reference_point  !<
696
697
698    CALL location_message( 'checking parameters', .FALSE. )
699!
700!-- At first, check static and dynamic input for consistency
701    CALL netcdf_data_input_check_dynamic
702    CALL netcdf_data_input_check_static
703!
704!-- Check for overlap combinations, which are not realized yet
705    IF ( transpose_compute_overlap )  THEN
706       IF ( numprocs == 1 )  STOP '+++ transpose-compute-overlap not implemented for single PE runs'
707    ENDIF
708
709!
710!-- Check the coupling mode
711!> @todo Check if any queries for other coupling modes (e.g. precursor_ocean) are missing
712    IF ( coupling_mode /= 'uncoupled'            .AND.  &
713         coupling_mode /= 'vnested_crse'         .AND.  &
714         coupling_mode /= 'vnested_fine'         .AND.  &
715         coupling_mode /= 'atmosphere_to_ocean'  .AND.  &
716         coupling_mode /= 'ocean_to_atmosphere' )  THEN
717       message_string = 'illegal coupling mode: ' // TRIM( coupling_mode )
718       CALL message( 'check_parameters', 'PA0002', 1, 2, 0, 6, 0 )
719    ENDIF
720
721!
722!-- Check if humidity is set to TRUE in case of the atmospheric run (for coupled runs)
723    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. .NOT. humidity) THEN
724       message_string = ' Humidity has to be set to .T. in the _p3d file for ' //      &
725                        'coupled runs between ocean and atmosphere.'
726       CALL message( 'check_parameters', 'PA0476', 1, 2, 0, 6, 0 )
727    ENDIF
728   
729!
730!-- Check dt_coupling, restart_time, dt_restart, end_time, dx, dy, nx and ny
731    IF ( coupling_mode /= 'uncoupled'  .AND.                                   &
732         coupling_mode(1:8) /= 'vnested_' )  THEN
733
734       IF ( dt_coupling == 9999999.9_wp )  THEN
735          message_string = 'dt_coupling is not set but required for coup' //   &
736                           'ling mode "' //  TRIM( coupling_mode ) // '"'
737          CALL message( 'check_parameters', 'PA0003', 1, 2, 0, 6, 0 )
738       ENDIF
739
740#if defined( __parallel )
741
742
743       IF ( myid == 0 ) THEN
744          CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter,  &
745                         ierr )
746          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter,       &
747                         status, ierr )
748       ENDIF
749       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
750
751       IF ( dt_coupling /= remote )  THEN
752          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
753                 '": dt_coupling = ', dt_coupling, '& is not equal to ',       &
754                 'dt_coupling_remote = ', remote
755          CALL message( 'check_parameters', 'PA0004', 1, 2, 0, 6, 0 )
756       ENDIF
757       IF ( dt_coupling <= 0.0_wp )  THEN
758
759          IF ( myid == 0  ) THEN
760             CALL MPI_SEND( dt_max, 1, MPI_REAL, target_id, 19, comm_inter, ierr )
761             CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter,    &
762                            status, ierr )
763          ENDIF
764          CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
765
766          dt_coupling = MAX( dt_max, remote )
767          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
768                 '": dt_coupling <= 0.0 & is not allowed and is reset to ',    &
769                 'MAX(dt_max(A,O)) = ', dt_coupling
770          CALL message( 'check_parameters', 'PA0005', 0, 1, 0, 6, 0 )
771       ENDIF
772
773       IF ( myid == 0 ) THEN
774          CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, &
775                         ierr )
776          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter,       &
777                         status, ierr )
778       ENDIF
779       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
780
781       IF ( restart_time /= remote )  THEN
782          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
783                 '": restart_time = ', restart_time, '& is not equal to ',     &
784                 'restart_time_remote = ', remote
785          CALL message( 'check_parameters', 'PA0006', 1, 2, 0, 6, 0 )
786       ENDIF
787
788       IF ( myid == 0 ) THEN
789          CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter,   &
790                         ierr )
791          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter,       &
792                         status, ierr )
793       ENDIF
794       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
795
796       IF ( dt_restart /= remote )  THEN
797          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
798                 '": dt_restart = ', dt_restart, '& is not equal to ',         &
799                 'dt_restart_remote = ', remote
800          CALL message( 'check_parameters', 'PA0007', 1, 2, 0, 6, 0 )
801       ENDIF
802
803       time_to_be_simulated_from_reference_point = end_time-coupling_start_time
804
805       IF  ( myid == 0 ) THEN
806          CALL MPI_SEND( time_to_be_simulated_from_reference_point, 1,         &
807                         MPI_REAL, target_id, 14, comm_inter, ierr )
808          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter,       &
809                         status, ierr )
810       ENDIF
811       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
812
813       IF ( time_to_be_simulated_from_reference_point /= remote )  THEN
814          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
815                 '": time_to_be_simulated_from_reference_point = ',            &
816                 time_to_be_simulated_from_reference_point, '& is not equal ', &
817                 'to time_to_be_simulated_from_reference_point_remote = ',     &
818                 remote
819          CALL message( 'check_parameters', 'PA0008', 1, 2, 0, 6, 0 )
820       ENDIF
821
822       IF ( myid == 0 ) THEN
823          CALL MPI_SEND( dx, 1, MPI_REAL, target_id, 15, comm_inter, ierr )
824          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter,       &
825                                                             status, ierr )
826       ENDIF
827       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
828
829
830       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
831
832          IF ( dx < remote ) THEN
833             WRITE( message_string, * ) 'coupling mode "',                     &
834                   TRIM( coupling_mode ),                                      &
835           '": dx in Atmosphere is not equal to or not larger than dx in ocean'
836             CALL message( 'check_parameters', 'PA0009', 1, 2, 0, 6, 0 )
837          ENDIF
838
839          IF ( (nx_a+1)*dx /= (nx_o+1)*remote )  THEN
840             WRITE( message_string, * ) 'coupling mode "',                     &
841                    TRIM( coupling_mode ),                                     &
842             '": Domain size in x-direction is not equal in ocean and atmosphere'
843             CALL message( 'check_parameters', 'PA0010', 1, 2, 0, 6, 0 )
844          ENDIF
845
846       ENDIF
847
848       IF ( myid == 0) THEN
849          CALL MPI_SEND( dy, 1, MPI_REAL, target_id, 16, comm_inter, ierr )
850          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter,       &
851                         status, ierr )
852       ENDIF
853       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
854
855       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
856
857          IF ( dy < remote )  THEN
858             WRITE( message_string, * ) 'coupling mode "',                     &
859                    TRIM( coupling_mode ),                                     &
860                 '": dy in Atmosphere is not equal to or not larger than dy in ocean'
861             CALL message( 'check_parameters', 'PA0011', 1, 2, 0, 6, 0 )
862          ENDIF
863
864          IF ( (ny_a+1)*dy /= (ny_o+1)*remote )  THEN
865             WRITE( message_string, * ) 'coupling mode "',                     &
866                   TRIM( coupling_mode ),                                      &
867             '": Domain size in y-direction is not equal in ocean and atmosphere'
868             CALL message( 'check_parameters', 'PA0012', 1, 2, 0, 6, 0 )
869          ENDIF
870
871          IF ( MOD(nx_o+1,nx_a+1) /= 0 )  THEN
872             WRITE( message_string, * ) 'coupling mode "',                     &
873                   TRIM( coupling_mode ),                                      &
874             '": nx+1 in ocean is not divisible by nx+1 in', &
875             ' atmosphere without remainder'
876             CALL message( 'check_parameters', 'PA0339', 1, 2, 0, 6, 0 )
877          ENDIF
878
879          IF ( MOD(ny_o+1,ny_a+1) /= 0 )  THEN
880             WRITE( message_string, * ) 'coupling mode "',                     &
881                   TRIM( coupling_mode ),                                      &
882             '": ny+1 in ocean is not divisible by ny+1 in', &
883             ' atmosphere without remainder'
884
885             CALL message( 'check_parameters', 'PA0340', 1, 2, 0, 6, 0 )
886          ENDIF
887
888       ENDIF
889#else
890       WRITE( message_string, * ) 'coupling requires PALM to be compiled with',&
891            ' cpp-option "-D__parallel"'
892       CALL message( 'check_parameters', 'PA0141', 1, 2, 0, 6, 0 )
893#endif
894    ENDIF
895
896#if defined( __parallel )
897!
898!-- Exchange via intercommunicator
899    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. myid == 0 )  THEN
900       CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter,     &
901                      ierr )
902    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' .AND. myid == 0)  THEN
903       CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19,          &
904                      comm_inter, status, ierr )
905    ENDIF
906    CALL MPI_BCAST( humidity_remote, 1, MPI_LOGICAL, 0, comm2d, ierr)
907
908#endif
909
910!
911!-- User settings for restart times requires that "restart" has been given as
912!-- file activation string. Otherwise, binary output would not be saved by
913!-- palmrun.
914    IF (  ( restart_time /= 9999999.9_wp  .OR.  dt_restart /= 9999999.9_wp )   &
915         .AND.  .NOT. write_binary )  THEN
916       WRITE( message_string, * ) 'manual restart settings requires file ',    &
917                                  'activation string "restart"'
918       CALL message( 'check_parameters', 'PA0001', 1, 2, 0, 6, 0 )
919    ENDIF
920
921
922!
923!-- Generate the file header which is used as a header for most of PALM's
924!-- output files
925    CALL DATE_AND_TIME( date, time )
926    run_date = date(7:8)//'-'//date(5:6)//'-'//date(3:4)
927    run_time = time(1:2)//':'//time(3:4)//':'//time(5:6)
928    IF ( coupling_mode == 'uncoupled' )  THEN
929       coupling_string = ''
930    ELSEIF ( coupling_mode == 'vnested_crse' )  THEN
931       coupling_string = ' nested (coarse)'
932    ELSEIF ( coupling_mode == 'vnested_fine' )  THEN
933       coupling_string = ' nested (fine)'
934    ELSEIF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
935       coupling_string = ' coupled (atmosphere)'
936    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
937       coupling_string = ' coupled (ocean)'
938    ENDIF
939    IF ( ensemble_member_nr /= 0 )  THEN
940       WRITE( ensemble_string, '(2X,A,I2.2)' )  'en-no: ', ensemble_member_nr
941    ELSE
942       ensemble_string = ''
943    ENDIF
944    IF ( nested_run )  THEN
945       WRITE( nest_string, '(2X,A,I2.2)' )  'nest-id: ', cpl_id
946    ELSE
947       nest_string = ''
948    ENDIF
949
950    WRITE ( run_description_header,                                            &
951            '(A,2X,A,2X,A,A,A,I2.2,A,A,A,2X,A,A,2X,A,1X,A)' )                  &
952          TRIM( version ), TRIM( revision ), 'run: ',                          &
953          TRIM( run_identifier ), '.', runnr, TRIM( coupling_string ),         &
954          TRIM( nest_string ), TRIM( ensemble_string), 'host: ', TRIM( host ), &
955          run_date, run_time
956
957!
958!-- Check the general loop optimization method
959    SELECT CASE ( TRIM( loop_optimization ) )
960
961       CASE ( 'cache', 'vector' )
962          CONTINUE
963
964       CASE DEFAULT
965          message_string = 'illegal value given for loop_optimization: "' //   &
966                           TRIM( loop_optimization ) // '"'
967          CALL message( 'check_parameters', 'PA0013', 1, 2, 0, 6, 0 )
968
969    END SELECT
970
971!
972!-- Check topography setting (check for illegal parameter combinations)
973    IF ( topography /= 'flat' )  THEN
974       action = ' '
975       IF ( scalar_advec /= 'pw-scheme' .AND. scalar_advec /= 'ws-scheme'      &
976          )  THEN
977          WRITE( action, '(A,A)' )  'scalar_advec = ', scalar_advec
978       ENDIF
979       IF ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' )&
980       THEN
981          WRITE( action, '(A,A)' )  'momentum_advec = ', momentum_advec
982       ENDIF
983       IF ( psolver == 'sor' )  THEN
984          WRITE( action, '(A,A)' )  'psolver = ', psolver
985       ENDIF
986       IF ( sloping_surface )  THEN
987          WRITE( action, '(A)' )  'sloping surface = .TRUE.'
988       ENDIF
989       IF ( galilei_transformation )  THEN
990          WRITE( action, '(A)' )  'galilei_transformation = .TRUE.'
991       ENDIF
992       IF ( cloud_physics )  THEN
993          WRITE( action, '(A)' )  'cloud_physics = .TRUE.'
994       ENDIF
995       IF ( cloud_droplets )  THEN
996          WRITE( action, '(A)' )  'cloud_droplets = .TRUE.'
997       ENDIF
998       IF ( .NOT. constant_flux_layer )  THEN
999          WRITE( action, '(A)' )  'constant_flux_layer = .FALSE.'
1000       ENDIF
1001       IF ( action /= ' ' )  THEN
1002          message_string = 'a non-flat topography does not allow ' //          &
1003                           TRIM( action )
1004          CALL message( 'check_parameters', 'PA0014', 1, 2, 0, 6, 0 )
1005       ENDIF
1006
1007    ENDIF
1008
1009!
1010!-- Check turbulence closure setup
1011    CALL tcm_check_parameters
1012
1013!
1014!-- Check approximation
1015    IF ( TRIM( approximation ) /= 'boussinesq'   .AND.   &
1016         TRIM( approximation ) /= 'anelastic' )  THEN
1017       message_string = 'unknown approximation: approximation = "' //    &
1018                        TRIM( approximation ) // '"'
1019       CALL message( 'check_parameters', 'PA0446', 1, 2, 0, 6, 0 )
1020    ENDIF
1021
1022!
1023!-- Check approximation requirements
1024    IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
1025         TRIM( momentum_advec ) /= 'ws-scheme' )  THEN
1026       message_string = 'Anelastic approximation requires: ' //                &
1027                        'momentum_advec = "ws-scheme"'
1028       CALL message( 'check_parameters', 'PA0447', 1, 2, 0, 6, 0 )
1029    ENDIF
1030    IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
1031         TRIM( psolver ) == 'multigrid' )  THEN
1032       message_string = 'Anelastic approximation currently only supports: ' // &
1033                        'psolver = "poisfft", ' // &
1034                        'psolver = "sor" and ' // &
1035                        'psolver = "multigrid_noopt"'
1036       CALL message( 'check_parameters', 'PA0448', 1, 2, 0, 6, 0 )
1037    ENDIF
1038    IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
1039         conserve_volume_flow )  THEN
1040       message_string = 'Anelastic approximation is not allowed with:' //      &
1041                        'conserve_volume_flow = .TRUE.'
1042       CALL message( 'check_parameters', 'PA0449', 1, 2, 0, 6, 0 )
1043    ENDIF
1044
1045!
1046!-- Check flux input mode
1047    IF ( TRIM( flux_input_mode ) /= 'dynamic'    .AND.   &
1048         TRIM( flux_input_mode ) /= 'kinematic'  .AND.   &
1049         TRIM( flux_input_mode ) /= 'approximation-specific' )  THEN
1050       message_string = 'unknown flux input mode: flux_input_mode = "' //      &
1051                        TRIM( flux_input_mode ) // '"'
1052       CALL message( 'check_parameters', 'PA0450', 1, 2, 0, 6, 0 )
1053    ENDIF
1054!-- Set flux input mode according to approximation if applicable
1055    IF ( TRIM( flux_input_mode ) == 'approximation-specific' )  THEN
1056       IF ( TRIM( approximation ) == 'anelastic' )  THEN
1057          flux_input_mode = 'dynamic'
1058       ELSEIF ( TRIM( approximation ) == 'boussinesq' )  THEN
1059          flux_input_mode = 'kinematic'
1060       ENDIF
1061    ENDIF
1062
1063!
1064!-- Check flux output mode
1065    IF ( TRIM( flux_output_mode ) /= 'dynamic'    .AND.   &
1066         TRIM( flux_output_mode ) /= 'kinematic'  .AND.   &
1067         TRIM( flux_output_mode ) /= 'approximation-specific' )  THEN
1068       message_string = 'unknown flux output mode: flux_output_mode = "' //    &
1069                        TRIM( flux_output_mode ) // '"'
1070       CALL message( 'check_parameters', 'PA0451', 1, 2, 0, 6, 0 )
1071    ENDIF
1072!-- Set flux output mode according to approximation if applicable
1073    IF ( TRIM( flux_output_mode ) == 'approximation-specific' )  THEN
1074       IF ( TRIM( approximation ) == 'anelastic' )  THEN
1075          flux_output_mode = 'dynamic'
1076       ELSEIF ( TRIM( approximation ) == 'boussinesq' )  THEN
1077          flux_output_mode = 'kinematic'
1078       ENDIF
1079    ENDIF
1080
1081
1082!
1083!-- When the land- or urban-surface model is used, the flux output must be
1084!-- dynamic.
1085    IF ( land_surface  .OR.  urban_surface )  THEN
1086       flux_output_mode = 'dynamic'
1087    ENDIF
1088
1089!
1090!-- set the flux output units according to flux_output_mode
1091    IF ( TRIM( flux_output_mode ) == 'kinematic' ) THEN
1092        heatflux_output_unit              = 'K m/s'
1093        waterflux_output_unit             = 'kg/kg m/s'
1094        momentumflux_output_unit          = 'm2/s2'
1095    ELSEIF ( TRIM( flux_output_mode ) == 'dynamic' ) THEN
1096        heatflux_output_unit              = 'W/m2'
1097        waterflux_output_unit             = 'W/m2'
1098        momentumflux_output_unit          = 'N/m2'
1099    ENDIF
1100
1101!-- set time series output units for fluxes
1102    dots_unit(14:16) = heatflux_output_unit
1103    dots_unit(21)    = waterflux_output_unit
1104    dots_unit(19:20) = momentumflux_output_unit
1105
1106!
1107!-- Check ocean setting
1108    IF ( TRIM( coupling_mode ) == 'uncoupled'  .AND.                           &
1109         TRIM( coupling_char ) == '_O' .AND.                                   &
1110         .NOT. ocean )  THEN
1111
1112!
1113!--    Check whether an (uncoupled) atmospheric run has been declared as an
1114!--    ocean run (this setting is done via mrun-option -y)
1115       message_string = 'ocean = .F. does not allow coupling_char = "' //      &
1116                        TRIM( coupling_char ) // '" set by palmrun-option "-y"'
1117       CALL message( 'check_parameters', 'PA0317', 1, 2, 0, 6, 0 )
1118
1119    ENDIF
1120!
1121!-- Check cloud scheme
1122    IF ( cloud_scheme == 'saturation_adjust' )  THEN
1123       microphysics_sat_adjust = .TRUE.
1124       microphysics_seifert    = .FALSE.
1125       microphysics_kessler    = .FALSE.
1126       precipitation           = .FALSE.
1127    ELSEIF ( cloud_scheme == 'seifert_beheng' )  THEN
1128       microphysics_sat_adjust = .FALSE.
1129       microphysics_seifert    = .TRUE.
1130       microphysics_kessler    = .FALSE.
1131       microphysics_morrison  = .FALSE.
1132       precipitation           = .TRUE.
1133    ELSEIF ( cloud_scheme == 'kessler' )  THEN
1134       microphysics_sat_adjust = .FALSE.
1135       microphysics_seifert    = .FALSE.
1136       microphysics_kessler    = .TRUE.
1137       microphysics_morrison   = .FALSE.
1138       precipitation           = .TRUE.
1139    ELSEIF ( cloud_scheme == 'morrison' )  THEN
1140       microphysics_sat_adjust = .FALSE.
1141       microphysics_seifert    = .TRUE.
1142       microphysics_kessler    = .FALSE.
1143       microphysics_morrison   = .TRUE.
1144       precipitation           = .TRUE.
1145    ELSE
1146       message_string = 'unknown cloud microphysics scheme cloud_scheme ="' // &
1147                        TRIM( cloud_scheme ) // '"'
1148       CALL message( 'check_parameters', 'PA0357', 1, 2, 0, 6, 0 )
1149    ENDIF
1150!
1151!-- Check aerosol
1152    IF ( aerosol_bulk == 'nacl' )  THEN
1153       aerosol_nacl   = .TRUE.
1154       aerosol_c3h4o4 = .FALSE.
1155       aerosol_nh4no3 = .FALSE.
1156    ELSEIF ( aerosol_bulk == 'c3h4o4' )  THEN
1157       aerosol_nacl   = .FALSE.
1158       aerosol_c3h4o4 = .TRUE.
1159       aerosol_nh4no3 = .FALSE.
1160    ELSEIF ( aerosol_bulk == 'nh4no3' )  THEN
1161       aerosol_nacl   = .FALSE.
1162       aerosol_c3h4o4 = .FALSE.
1163       aerosol_nh4no3 = .TRUE.
1164    ELSE
1165       message_string = 'unknown aerosol ="' // &
1166                        TRIM( aerosol_bulk ) // '"'
1167       CALL message( 'check_parameters', 'PA0469', 1, 2, 0, 6, 0 )
1168    ENDIF
1169
1170!
1171!-- Check whether there are any illegal values
1172!-- Pressure solver:
1173    IF ( psolver /= 'poisfft'  .AND.  psolver /= 'sor'  .AND.                  &
1174         psolver /= 'multigrid'  .AND.  psolver /= 'multigrid_noopt' )  THEN
1175       message_string = 'unknown solver for perturbation pressure: psolver' // &
1176                        ' = "' // TRIM( psolver ) // '"'
1177       CALL message( 'check_parameters', 'PA0016', 1, 2, 0, 6, 0 )
1178    ENDIF
1179
1180    IF ( psolver(1:9) == 'multigrid' )  THEN
1181       IF ( cycle_mg == 'w' )  THEN
1182          gamma_mg = 2
1183       ELSEIF ( cycle_mg == 'v' )  THEN
1184          gamma_mg = 1
1185       ELSE
1186          message_string = 'unknown multigrid cycle: cycle_mg = "' //          &
1187                           TRIM( cycle_mg ) // '"'
1188          CALL message( 'check_parameters', 'PA0020', 1, 2, 0, 6, 0 )
1189       ENDIF
1190    ENDIF
1191
1192    IF ( fft_method /= 'singleton-algorithm'  .AND.                            &
1193         fft_method /= 'temperton-algorithm'  .AND.                            &
1194         fft_method /= 'fftw'                 .AND.                            &
1195         fft_method /= 'system-specific' )  THEN
1196       message_string = 'unknown fft-algorithm: fft_method = "' //             &
1197                        TRIM( fft_method ) // '"'
1198       CALL message( 'check_parameters', 'PA0021', 1, 2, 0, 6, 0 )
1199    ENDIF
1200
1201    IF( momentum_advec == 'ws-scheme' .AND.                                    &
1202        .NOT. call_psolver_at_all_substeps  ) THEN
1203        message_string = 'psolver must be called at each RK3 substep when "'// &
1204                      TRIM(momentum_advec) // ' "is used for momentum_advec'
1205        CALL message( 'check_parameters', 'PA0344', 1, 2, 0, 6, 0 )
1206    END IF
1207!
1208!-- Advection schemes:
1209    IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' ) &
1210    THEN
1211       message_string = 'unknown advection scheme: momentum_advec = "' //      &
1212                        TRIM( momentum_advec ) // '"'
1213       CALL message( 'check_parameters', 'PA0022', 1, 2, 0, 6, 0 )
1214    ENDIF
1215    IF ( ( momentum_advec == 'ws-scheme' .OR.  scalar_advec == 'ws-scheme' )   &
1216           .AND. ( timestep_scheme == 'euler' .OR.                             &
1217                   timestep_scheme == 'runge-kutta-2' ) )                      &
1218    THEN
1219       message_string = 'momentum_advec or scalar_advec = "'                   &
1220         // TRIM( momentum_advec ) // '" is not allowed with timestep_scheme = "' // &
1221         TRIM( timestep_scheme ) // '"'
1222       CALL message( 'check_parameters', 'PA0023', 1, 2, 0, 6, 0 )
1223    ENDIF
1224    IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' .AND. &
1225         scalar_advec /= 'bc-scheme' )                                         &
1226    THEN
1227       message_string = 'unknown advection scheme: scalar_advec = "' //        &
1228                        TRIM( scalar_advec ) // '"'
1229       CALL message( 'check_parameters', 'PA0024', 1, 2, 0, 6, 0 )
1230    ENDIF
1231    IF ( scalar_advec == 'bc-scheme'  .AND.  loop_optimization == 'cache' )    &
1232    THEN
1233       message_string = 'advection_scheme scalar_advec = "'                    &
1234         // TRIM( scalar_advec ) // '" not implemented for & loop_optimization = "' // &
1235         TRIM( loop_optimization ) // '"'
1236       CALL message( 'check_parameters', 'PA0026', 1, 2, 0, 6, 0 )
1237    ENDIF
1238
1239    IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets  .AND.             &
1240         .NOT. use_upstream_for_tke  .AND.                                     &
1241         scalar_advec /= 'ws-scheme'                                           &
1242       )  THEN
1243       use_upstream_for_tke = .TRUE.
1244       message_string = 'use_upstream_for_tke is set to .TRUE. because ' //    &
1245                        'use_sgs_for_particles = .TRUE. '          //          &
1246                        'and scalar_advec /= ws-scheme'
1247       CALL message( 'check_parameters', 'PA0025', 0, 1, 0, 6, 0 )
1248    ENDIF
1249
1250!
1251!-- Set LOGICAL switches to enhance performance
1252    IF ( momentum_advec == 'ws-scheme' )  ws_scheme_mom = .TRUE.
1253    IF ( scalar_advec   == 'ws-scheme' )  ws_scheme_sca = .TRUE.
1254
1255
1256!
1257!-- Timestep schemes:
1258    SELECT CASE ( TRIM( timestep_scheme ) )
1259
1260       CASE ( 'euler' )
1261          intermediate_timestep_count_max = 1
1262
1263       CASE ( 'runge-kutta-2' )
1264          intermediate_timestep_count_max = 2
1265
1266       CASE ( 'runge-kutta-3' )
1267          intermediate_timestep_count_max = 3
1268
1269       CASE DEFAULT
1270          message_string = 'unknown timestep scheme: timestep_scheme = "' //   &
1271                           TRIM( timestep_scheme ) // '"'
1272          CALL message( 'check_parameters', 'PA0027', 1, 2, 0, 6, 0 )
1273
1274    END SELECT
1275
1276    IF ( (momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme')   &
1277         .AND. timestep_scheme(1:5) == 'runge' ) THEN
1278       message_string = 'momentum advection scheme "' // &
1279                        TRIM( momentum_advec ) // '" & does not work with ' // &
1280                        'timestep_scheme "' // TRIM( timestep_scheme ) // '"'
1281       CALL message( 'check_parameters', 'PA0029', 1, 2, 0, 6, 0 )
1282    ENDIF
1283!
1284!-- Check for proper settings for microphysics
1285    IF ( cloud_physics  .AND.  cloud_droplets )  THEN
1286       message_string = 'cloud_physics = .TRUE. is not allowed with ' //  &
1287                        'cloud_droplets = .TRUE.'
1288       CALL message( 'check_parameters', 'PA0442', 1, 2, 0, 6, 0 )
1289    ENDIF
1290
1291!
1292!-- Collision kernels:
1293    SELECT CASE ( TRIM( collision_kernel ) )
1294
1295       CASE ( 'hall', 'hall_fast' )
1296          hall_kernel = .TRUE.
1297
1298       CASE ( 'wang', 'wang_fast' )
1299          wang_kernel = .TRUE.
1300
1301       CASE ( 'none' )
1302
1303
1304       CASE DEFAULT
1305          message_string = 'unknown collision kernel: collision_kernel = "' // &
1306                           TRIM( collision_kernel ) // '"'
1307          CALL message( 'check_parameters', 'PA0350', 1, 2, 0, 6, 0 )
1308
1309    END SELECT
1310    IF ( collision_kernel(6:9) == 'fast' )  use_kernel_tables = .TRUE.
1311
1312    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.            &
1313         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
1314!
1315!--    No restart run: several initialising actions are possible
1316       action = initializing_actions
1317       DO  WHILE ( TRIM( action ) /= '' )
1318          position = INDEX( action, ' ' )
1319          SELECT CASE ( action(1:position-1) )
1320
1321             CASE ( 'set_constant_profiles', 'set_1d-model_profiles',          &
1322                    'by_user', 'initialize_vortex', 'initialize_ptanom',       &
1323                    'inifor' )
1324                action = action(position+1:)
1325
1326             CASE DEFAULT
1327                message_string = 'initializing_action = "' //                  &
1328                                 TRIM( action ) // '" unkown or not allowed'
1329                CALL message( 'check_parameters', 'PA0030', 1, 2, 0, 6, 0 )
1330
1331          END SELECT
1332       ENDDO
1333    ENDIF
1334
1335    IF ( TRIM( initializing_actions ) == 'initialize_vortex'  .AND.            &
1336         conserve_volume_flow ) THEN
1337         message_string = 'initializing_actions = "initialize_vortex"' //      &
1338                        ' is not allowed with conserve_volume_flow = .T.'
1339       CALL message( 'check_parameters', 'PA0343', 1, 2, 0, 6, 0 )
1340    ENDIF
1341
1342
1343    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
1344         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1345       message_string = 'initializing_actions = "set_constant_profiles"' //    &
1346                        ' and "set_1d-model_profiles" are not allowed ' //     &
1347                        'simultaneously'
1348       CALL message( 'check_parameters', 'PA0031', 1, 2, 0, 6, 0 )
1349    ENDIF
1350
1351    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
1352         INDEX( initializing_actions, 'by_user' ) /= 0 )  THEN
1353       message_string = 'initializing_actions = "set_constant_profiles"' //    &
1354                        ' and "by_user" are not allowed simultaneously'
1355       CALL message( 'check_parameters', 'PA0032', 1, 2, 0, 6, 0 )
1356    ENDIF
1357
1358    IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND.                  &
1359         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1360       message_string = 'initializing_actions = "by_user" and ' //             &
1361                        '"set_1d-model_profiles" are not allowed simultaneously'
1362       CALL message( 'check_parameters', 'PA0033', 1, 2, 0, 6, 0 )
1363    ENDIF
1364!
1365!-- In case of nested run assure that all domains are initialized the same
1366!-- way, i.e. if at least at one domain is initialized with soil and
1367!-- atmospheric data provided by COSMO, all domains must be initialized the
1368!-- same way, to assure that soil and atmospheric quantities are
1369!-- consistent.
1370    IF ( nested_run )  THEN
1371       check_nest = .TRUE.
1372#if defined( __parallel )
1373       CALL MPI_ALLREDUCE( TRIM( initializing_actions ) == 'inifor',           &
1374                           check_nest, 1, MPI_LOGICAL,                         &
1375                           MPI_LAND, MPI_COMM_WORLD, ierr )
1376
1377       IF ( TRIM( initializing_actions ) == 'inifor'  .AND.                    &
1378            .NOT.  check_nest )  THEN
1379          message_string = 'In case of nesting, if at least in one ' //        &
1380                           'domain initializing_actions = inifor, '  //        &
1381                           'all domains need to be initialized that way.'
1382          CALL message( 'netcdf_data_input_mod', 'PA0430', 3, 2, 0, 6, 0 )
1383       ENDIF
1384#endif
1385    ENDIF
1386
1387    IF ( cloud_physics  .AND.  .NOT.  humidity )  THEN
1388       WRITE( message_string, * ) 'cloud_physics = ', cloud_physics, ' is ',   &
1389              'not allowed with humidity = ', humidity
1390       CALL message( 'check_parameters', 'PA0034', 1, 2, 0, 6, 0 )
1391    ENDIF
1392
1393    IF ( humidity  .AND.  sloping_surface )  THEN
1394       message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' //   &
1395                        'are not allowed simultaneously'
1396       CALL message( 'check_parameters', 'PA0036', 1, 2, 0, 6, 0 )
1397    ENDIF
1398
1399!
1400!-- When synthetic turbulence generator is used, peform addtional checks
1401    IF ( syn_turb_gen )  CALL stg_check_parameters
1402!
1403!-- When plant canopy model is used, peform addtional checks
1404    IF ( plant_canopy )  CALL pcm_check_parameters
1405
1406!
1407!-- Additional checks for spectra
1408    IF ( calculate_spectra )  CALL spectra_check_parameters
1409!
1410!-- When land surface model is used, perform additional checks
1411    IF ( land_surface )  CALL lsm_check_parameters
1412
1413!
1414!-- When urban surface model is used, perform additional checks
1415    IF ( urban_surface )  CALL usm_check_parameters
1416
1417!
1418!-- If wind turbine model is used, perform additional checks
1419    IF ( wind_turbine )  CALL wtm_check_parameters
1420!
1421!-- When radiation model is used, peform addtional checks
1422    IF ( radiation )  CALL radiation_check_parameters
1423!
1424!-- When gust module is used, perform additional checks
1425    IF ( gust_module_enabled )  CALL gust_check_parameters
1426!
1427!-- When large-scale forcing or nudging is used, peform addtional checks
1428    IF ( large_scale_forcing  .OR.  nudging )  CALL lsf_nudging_check_parameters
1429
1430
1431
1432    IF ( .NOT. ( loop_optimization == 'cache'  .OR.                            &
1433                 loop_optimization == 'vector' )                               &
1434         .AND.  cloud_physics  .AND.  microphysics_seifert )  THEN
1435       message_string = 'cloud_scheme = seifert_beheng requires ' //           &
1436                        'loop_optimization = "cache" or "vector"'
1437       CALL message( 'check_parameters', 'PA0362', 1, 2, 0, 6, 0 )
1438    ENDIF
1439
1440!
1441!-- In case of no model continuation run, check initialising parameters and
1442!-- deduce further quantities
1443    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
1444
1445!
1446!--    Initial profiles for 1D and 3D model, respectively (u,v further below)
1447       pt_init = pt_surface
1448       IF ( humidity       )  q_init  = q_surface
1449       IF ( ocean          )  sa_init = sa_surface
1450       IF ( passive_scalar )  s_init  = s_surface
1451       IF ( air_chemistry )  THEN
1452         DO lsp = 1, nvar
1453            chem_species(lsp)%conc_pr_init = cs_surface(lsp)     
1454         ENDDO
1455       ENDIF
1456!
1457!--
1458!--    If required, compute initial profile of the geostrophic wind
1459!--    (component ug)
1460       i = 1
1461       gradient = 0.0_wp
1462
1463       IF (  .NOT.  ocean )  THEN
1464
1465          ug_vertical_gradient_level_ind(1) = 0
1466          ug(0) = ug_surface
1467          DO  k = 1, nzt+1
1468             IF ( i < 11 )  THEN
1469                IF ( ug_vertical_gradient_level(i) < zu(k)  .AND.              &
1470                     ug_vertical_gradient_level(i) >= 0.0_wp )  THEN
1471                   gradient = ug_vertical_gradient(i) / 100.0_wp
1472                   ug_vertical_gradient_level_ind(i) = k - 1
1473                   i = i + 1
1474                ENDIF
1475             ENDIF
1476             IF ( gradient /= 0.0_wp )  THEN
1477                IF ( k /= 1 )  THEN
1478                   ug(k) = ug(k-1) + dzu(k) * gradient
1479                ELSE
1480                   ug(k) = ug_surface + dzu(k) * gradient
1481                ENDIF
1482             ELSE
1483                ug(k) = ug(k-1)
1484             ENDIF
1485          ENDDO
1486
1487       ELSE
1488
1489          ug_vertical_gradient_level_ind(1) = nzt+1
1490          ug(nzt+1) = ug_surface
1491          DO  k = nzt, nzb, -1
1492             IF ( i < 11 )  THEN
1493                IF ( ug_vertical_gradient_level(i) > zu(k)  .AND.              &
1494                     ug_vertical_gradient_level(i) <= 0.0_wp )  THEN
1495                   gradient = ug_vertical_gradient(i) / 100.0_wp
1496                   ug_vertical_gradient_level_ind(i) = k + 1
1497                   i = i + 1
1498                ENDIF
1499             ENDIF
1500             IF ( gradient /= 0.0_wp )  THEN
1501                IF ( k /= nzt )  THEN
1502                   ug(k) = ug(k+1) - dzu(k+1) * gradient
1503                ELSE
1504                   ug(k)   = ug_surface - 0.5_wp * dzu(k+1) * gradient
1505                   ug(k+1) = ug_surface + 0.5_wp * dzu(k+1) * gradient
1506                ENDIF
1507             ELSE
1508                ug(k) = ug(k+1)
1509             ENDIF
1510          ENDDO
1511
1512       ENDIF
1513
1514!
1515!--    In case of no given gradients for ug, choose a zero gradient
1516       IF ( ug_vertical_gradient_level(1) == -9999999.9_wp )  THEN
1517          ug_vertical_gradient_level(1) = 0.0_wp
1518       ENDIF
1519
1520!
1521!--
1522!--    If required, compute initial profile of the geostrophic wind
1523!--    (component vg)
1524       i = 1
1525       gradient = 0.0_wp
1526
1527       IF (  .NOT.  ocean )  THEN
1528
1529          vg_vertical_gradient_level_ind(1) = 0
1530          vg(0) = vg_surface
1531          DO  k = 1, nzt+1
1532             IF ( i < 11 )  THEN
1533                IF ( vg_vertical_gradient_level(i) < zu(k)  .AND.              &
1534                     vg_vertical_gradient_level(i) >= 0.0_wp )  THEN
1535                   gradient = vg_vertical_gradient(i) / 100.0_wp
1536                   vg_vertical_gradient_level_ind(i) = k - 1
1537                   i = i + 1
1538                ENDIF
1539             ENDIF
1540             IF ( gradient /= 0.0_wp )  THEN
1541                IF ( k /= 1 )  THEN
1542                   vg(k) = vg(k-1) + dzu(k) * gradient
1543                ELSE
1544                   vg(k) = vg_surface + dzu(k) * gradient
1545                ENDIF
1546             ELSE
1547                vg(k) = vg(k-1)
1548             ENDIF
1549          ENDDO
1550
1551       ELSE
1552
1553          vg_vertical_gradient_level_ind(1) = nzt+1
1554          vg(nzt+1) = vg_surface
1555          DO  k = nzt, nzb, -1
1556             IF ( i < 11 )  THEN
1557                IF ( vg_vertical_gradient_level(i) > zu(k)  .AND.              &
1558                     vg_vertical_gradient_level(i) <= 0.0_wp )  THEN
1559                   gradient = vg_vertical_gradient(i) / 100.0_wp
1560                   vg_vertical_gradient_level_ind(i) = k + 1
1561                   i = i + 1
1562                ENDIF
1563             ENDIF
1564             IF ( gradient /= 0.0_wp )  THEN
1565                IF ( k /= nzt )  THEN
1566                   vg(k) = vg(k+1) - dzu(k+1) * gradient
1567                ELSE
1568                   vg(k)   = vg_surface - 0.5_wp * dzu(k+1) * gradient
1569                   vg(k+1) = vg_surface + 0.5_wp * dzu(k+1) * gradient
1570                ENDIF
1571             ELSE
1572                vg(k) = vg(k+1)
1573             ENDIF
1574          ENDDO
1575
1576       ENDIF
1577
1578!
1579!--    In case of no given gradients for vg, choose a zero gradient
1580       IF ( vg_vertical_gradient_level(1) == -9999999.9_wp )  THEN
1581          vg_vertical_gradient_level(1) = 0.0_wp
1582       ENDIF
1583
1584!
1585!--    Let the initial wind profiles be the calculated ug/vg profiles or
1586!--    interpolate them from wind profile data (if given)
1587       IF ( u_profile(1) == 9999999.9_wp  .AND.  v_profile(1) == 9999999.9_wp )  THEN
1588
1589          u_init = ug
1590          v_init = vg
1591
1592       ELSEIF ( u_profile(1) == 0.0_wp  .AND.  v_profile(1) == 0.0_wp )  THEN
1593
1594          IF ( uv_heights(1) /= 0.0_wp )  THEN
1595             message_string = 'uv_heights(1) must be 0.0'
1596             CALL message( 'check_parameters', 'PA0345', 1, 2, 0, 6, 0 )
1597          ENDIF
1598
1599          IF ( omega /= 0.0_wp )  THEN
1600             message_string = 'Coriolis force must be switched off (by setting omega=0.0)' //  &
1601                              ' when prescribing the forcing by u_profile and v_profile'
1602             CALL message( 'check_parameters', 'PA0347', 1, 2, 0, 6, 0 )
1603          ENDIF
1604
1605          use_prescribed_profile_data = .TRUE.
1606
1607          kk = 1
1608          u_init(0) = 0.0_wp
1609          v_init(0) = 0.0_wp
1610
1611          DO  k = 1, nz+1
1612
1613             IF ( kk < 100 )  THEN
1614                DO  WHILE ( uv_heights(kk+1) <= zu(k) )
1615                   kk = kk + 1
1616                   IF ( kk == 100 )  EXIT
1617                ENDDO
1618             ENDIF
1619
1620             IF ( kk < 100  .AND.  uv_heights(kk+1) /= 9999999.9_wp )  THEN
1621                u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
1622                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
1623                                       ( u_profile(kk+1) - u_profile(kk) )
1624                v_init(k) = v_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
1625                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
1626                                       ( v_profile(kk+1) - v_profile(kk) )
1627             ELSE
1628                u_init(k) = u_profile(kk)
1629                v_init(k) = v_profile(kk)
1630             ENDIF
1631
1632          ENDDO
1633
1634       ELSE
1635
1636          message_string = 'u_profile(1) and v_profile(1) must be 0.0'
1637          CALL message( 'check_parameters', 'PA0346', 1, 2, 0, 6, 0 )
1638
1639       ENDIF
1640
1641!
1642!--    Compute initial temperature profile using the given temperature gradients
1643       IF (  .NOT.  neutral )  THEN
1644          CALL init_vertical_profiles( pt_vertical_gradient_level_ind,          &
1645                                       pt_vertical_gradient_level,              &
1646                                       pt_vertical_gradient, pt_init,           &
1647                                       pt_surface, bc_pt_t_val )
1648       ENDIF
1649!
1650!--    Compute initial humidity profile using the given humidity gradients
1651       IF ( humidity )  THEN
1652          CALL init_vertical_profiles( q_vertical_gradient_level_ind,          &
1653                                       q_vertical_gradient_level,              &
1654                                       q_vertical_gradient, q_init,            &
1655                                       q_surface, bc_q_t_val )
1656       ENDIF
1657!
1658!--    Compute initial scalar profile using the given scalar gradients
1659       IF ( passive_scalar )  THEN
1660          CALL init_vertical_profiles( s_vertical_gradient_level_ind,          &
1661                                       s_vertical_gradient_level,              &
1662                                       s_vertical_gradient, s_init,            &
1663                                       s_surface, bc_s_t_val )
1664       ENDIF
1665!
1666!--    Compute initial chemistry profile using the given chemical species gradients
1667       IF ( air_chemistry )  THEN                                                         
1668         DO lsp = 1, nvar
1669          CALL init_vertical_profiles( cs_vertical_gradient_level_ind(lsp,:),  &
1670                                       cs_vertical_gradient_level(lsp,:),      &
1671                                       cs_vertical_gradient(lsp,:),            &
1672                                       chem_species(lsp)%conc_pr_init,         &
1673                                       cs_surface(lsp), bc_cs_t_val(lsp) )
1674         ENDDO
1675       ENDIF
1676!
1677!
1678!--    If required, compute initial salinity profile using the given salinity
1679!--    gradients
1680       IF ( ocean )  THEN
1681          CALL init_vertical_profiles( sa_vertical_gradient_level_ind,          &
1682                                       sa_vertical_gradient_level,              &
1683                                       sa_vertical_gradient, sa_init,           &
1684                                       sa_surface, dum )
1685       ENDIF
1686
1687
1688    ENDIF
1689
1690!
1691!-- Check if the control parameter use_subsidence_tendencies is used correctly
1692    IF ( use_subsidence_tendencies  .AND.  .NOT.  large_scale_subsidence )  THEN
1693       message_string = 'The usage of use_subsidence_tendencies ' //           &
1694                            'requires large_scale_subsidence = .T..'
1695       CALL message( 'check_parameters', 'PA0396', 1, 2, 0, 6, 0 )
1696    ELSEIF ( use_subsidence_tendencies  .AND.  .NOT. large_scale_forcing )  THEN
1697       message_string = 'The usage of use_subsidence_tendencies ' //           &
1698                            'requires large_scale_forcing = .T..'
1699       CALL message( 'check_parameters', 'PA0397', 1, 2, 0, 6, 0 )
1700    ENDIF
1701
1702!
1703!-- Initialize large scale subsidence if required
1704    If ( large_scale_subsidence )  THEN
1705       IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp  .AND.            &
1706                                     .NOT.  large_scale_forcing )  THEN
1707          CALL init_w_subsidence
1708       ENDIF
1709!
1710!--    In case large_scale_forcing is used, profiles for subsidence velocity
1711!--    are read in from file LSF_DATA
1712
1713       IF ( subs_vertical_gradient_level(1) == -9999999.9_wp  .AND.            &
1714            .NOT.  large_scale_forcing )  THEN
1715          message_string = 'There is no default large scale vertical ' //      &
1716                           'velocity profile set. Specify the subsidence ' //  &
1717                           'velocity profile via subs_vertical_gradient ' //   &
1718                           'and subs_vertical_gradient_level.'
1719          CALL message( 'check_parameters', 'PA0380', 1, 2, 0, 6, 0 )
1720       ENDIF
1721    ELSE
1722        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp )  THEN
1723           message_string = 'Enable usage of large scale subsidence by ' //    &
1724                            'setting large_scale_subsidence = .T..'
1725          CALL message( 'check_parameters', 'PA0381', 1, 2, 0, 6, 0 )
1726        ENDIF
1727    ENDIF
1728
1729!
1730!-- Overwrite latitude if necessary and compute Coriolis parameter.
1731!-- To do - move initialization of f and fs to coriolis_mod.
1732    IF ( input_pids_static )  THEN
1733       latitude  = init_model%latitude
1734       longitude = init_model%longitude
1735    ENDIF
1736
1737    f  = 2.0_wp * omega * SIN( latitude / 180.0_wp * pi )
1738    fs = 2.0_wp * omega * COS( latitude / 180.0_wp * pi )
1739
1740!
1741!-- Check and set buoyancy related parameters and switches
1742    IF ( reference_state == 'horizontal_average' )  THEN
1743       CONTINUE
1744    ELSEIF ( reference_state == 'initial_profile' )  THEN
1745       use_initial_profile_as_reference = .TRUE.
1746    ELSEIF ( reference_state == 'single_value' )  THEN
1747       use_single_reference_value = .TRUE.
1748       IF ( pt_reference == 9999999.9_wp )  pt_reference = pt_surface
1749       vpt_reference = pt_reference * ( 1.0_wp + 0.61_wp * q_surface )
1750    ELSE
1751       message_string = 'illegal value for reference_state: "' //              &
1752                        TRIM( reference_state ) // '"'
1753       CALL message( 'check_parameters', 'PA0056', 1, 2, 0, 6, 0 )
1754    ENDIF
1755
1756!
1757!-- Sign of buoyancy/stability terms
1758    IF ( ocean )  atmos_ocean_sign = -1.0_wp
1759
1760!
1761!-- Ocean version must use flux boundary conditions at the top
1762    IF ( ocean .AND. .NOT. use_top_fluxes )  THEN
1763       message_string = 'use_top_fluxes must be .TRUE. in ocean mode'
1764       CALL message( 'check_parameters', 'PA0042', 1, 2, 0, 6, 0 )
1765    ENDIF
1766
1767!
1768!-- In case of a given slope, compute the relevant quantities
1769    IF ( alpha_surface /= 0.0_wp )  THEN
1770       IF ( ABS( alpha_surface ) > 90.0_wp )  THEN
1771          WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface,   &
1772                                     ' ) must be < 90.0'
1773          CALL message( 'check_parameters', 'PA0043', 1, 2, 0, 6, 0 )
1774       ENDIF
1775       sloping_surface = .TRUE.
1776       cos_alpha_surface = COS( alpha_surface / 180.0_wp * pi )
1777       sin_alpha_surface = SIN( alpha_surface / 180.0_wp * pi )
1778    ENDIF
1779
1780!
1781!-- Check time step and cfl_factor
1782    IF ( dt /= -1.0_wp )  THEN
1783       IF ( dt <= 0.0_wp  .AND.  dt /= -1.0_wp )  THEN
1784          WRITE( message_string, * ) 'dt = ', dt , ' <= 0.0'
1785          CALL message( 'check_parameters', 'PA0044', 1, 2, 0, 6, 0 )
1786       ENDIF
1787       dt_3d = dt
1788       dt_fixed = .TRUE.
1789    ENDIF
1790
1791    IF ( cfl_factor <= 0.0_wp  .OR.  cfl_factor > 1.0_wp )  THEN
1792       IF ( cfl_factor == -1.0_wp )  THEN
1793          IF ( timestep_scheme == 'runge-kutta-2' )  THEN
1794             cfl_factor = 0.8_wp
1795          ELSEIF ( timestep_scheme == 'runge-kutta-3' )  THEN
1796             cfl_factor = 0.9_wp
1797          ELSE
1798             cfl_factor = 0.9_wp
1799          ENDIF
1800       ELSE
1801          WRITE( message_string, * ) 'cfl_factor = ', cfl_factor,              &
1802                 ' out of range & 0.0 < cfl_factor <= 1.0 is required'
1803          CALL message( 'check_parameters', 'PA0045', 1, 2, 0, 6, 0 )
1804       ENDIF
1805    ENDIF
1806
1807!
1808!-- Store simulated time at begin
1809    simulated_time_at_begin = simulated_time
1810
1811!
1812!-- Store reference time for coupled runs and change the coupling flag,
1813!-- if ...
1814    IF ( simulated_time == 0.0_wp )  THEN
1815       IF ( coupling_start_time == 0.0_wp )  THEN
1816          time_since_reference_point = 0.0_wp
1817       ELSEIF ( time_since_reference_point < 0.0_wp )  THEN
1818          run_coupled = .FALSE.
1819       ENDIF
1820    ENDIF
1821
1822!
1823!-- Set wind speed in the Galilei-transformed system
1824    IF ( galilei_transformation )  THEN
1825       IF ( use_ug_for_galilei_tr                    .AND.                     &
1826            ug_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
1827            ug_vertical_gradient(1) == 0.0_wp        .AND.                     &
1828            vg_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
1829            vg_vertical_gradient(1) == 0.0_wp )  THEN
1830          u_gtrans = ug_surface * 0.6_wp
1831          v_gtrans = vg_surface * 0.6_wp
1832       ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
1833                ( ug_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
1834                ug_vertical_gradient(1) /= 0.0_wp ) )  THEN
1835          message_string = 'baroclinity (ug) not allowed simultaneously' //    &
1836                           ' with galilei transformation'
1837          CALL message( 'check_parameters', 'PA0046', 1, 2, 0, 6, 0 )
1838       ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
1839                ( vg_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
1840                vg_vertical_gradient(1) /= 0.0_wp ) )  THEN
1841          message_string = 'baroclinity (vg) not allowed simultaneously' //    &
1842                           ' with galilei transformation'
1843          CALL message( 'check_parameters', 'PA0047', 1, 2, 0, 6, 0 )
1844       ELSE
1845          message_string = 'variable translation speed used for galilei-' //   &
1846             'transformation, which may cause & instabilities in stably ' //   &
1847             'stratified regions'
1848          CALL message( 'check_parameters', 'PA0048', 0, 1, 0, 6, 0 )
1849       ENDIF
1850    ENDIF
1851
1852!
1853!-- In case of using a prandtl-layer, calculated (or prescribed) surface
1854!-- fluxes have to be used in the diffusion-terms
1855    IF ( constant_flux_layer )  use_surface_fluxes = .TRUE.
1856
1857!
1858!-- Check boundary conditions and set internal variables:
1859!-- Attention: the lateral boundary conditions have been already checked in
1860!-- parin
1861!
1862!-- Non-cyclic lateral boundaries require the multigrid method and Piascek-
1863!-- Willimas or Wicker - Skamarock advection scheme. Several schemes
1864!-- and tools do not work with non-cyclic boundary conditions.
1865    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1866       IF ( psolver(1:9) /= 'multigrid' )  THEN
1867          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
1868                           'psolver = "' // TRIM( psolver ) // '"'
1869          CALL message( 'check_parameters', 'PA0051', 1, 2, 0, 6, 0 )
1870       ENDIF
1871       IF ( momentum_advec /= 'pw-scheme'  .AND.                               &
1872            momentum_advec /= 'ws-scheme' )  THEN
1873
1874          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
1875                           'momentum_advec = "' // TRIM( momentum_advec ) // '"'
1876          CALL message( 'check_parameters', 'PA0052', 1, 2, 0, 6, 0 )
1877       ENDIF
1878       IF ( scalar_advec /= 'pw-scheme'  .AND.                                 &
1879            scalar_advec /= 'ws-scheme' )  THEN
1880          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
1881                           'scalar_advec = "' // TRIM( scalar_advec ) // '"'
1882          CALL message( 'check_parameters', 'PA0053', 1, 2, 0, 6, 0 )
1883       ENDIF
1884       IF ( galilei_transformation )  THEN
1885          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
1886                           'galilei_transformation = .T.'
1887          CALL message( 'check_parameters', 'PA0054', 1, 2, 0, 6, 0 )
1888       ENDIF
1889    ENDIF
1890
1891!
1892!-- Bottom boundary condition for the turbulent Kinetic energy
1893    IF ( bc_e_b == 'neumann' )  THEN
1894       ibc_e_b = 1
1895    ELSEIF ( bc_e_b == '(u*)**2+neumann' )  THEN
1896       ibc_e_b = 2
1897       IF ( .NOT. constant_flux_layer )  THEN
1898          bc_e_b = 'neumann'
1899          ibc_e_b = 1
1900          message_string = 'boundary condition bc_e_b changed to "' //         &
1901                           TRIM( bc_e_b ) // '"'
1902          CALL message( 'check_parameters', 'PA0057', 0, 1, 0, 6, 0 )
1903       ENDIF
1904    ELSE
1905       message_string = 'unknown boundary condition: bc_e_b = "' //            &
1906                        TRIM( bc_e_b ) // '"'
1907       CALL message( 'check_parameters', 'PA0058', 1, 2, 0, 6, 0 )
1908    ENDIF
1909
1910!
1911!-- Boundary conditions for perturbation pressure
1912    IF ( bc_p_b == 'dirichlet' )  THEN
1913       ibc_p_b = 0
1914    ELSEIF ( bc_p_b == 'neumann' )  THEN
1915       ibc_p_b = 1
1916    ELSE
1917       message_string = 'unknown boundary condition: bc_p_b = "' //            &
1918                        TRIM( bc_p_b ) // '"'
1919       CALL message( 'check_parameters', 'PA0059', 1, 2, 0, 6, 0 )
1920    ENDIF
1921
1922    IF ( bc_p_t == 'dirichlet' )  THEN
1923       ibc_p_t = 0
1924!-- TO_DO: later set bc_p_t to neumann before, in case of nested domain
1925    ELSEIF ( bc_p_t == 'neumann' .OR. bc_p_t == 'nested'  .OR.                 &
1926             bc_p_t == 'forcing'  )  THEN
1927       ibc_p_t = 1
1928    ELSE
1929       message_string = 'unknown boundary condition: bc_p_t = "' //            &
1930                        TRIM( bc_p_t ) // '"'
1931       CALL message( 'check_parameters', 'PA0061', 1, 2, 0, 6, 0 )
1932    ENDIF
1933
1934!
1935!-- Boundary conditions for potential temperature
1936    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
1937       ibc_pt_b = 2
1938    ELSE
1939       IF ( bc_pt_b == 'dirichlet' )  THEN
1940          ibc_pt_b = 0
1941       ELSEIF ( bc_pt_b == 'neumann' )  THEN
1942          ibc_pt_b = 1
1943       ELSE
1944          message_string = 'unknown boundary condition: bc_pt_b = "' //        &
1945                           TRIM( bc_pt_b ) // '"'
1946          CALL message( 'check_parameters', 'PA0062', 1, 2, 0, 6, 0 )
1947       ENDIF
1948    ENDIF
1949
1950    IF ( bc_pt_t == 'dirichlet' )  THEN
1951       ibc_pt_t = 0
1952    ELSEIF ( bc_pt_t == 'neumann' )  THEN
1953       ibc_pt_t = 1
1954    ELSEIF ( bc_pt_t == 'initial_gradient' )  THEN
1955       ibc_pt_t = 2
1956    ELSEIF ( bc_pt_t == 'nested'  .OR.  bc_pt_t == 'forcing' )  THEN
1957       ibc_pt_t = 3
1958    ELSE
1959       message_string = 'unknown boundary condition: bc_pt_t = "' //           &
1960                        TRIM( bc_pt_t ) // '"'
1961       CALL message( 'check_parameters', 'PA0063', 1, 2, 0, 6, 0 )
1962    ENDIF
1963
1964    IF ( ANY( wall_heatflux /= 0.0_wp )  .AND.                        &
1965         surface_heatflux == 9999999.9_wp )  THEN
1966       message_string = 'wall_heatflux additionally requires ' //     &
1967                        'setting of surface_heatflux'
1968       CALL message( 'check_parameters', 'PA0443', 1, 2, 0, 6, 0 )
1969    ENDIF
1970
1971!
1972!   This IF clause needs revision, got too complex!!
1973    IF ( surface_heatflux == 9999999.9_wp  )  THEN
1974       constant_heatflux = .FALSE.
1975       IF ( large_scale_forcing  .OR.  land_surface  .OR.  urban_surface )  THEN
1976          IF ( ibc_pt_b == 0 )  THEN
1977             constant_heatflux = .FALSE.
1978          ELSEIF ( ibc_pt_b == 1 )  THEN
1979             constant_heatflux = .TRUE.
1980             IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.   &
1981                  .NOT.  land_surface )  THEN
1982                surface_heatflux = shf_surf(1)
1983             ELSE
1984                surface_heatflux = 0.0_wp
1985             ENDIF
1986          ENDIF
1987       ENDIF
1988    ELSE
1989        constant_heatflux = .TRUE.
1990        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
1991             large_scale_forcing  .AND.  .NOT.  land_surface )  THEN
1992           surface_heatflux = shf_surf(1)
1993        ENDIF
1994    ENDIF
1995
1996    IF ( top_heatflux     == 9999999.9_wp )  constant_top_heatflux = .FALSE.
1997
1998    IF ( neutral )  THEN
1999
2000       IF ( surface_heatflux /= 0.0_wp  .AND.                                  &
2001            surface_heatflux /= 9999999.9_wp )  THEN
2002          message_string = 'heatflux must not be set for pure neutral flow'
2003          CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
2004       ENDIF
2005
2006       IF ( top_heatflux /= 0.0_wp  .AND.  top_heatflux /= 9999999.9_wp )      &
2007       THEN
2008          message_string = 'heatflux must not be set for pure neutral flow'
2009          CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
2010       ENDIF
2011
2012    ENDIF
2013
2014    IF ( top_momentumflux_u /= 9999999.9_wp  .AND.                             &
2015         top_momentumflux_v /= 9999999.9_wp )  THEN
2016       constant_top_momentumflux = .TRUE.
2017    ELSEIF (  .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.                &
2018           top_momentumflux_v == 9999999.9_wp ) )  THEN
2019       message_string = 'both, top_momentumflux_u AND top_momentumflux_v ' //  &
2020                        'must be set'
2021       CALL message( 'check_parameters', 'PA0064', 1, 2, 0, 6, 0 )
2022    ENDIF
2023
2024!
2025!-- A given surface temperature implies Dirichlet boundary condition for
2026!-- temperature. In this case specification of a constant heat flux is
2027!-- forbidden.
2028    IF ( ibc_pt_b == 0  .AND.  constant_heatflux  .AND.                        &
2029         surface_heatflux /= 0.0_wp )  THEN
2030       message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //&
2031                        '& is not allowed with constant_heatflux = .TRUE.'
2032       CALL message( 'check_parameters', 'PA0065', 1, 2, 0, 6, 0 )
2033    ENDIF
2034    IF ( constant_heatflux  .AND.  pt_surface_initial_change /= 0.0_wp )  THEN
2035       WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo',  &
2036               'wed with pt_surface_initial_change (/=0) = ',                  &
2037               pt_surface_initial_change
2038       CALL message( 'check_parameters', 'PA0066', 1, 2, 0, 6, 0 )
2039    ENDIF
2040
2041!
2042!-- A given temperature at the top implies Dirichlet boundary condition for
2043!-- temperature. In this case specification of a constant heat flux is
2044!-- forbidden.
2045    IF ( ibc_pt_t == 0  .AND.  constant_top_heatflux  .AND.                    &
2046         top_heatflux /= 0.0_wp )  THEN
2047       message_string = 'boundary_condition: bc_pt_t = "' // TRIM( bc_pt_t ) //&
2048                        '" is not allowed with constant_top_heatflux = .TRUE.'
2049       CALL message( 'check_parameters', 'PA0067', 1, 2, 0, 6, 0 )
2050    ENDIF
2051
2052!
2053!-- Boundary conditions for salinity
2054    IF ( ocean )  THEN
2055       IF ( bc_sa_t == 'dirichlet' )  THEN
2056          ibc_sa_t = 0
2057       ELSEIF ( bc_sa_t == 'neumann' )  THEN
2058          ibc_sa_t = 1
2059       ELSE
2060          message_string = 'unknown boundary condition: bc_sa_t = "' //        &
2061                           TRIM( bc_sa_t ) // '"'
2062          CALL message( 'check_parameters', 'PA0068', 1, 2, 0, 6, 0 )
2063       ENDIF
2064
2065       IF ( top_salinityflux == 9999999.9_wp )  constant_top_salinityflux = .FALSE.
2066       IF ( ibc_sa_t == 1  .AND.  top_salinityflux == 9999999.9_wp )  THEN
2067          message_string = 'boundary condition: bc_sa_t = "' //                &
2068                           TRIM( bc_sa_t ) // '" requires to set ' //          &
2069                           'top_salinityflux'
2070          CALL message( 'check_parameters', 'PA0069', 1, 2, 0, 6, 0 )
2071       ENDIF
2072
2073!
2074!--    A fixed salinity at the top implies Dirichlet boundary condition for
2075!--    salinity. In this case specification of a constant salinity flux is
2076!--    forbidden.
2077       IF ( ibc_sa_t == 0  .AND.  constant_top_salinityflux  .AND.             &
2078            top_salinityflux /= 0.0_wp )  THEN
2079          message_string = 'boundary condition: bc_sa_t = "' //                &
2080                           TRIM( bc_sa_t ) // '" is not allowed with ' //      &
2081                           'top_salinityflux /= 0.0'
2082          CALL message( 'check_parameters', 'PA0070', 1, 2, 0, 6, 0 )
2083       ENDIF
2084
2085    ENDIF
2086
2087!
2088!-- Set boundary conditions for total water content
2089    IF ( humidity )  THEN
2090
2091       IF ( ANY( wall_humidityflux /= 0.0_wp )  .AND.                        &
2092            surface_waterflux == 9999999.9_wp )  THEN
2093          message_string = 'wall_humidityflux additionally requires ' //     &
2094                           'setting of surface_waterflux'
2095          CALL message( 'check_parameters', 'PA0444', 1, 2, 0, 6, 0 )
2096       ENDIF
2097
2098       CALL set_bc_scalars( 'q', bc_q_b, bc_q_t, ibc_q_b, ibc_q_t,           &
2099                            'PA0071', 'PA0072' )
2100
2101       IF ( surface_waterflux == 9999999.9_wp  )  THEN
2102          constant_waterflux = .FALSE.
2103          IF ( large_scale_forcing .OR. land_surface )  THEN
2104             IF ( ibc_q_b == 0 )  THEN
2105                constant_waterflux = .FALSE.
2106             ELSEIF ( ibc_q_b == 1 )  THEN
2107                constant_waterflux = .TRUE.
2108                IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
2109                   surface_waterflux = qsws_surf(1)
2110                ENDIF
2111             ENDIF
2112          ENDIF
2113       ELSE
2114          constant_waterflux = .TRUE.
2115          IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.      &
2116               large_scale_forcing )  THEN
2117             surface_waterflux = qsws_surf(1)
2118          ENDIF
2119       ENDIF
2120
2121       CALL check_bc_scalars( 'q', bc_q_b, ibc_q_b, 'PA0073', 'PA0074',        &
2122                              constant_waterflux, q_surface_initial_change )
2123
2124    ENDIF
2125
2126    IF ( passive_scalar )  THEN
2127
2128       IF ( ANY( wall_scalarflux /= 0.0_wp )  .AND.                        &
2129            surface_scalarflux == 9999999.9_wp )  THEN
2130          message_string = 'wall_scalarflux additionally requires ' //     &
2131                           'setting of surface_scalarflux'
2132          CALL message( 'check_parameters', 'PA0445', 1, 2, 0, 6, 0 )
2133       ENDIF
2134
2135       IF ( surface_scalarflux == 9999999.9_wp )  constant_scalarflux = .FALSE.
2136
2137       CALL set_bc_scalars( 's', bc_s_b, bc_s_t, ibc_s_b, ibc_s_t,             &
2138                            'PA0071', 'PA0072' )
2139
2140       CALL check_bc_scalars( 's', bc_s_b, ibc_s_b, 'PA0073', 'PA0074',        &
2141                              constant_scalarflux, s_surface_initial_change )
2142
2143       IF ( top_scalarflux == 9999999.9_wp )  constant_top_scalarflux = .FALSE.
2144!
2145!--    A fixed scalar concentration at the top implies Dirichlet boundary
2146!--    condition for scalar. Hence, in this case specification of a constant
2147!--    scalar flux is forbidden.
2148       IF ( ( ibc_s_t == 0 .OR. ibc_s_t == 2 )  .AND.  constant_top_scalarflux &
2149               .AND.  top_scalarflux /= 0.0_wp )  THEN
2150          message_string = 'boundary condition: bc_s_t = "' //                 &
2151                           TRIM( bc_sa_t ) // '" is not allowed with ' //      &
2152                           'top_scalarflux /= 0.0'
2153          CALL message( 'check_parameters', 'PA0441', 1, 2, 0, 6, 0 )
2154       ENDIF
2155    ENDIF
2156
2157!
2158!-- Boundary conditions for chemical species
2159    IF ( air_chemistry )  CALL chem_boundary_conds( 'init' )
2160
2161!
2162!-- Boundary conditions for horizontal components of wind speed
2163    IF ( bc_uv_b == 'dirichlet' )  THEN
2164       ibc_uv_b = 0
2165    ELSEIF ( bc_uv_b == 'neumann' )  THEN
2166       ibc_uv_b = 1
2167       IF ( constant_flux_layer )  THEN
2168          message_string = 'boundary condition: bc_uv_b = "' //                &
2169               TRIM( bc_uv_b ) // '" is not allowed with constant_flux_layer'  &
2170               // ' = .TRUE.'
2171          CALL message( 'check_parameters', 'PA0075', 1, 2, 0, 6, 0 )
2172       ENDIF
2173    ELSE
2174       message_string = 'unknown boundary condition: bc_uv_b = "' //           &
2175                        TRIM( bc_uv_b ) // '"'
2176       CALL message( 'check_parameters', 'PA0076', 1, 2, 0, 6, 0 )
2177    ENDIF
2178!
2179!-- In case of coupled simulations u and v at the ground in atmosphere will be
2180!-- assigned with the u and v values of the ocean surface
2181    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
2182       ibc_uv_b = 2
2183    ENDIF
2184
2185    IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
2186       bc_uv_t = 'neumann'
2187       ibc_uv_t = 1
2188    ELSE
2189       IF ( bc_uv_t == 'dirichlet' .OR. bc_uv_t == 'dirichlet_0' )  THEN
2190          ibc_uv_t = 0
2191          IF ( bc_uv_t == 'dirichlet_0' )  THEN
2192!
2193!--          Velocities for the initial u,v-profiles are set zero at the top
2194!--          in case of dirichlet_0 conditions
2195             u_init(nzt+1)    = 0.0_wp
2196             v_init(nzt+1)    = 0.0_wp
2197          ENDIF
2198       ELSEIF ( bc_uv_t == 'neumann' )  THEN
2199          ibc_uv_t = 1
2200       ELSEIF ( bc_uv_t == 'nested'  .OR.  bc_uv_t == 'forcing' )  THEN
2201          ibc_uv_t = 3
2202       ELSE
2203          message_string = 'unknown boundary condition: bc_uv_t = "' //        &
2204                           TRIM( bc_uv_t ) // '"'
2205          CALL message( 'check_parameters', 'PA0077', 1, 2, 0, 6, 0 )
2206       ENDIF
2207    ENDIF
2208
2209!
2210!-- Compute and check, respectively, the Rayleigh Damping parameter
2211    IF ( rayleigh_damping_factor == -1.0_wp )  THEN
2212       rayleigh_damping_factor = 0.0_wp
2213    ELSE
2214       IF ( rayleigh_damping_factor < 0.0_wp  .OR.                             &
2215            rayleigh_damping_factor > 1.0_wp )  THEN
2216          WRITE( message_string, * )  'rayleigh_damping_factor = ',            &
2217                              rayleigh_damping_factor, ' out of range [0.0,1.0]'
2218          CALL message( 'check_parameters', 'PA0078', 1, 2, 0, 6, 0 )
2219       ENDIF
2220    ENDIF
2221
2222    IF ( rayleigh_damping_height == -1.0_wp )  THEN
2223       IF (  .NOT.  ocean )  THEN
2224          rayleigh_damping_height = 0.66666666666_wp * zu(nzt)
2225       ELSE
2226          rayleigh_damping_height = 0.66666666666_wp * zu(nzb)
2227       ENDIF
2228    ELSE
2229       IF (  .NOT.  ocean )  THEN
2230          IF ( rayleigh_damping_height < 0.0_wp  .OR.                          &
2231               rayleigh_damping_height > zu(nzt) )  THEN
2232             WRITE( message_string, * )  'rayleigh_damping_height = ',         &
2233                   rayleigh_damping_height, ' out of range [0.0,', zu(nzt), ']'
2234             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
2235          ENDIF
2236       ELSE
2237          IF ( rayleigh_damping_height > 0.0_wp  .OR.                          &
2238               rayleigh_damping_height < zu(nzb) )  THEN
2239             WRITE( message_string, * )  'rayleigh_damping_height = ',         &
2240                   rayleigh_damping_height, ' out of range [0.0,', zu(nzb), ']'
2241             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
2242          ENDIF
2243       ENDIF
2244    ENDIF
2245
2246!
2247!-- Check number of chosen statistic regions
2248    IF ( statistic_regions < 0 )  THEN
2249       WRITE ( message_string, * ) 'number of statistic_regions = ',           &
2250                   statistic_regions+1, ' is not allowed'
2251       CALL message( 'check_parameters', 'PA0082', 1, 2, 0, 6, 0 )
2252    ENDIF
2253    IF ( normalizing_region > statistic_regions  .OR.                          &
2254         normalizing_region < 0)  THEN
2255       WRITE ( message_string, * ) 'normalizing_region = ',                    &
2256                normalizing_region, ' must be >= 0 and <= ',statistic_regions, &
2257                ' (value of statistic_regions)'
2258       CALL message( 'check_parameters', 'PA0083', 1, 2, 0, 6, 0 )
2259    ENDIF
2260
2261!
2262!-- Set the default intervals for data output, if necessary
2263!-- NOTE: dt_dosp has already been set in spectra_parin
2264    IF ( dt_data_output /= 9999999.9_wp )  THEN
2265       IF ( dt_dopr           == 9999999.9_wp )  dt_dopr           = dt_data_output
2266       IF ( dt_dopts          == 9999999.9_wp )  dt_dopts          = dt_data_output
2267       IF ( dt_do2d_xy        == 9999999.9_wp )  dt_do2d_xy        = dt_data_output
2268       IF ( dt_do2d_xz        == 9999999.9_wp )  dt_do2d_xz        = dt_data_output
2269       IF ( dt_do2d_yz        == 9999999.9_wp )  dt_do2d_yz        = dt_data_output
2270       IF ( dt_do3d           == 9999999.9_wp )  dt_do3d           = dt_data_output
2271       IF ( dt_data_output_av == 9999999.9_wp )  dt_data_output_av = dt_data_output
2272       DO  mid = 1, max_masks
2273          IF ( dt_domask(mid) == 9999999.9_wp )  dt_domask(mid)    = dt_data_output
2274       ENDDO
2275    ENDIF
2276
2277!
2278!-- Set the default skip time intervals for data output, if necessary
2279    IF ( skip_time_dopr    == 9999999.9_wp )                                   &
2280                                       skip_time_dopr    = skip_time_data_output
2281    IF ( skip_time_do2d_xy == 9999999.9_wp )                                   &
2282                                       skip_time_do2d_xy = skip_time_data_output
2283    IF ( skip_time_do2d_xz == 9999999.9_wp )                                   &
2284                                       skip_time_do2d_xz = skip_time_data_output
2285    IF ( skip_time_do2d_yz == 9999999.9_wp )                                   &
2286                                       skip_time_do2d_yz = skip_time_data_output
2287    IF ( skip_time_do3d    == 9999999.9_wp )                                   &
2288                                       skip_time_do3d    = skip_time_data_output
2289    IF ( skip_time_data_output_av == 9999999.9_wp )                            &
2290                                skip_time_data_output_av = skip_time_data_output
2291    DO  mid = 1, max_masks
2292       IF ( skip_time_domask(mid) == 9999999.9_wp )                            &
2293                                skip_time_domask(mid)    = skip_time_data_output
2294    ENDDO
2295
2296!
2297!-- Check the average intervals (first for 3d-data, then for profiles)
2298    IF ( averaging_interval > dt_data_output_av )  THEN
2299       WRITE( message_string, * )  'averaging_interval = ',                    &
2300             averaging_interval, ' must be <= dt_data_output = ', dt_data_output
2301       CALL message( 'check_parameters', 'PA0085', 1, 2, 0, 6, 0 )
2302    ENDIF
2303
2304    IF ( averaging_interval_pr == 9999999.9_wp )  THEN
2305       averaging_interval_pr = averaging_interval
2306    ENDIF
2307
2308    IF ( averaging_interval_pr > dt_dopr )  THEN
2309       WRITE( message_string, * )  'averaging_interval_pr = ',                 &
2310             averaging_interval_pr, ' must be <= dt_dopr = ', dt_dopr
2311       CALL message( 'check_parameters', 'PA0086', 1, 2, 0, 6, 0 )
2312    ENDIF
2313
2314!
2315!-- Set the default interval for profiles entering the temporal average
2316    IF ( dt_averaging_input_pr == 9999999.9_wp )  THEN
2317       dt_averaging_input_pr = dt_averaging_input
2318    ENDIF
2319
2320!
2321!-- Set the default interval at which data of vertical profiles shall be output
2322    IF ( dt_dopr_listing == 9999999.9_wp )  THEN
2323       dt_dopr_listing = 0.0_wp
2324    ENDIF
2325
2326!
2327!-- Set the default interval for the output of timeseries to a reasonable
2328!-- value (tries to minimize the number of calls of flow_statistics)
2329    IF ( dt_dots == 9999999.9_wp )  THEN
2330       IF ( averaging_interval_pr == 0.0_wp )  THEN
2331          dt_dots = MIN( dt_run_control, dt_dopr )
2332       ELSE
2333          dt_dots = MIN( dt_run_control, dt_averaging_input_pr )
2334       ENDIF
2335    ENDIF
2336
2337!
2338!-- Check the sample rate for averaging (first for 3d-data, then for profiles)
2339    IF ( dt_averaging_input > averaging_interval )  THEN
2340       WRITE( message_string, * )  'dt_averaging_input = ',                    &
2341                dt_averaging_input, ' must be <= averaging_interval = ',       &
2342                averaging_interval
2343       CALL message( 'check_parameters', 'PA0088', 1, 2, 0, 6, 0 )
2344    ENDIF
2345
2346    IF ( dt_averaging_input_pr > averaging_interval_pr )  THEN
2347       WRITE( message_string, * )  'dt_averaging_input_pr = ',                 &
2348                dt_averaging_input_pr, ' must be <= averaging_interval_pr = ', &
2349                averaging_interval_pr
2350       CALL message( 'check_parameters', 'PA0089', 1, 2, 0, 6, 0 )
2351    ENDIF
2352
2353!
2354!-- Set the default value for the integration interval of precipitation amount
2355    IF ( microphysics_seifert  .OR.  microphysics_kessler )  THEN
2356       IF ( precipitation_amount_interval == 9999999.9_wp )  THEN
2357          precipitation_amount_interval = dt_do2d_xy
2358       ELSE
2359          IF ( precipitation_amount_interval > dt_do2d_xy )  THEN
2360             WRITE( message_string, * )  'precipitation_amount_interval = ',   &
2361                 precipitation_amount_interval, ' must not be larger than ',   &
2362                 'dt_do2d_xy = ', dt_do2d_xy
2363             CALL message( 'check_parameters', 'PA0090', 1, 2, 0, 6, 0 )
2364          ENDIF
2365       ENDIF
2366    ENDIF
2367
2368!
2369!-- Determine the number of output profiles and check whether they are
2370!-- permissible
2371    DO  WHILE ( data_output_pr(dopr_n+1) /= '          ' )
2372
2373       dopr_n = dopr_n + 1
2374       i = dopr_n
2375
2376!
2377!--    Determine internal profile number (for hom, homs)
2378!--    and store height levels
2379       SELECT CASE ( TRIM( data_output_pr(i) ) )
2380
2381          CASE ( 'u', '#u' )
2382             dopr_index(i) = 1
2383             dopr_unit(i)  = 'm/s'
2384             hom(:,2,1,:)  = SPREAD( zu, 2, statistic_regions+1 )
2385             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2386                dopr_initial_index(i) = 5
2387                hom(:,2,5,:)          = SPREAD( zu, 2, statistic_regions+1 )
2388                data_output_pr(i)     = data_output_pr(i)(2:)
2389             ENDIF
2390
2391          CASE ( 'v', '#v' )
2392             dopr_index(i) = 2
2393             dopr_unit(i)  = 'm/s'
2394             hom(:,2,2,:)  = SPREAD( zu, 2, statistic_regions+1 )
2395             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2396                dopr_initial_index(i) = 6
2397                hom(:,2,6,:)          = SPREAD( zu, 2, statistic_regions+1 )
2398                data_output_pr(i)     = data_output_pr(i)(2:)
2399             ENDIF
2400
2401          CASE ( 'w' )
2402             dopr_index(i) = 3
2403             dopr_unit(i)  = 'm/s'
2404             hom(:,2,3,:)  = SPREAD( zw, 2, statistic_regions+1 )
2405
2406          CASE ( 'pt', '#pt' )
2407             IF ( .NOT. cloud_physics ) THEN
2408                dopr_index(i) = 4
2409                dopr_unit(i)  = 'K'
2410                hom(:,2,4,:)  = SPREAD( zu, 2, statistic_regions+1 )
2411                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2412                   dopr_initial_index(i) = 7
2413                   hom(:,2,7,:)          = SPREAD( zu, 2, statistic_regions+1 )
2414                   hom(nzb,2,7,:)        = 0.0_wp    ! because zu(nzb) is negative
2415                   data_output_pr(i)     = data_output_pr(i)(2:)
2416                ENDIF
2417             ELSE
2418                dopr_index(i) = 43
2419                dopr_unit(i)  = 'K'
2420                hom(:,2,43,:)  = SPREAD( zu, 2, statistic_regions+1 )
2421                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2422                   dopr_initial_index(i) = 28
2423                   hom(:,2,28,:)         = SPREAD( zu, 2, statistic_regions+1 )
2424                   hom(nzb,2,28,:)       = 0.0_wp    ! because zu(nzb) is negative
2425                   data_output_pr(i)     = data_output_pr(i)(2:)
2426                ENDIF
2427             ENDIF
2428
2429          CASE ( 'e' )
2430             dopr_index(i)  = 8
2431             dopr_unit(i)   = 'm2/s2'
2432             hom(:,2,8,:)   = SPREAD( zu, 2, statistic_regions+1 )
2433             hom(nzb,2,8,:) = 0.0_wp
2434
2435          CASE ( 'km', '#km' )
2436             dopr_index(i)  = 9
2437             dopr_unit(i)   = 'm2/s'
2438             hom(:,2,9,:)   = SPREAD( zu, 2, statistic_regions+1 )
2439             hom(nzb,2,9,:) = 0.0_wp
2440             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2441                dopr_initial_index(i) = 23
2442                hom(:,2,23,:)         = hom(:,2,9,:)
2443                data_output_pr(i)     = data_output_pr(i)(2:)
2444             ENDIF
2445
2446          CASE ( 'kh', '#kh' )
2447             dopr_index(i)   = 10
2448             dopr_unit(i)    = 'm2/s'
2449             hom(:,2,10,:)   = SPREAD( zu, 2, statistic_regions+1 )
2450             hom(nzb,2,10,:) = 0.0_wp
2451             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2452                dopr_initial_index(i) = 24
2453                hom(:,2,24,:)         = hom(:,2,10,:)
2454                data_output_pr(i)     = data_output_pr(i)(2:)
2455             ENDIF
2456
2457          CASE ( 'l', '#l' )
2458             dopr_index(i)   = 11
2459             dopr_unit(i)    = 'm'
2460             hom(:,2,11,:)   = SPREAD( zu, 2, statistic_regions+1 )
2461             hom(nzb,2,11,:) = 0.0_wp
2462             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2463                dopr_initial_index(i) = 25
2464                hom(:,2,25,:)         = hom(:,2,11,:)
2465                data_output_pr(i)     = data_output_pr(i)(2:)
2466             ENDIF
2467
2468          CASE ( 'w"u"' )
2469             dopr_index(i) = 12
2470             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2471             hom(:,2,12,:) = SPREAD( zw, 2, statistic_regions+1 )
2472             IF ( constant_flux_layer )  hom(nzb,2,12,:) = zu(1)
2473
2474          CASE ( 'w*u*' )
2475             dopr_index(i) = 13
2476             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2477             hom(:,2,13,:) = SPREAD( zw, 2, statistic_regions+1 )
2478
2479          CASE ( 'w"v"' )
2480             dopr_index(i) = 14
2481             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2482             hom(:,2,14,:) = SPREAD( zw, 2, statistic_regions+1 )
2483             IF ( constant_flux_layer )  hom(nzb,2,14,:) = zu(1)
2484
2485          CASE ( 'w*v*' )
2486             dopr_index(i) = 15
2487             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2488             hom(:,2,15,:) = SPREAD( zw, 2, statistic_regions+1 )
2489
2490          CASE ( 'w"pt"' )
2491             dopr_index(i) = 16
2492             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2493             hom(:,2,16,:) = SPREAD( zw, 2, statistic_regions+1 )
2494
2495          CASE ( 'w*pt*' )
2496             dopr_index(i) = 17
2497             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2498             hom(:,2,17,:) = SPREAD( zw, 2, statistic_regions+1 )
2499
2500          CASE ( 'wpt' )
2501             dopr_index(i) = 18
2502             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2503             hom(:,2,18,:) = SPREAD( zw, 2, statistic_regions+1 )
2504
2505          CASE ( 'wu' )
2506             dopr_index(i) = 19
2507             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2508             hom(:,2,19,:) = SPREAD( zw, 2, statistic_regions+1 )
2509             IF ( constant_flux_layer )  hom(nzb,2,19,:) = zu(1)
2510
2511          CASE ( 'wv' )
2512             dopr_index(i) = 20
2513             dopr_unit(i)  = TRIM ( momentumflux_output_unit )
2514             hom(:,2,20,:) = SPREAD( zw, 2, statistic_regions+1 )
2515             IF ( constant_flux_layer )  hom(nzb,2,20,:) = zu(1)
2516
2517          CASE ( 'w*pt*BC' )
2518             dopr_index(i) = 21
2519             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2520             hom(:,2,21,:) = SPREAD( zw, 2, statistic_regions+1 )
2521
2522          CASE ( 'wptBC' )
2523             dopr_index(i) = 22
2524             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2525             hom(:,2,22,:) = SPREAD( zw, 2, statistic_regions+1 )
2526
2527          CASE ( 'sa', '#sa' )
2528             IF ( .NOT. ocean )  THEN
2529                message_string = 'data_output_pr = ' // &
2530                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2531                                 'lemented for ocean = .FALSE.'
2532                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2533             ELSE
2534                dopr_index(i) = 23
2535                dopr_unit(i)  = 'psu'
2536                hom(:,2,23,:) = SPREAD( zu, 2, statistic_regions+1 )
2537                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2538                   dopr_initial_index(i) = 26
2539                   hom(:,2,26,:)         = SPREAD( zu, 2, statistic_regions+1 )
2540                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
2541                   data_output_pr(i)     = data_output_pr(i)(2:)
2542                ENDIF
2543             ENDIF
2544
2545          CASE ( 'u*2' )
2546             dopr_index(i) = 30
2547             dopr_unit(i)  = 'm2/s2'
2548             hom(:,2,30,:) = SPREAD( zu, 2, statistic_regions+1 )
2549
2550          CASE ( 'v*2' )
2551             dopr_index(i) = 31
2552             dopr_unit(i)  = 'm2/s2'
2553             hom(:,2,31,:) = SPREAD( zu, 2, statistic_regions+1 )
2554
2555          CASE ( 'w*2' )
2556             dopr_index(i) = 32
2557             dopr_unit(i)  = 'm2/s2'
2558             hom(:,2,32,:) = SPREAD( zw, 2, statistic_regions+1 )
2559
2560          CASE ( 'pt*2' )
2561             dopr_index(i) = 33
2562             dopr_unit(i)  = 'K2'
2563             hom(:,2,33,:) = SPREAD( zu, 2, statistic_regions+1 )
2564
2565          CASE ( 'e*' )
2566             dopr_index(i) = 34
2567             dopr_unit(i)  = 'm2/s2'
2568             hom(:,2,34,:) = SPREAD( zu, 2, statistic_regions+1 )
2569
2570          CASE ( 'w*2pt*' )
2571             dopr_index(i) = 35
2572             dopr_unit(i)  = 'K m2/s2'
2573             hom(:,2,35,:) = SPREAD( zw, 2, statistic_regions+1 )
2574
2575          CASE ( 'w*pt*2' )
2576             dopr_index(i) = 36
2577             dopr_unit(i)  = 'K2 m/s'
2578             hom(:,2,36,:) = SPREAD( zw, 2, statistic_regions+1 )
2579
2580          CASE ( 'w*e*' )
2581             dopr_index(i) = 37
2582             dopr_unit(i)  = 'm3/s3'
2583             hom(:,2,37,:) = SPREAD( zw, 2, statistic_regions+1 )
2584
2585          CASE ( 'w*3' )
2586             dopr_index(i) = 38
2587             dopr_unit(i)  = 'm3/s3'
2588             hom(:,2,38,:) = SPREAD( zw, 2, statistic_regions+1 )
2589
2590          CASE ( 'Sw' )
2591             dopr_index(i) = 39
2592             dopr_unit(i)  = 'none'
2593             hom(:,2,39,:) = SPREAD( zw, 2, statistic_regions+1 )
2594
2595          CASE ( 'p' )
2596             dopr_index(i) = 40
2597             dopr_unit(i)  = 'Pa'
2598             hom(:,2,40,:) = SPREAD( zu, 2, statistic_regions+1 )
2599
2600          CASE ( 'q', '#q' )
2601             IF ( .NOT. humidity )  THEN
2602                message_string = 'data_output_pr = ' // &
2603                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2604                                 'lemented for humidity = .FALSE.'
2605                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
2606             ELSE
2607                dopr_index(i) = 41
2608                dopr_unit(i)  = 'kg/kg'
2609                hom(:,2,41,:) = SPREAD( zu, 2, statistic_regions+1 )
2610                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2611                   dopr_initial_index(i) = 26
2612                   hom(:,2,26,:)         = SPREAD( zu, 2, statistic_regions+1 )
2613                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
2614                   data_output_pr(i)     = data_output_pr(i)(2:)
2615                ENDIF
2616             ENDIF
2617
2618          CASE ( 's', '#s' )
2619             IF ( .NOT. passive_scalar )  THEN
2620                message_string = 'data_output_pr = ' //                        &
2621                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2622                                 'lemented for passive_scalar = .FALSE.'
2623                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
2624             ELSE
2625                dopr_index(i) = 115
2626                dopr_unit(i)  = 'kg/m3'
2627                hom(:,2,115,:) = SPREAD( zu, 2, statistic_regions+1 )
2628                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2629                   dopr_initial_index(i) = 121
2630                   hom(:,2,121,:)        = SPREAD( zu, 2, statistic_regions+1 )
2631                   hom(nzb,2,121,:)      = 0.0_wp    ! because zu(nzb) is negative
2632                   data_output_pr(i)     = data_output_pr(i)(2:)
2633                ENDIF
2634             ENDIF
2635
2636          CASE ( 'qv', '#qv' )
2637             IF ( .NOT. cloud_physics ) THEN
2638                dopr_index(i) = 41
2639                dopr_unit(i)  = 'kg/kg'
2640                hom(:,2,41,:) = SPREAD( zu, 2, statistic_regions+1 )
2641                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2642                   dopr_initial_index(i) = 26
2643                   hom(:,2,26,:)         = SPREAD( zu, 2, statistic_regions+1 )
2644                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
2645                   data_output_pr(i)     = data_output_pr(i)(2:)
2646                ENDIF
2647             ELSE
2648                dopr_index(i) = 42
2649                dopr_unit(i)  = 'kg/kg'
2650                hom(:,2,42,:) = SPREAD( zu, 2, statistic_regions+1 )
2651                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2652                   dopr_initial_index(i) = 27
2653                   hom(:,2,27,:)         = SPREAD( zu, 2, statistic_regions+1 )
2654                   hom(nzb,2,27,:)       = 0.0_wp   ! because zu(nzb) is negative
2655                   data_output_pr(i)     = data_output_pr(i)(2:)
2656                ENDIF
2657             ENDIF
2658
2659          CASE ( 'lpt', '#lpt' )
2660             IF ( .NOT. cloud_physics ) THEN
2661                message_string = 'data_output_pr = ' //                        &
2662                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2663                                 'lemented for cloud_physics = .FALSE.'
2664                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
2665             ELSE
2666                dopr_index(i) = 4
2667                dopr_unit(i)  = 'K'
2668                hom(:,2,4,:)  = SPREAD( zu, 2, statistic_regions+1 )
2669                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2670                   dopr_initial_index(i) = 7
2671                   hom(:,2,7,:)          = SPREAD( zu, 2, statistic_regions+1 )
2672                   hom(nzb,2,7,:)        = 0.0_wp    ! because zu(nzb) is negative
2673                   data_output_pr(i)     = data_output_pr(i)(2:)
2674                ENDIF
2675             ENDIF
2676
2677          CASE ( 'vpt', '#vpt' )
2678             dopr_index(i) = 44
2679             dopr_unit(i)  = 'K'
2680             hom(:,2,44,:) = SPREAD( zu, 2, statistic_regions+1 )
2681             IF ( data_output_pr(i)(1:1) == '#' )  THEN
2682                dopr_initial_index(i) = 29
2683                hom(:,2,29,:)         = SPREAD( zu, 2, statistic_regions+1 )
2684                hom(nzb,2,29,:)       = 0.0_wp    ! because zu(nzb) is negative
2685                data_output_pr(i)     = data_output_pr(i)(2:)
2686             ENDIF
2687
2688          CASE ( 'w"vpt"' )
2689             dopr_index(i) = 45
2690             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2691             hom(:,2,45,:) = SPREAD( zw, 2, statistic_regions+1 )
2692
2693          CASE ( 'w*vpt*' )
2694             dopr_index(i) = 46
2695             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2696             hom(:,2,46,:) = SPREAD( zw, 2, statistic_regions+1 )
2697
2698          CASE ( 'wvpt' )
2699             dopr_index(i) = 47
2700             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2701             hom(:,2,47,:) = SPREAD( zw, 2, statistic_regions+1 )
2702
2703          CASE ( 'w"q"' )
2704             IF (  .NOT.  humidity )  THEN
2705                message_string = 'data_output_pr = ' //                        &
2706                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2707                                 'lemented for humidity = .FALSE.'
2708                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
2709             ELSE
2710                dopr_index(i) = 48
2711                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2712                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
2713             ENDIF
2714
2715          CASE ( 'w*q*' )
2716             IF (  .NOT.  humidity )  THEN
2717                message_string = 'data_output_pr = ' //                        &
2718                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2719                                 'lemented for humidity = .FALSE.'
2720                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
2721             ELSE
2722                dopr_index(i) = 49
2723                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2724                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
2725             ENDIF
2726
2727          CASE ( 'wq' )
2728             IF (  .NOT.  humidity )  THEN
2729                message_string = 'data_output_pr = ' //                        &
2730                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2731                                 'lemented for humidity = .FALSE.'
2732                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
2733             ELSE
2734                dopr_index(i) = 50
2735                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2736                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
2737             ENDIF
2738
2739          CASE ( 'w"s"' )
2740             IF (  .NOT.  passive_scalar )  THEN
2741                message_string = 'data_output_pr = ' //                        &
2742                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2743                                 'lemented for passive_scalar = .FALSE.'
2744                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
2745             ELSE
2746                dopr_index(i) = 117
2747                dopr_unit(i)  = 'kg/m3 m/s'
2748                hom(:,2,117,:) = SPREAD( zw, 2, statistic_regions+1 )
2749             ENDIF
2750
2751          CASE ( 'w*s*' )
2752             IF (  .NOT.  passive_scalar )  THEN
2753                message_string = 'data_output_pr = ' //                        &
2754                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2755                                 'lemented for passive_scalar = .FALSE.'
2756                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
2757             ELSE
2758                dopr_index(i) = 114
2759                dopr_unit(i)  = 'kg/m3 m/s'
2760                hom(:,2,114,:) = SPREAD( zw, 2, statistic_regions+1 )
2761             ENDIF
2762
2763          CASE ( 'ws' )
2764             IF (  .NOT.  passive_scalar )  THEN
2765                message_string = 'data_output_pr = ' //                        &
2766                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2767                                 'lemented for passive_scalar = .FALSE.'
2768                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
2769             ELSE
2770                dopr_index(i) = 118
2771                dopr_unit(i)  = 'kg/m3 m/s'
2772                hom(:,2,118,:) = SPREAD( zw, 2, statistic_regions+1 )
2773             ENDIF
2774
2775          CASE ( 'w"qv"' )
2776             IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
2777                dopr_index(i) = 48
2778                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2779                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
2780             ELSEIF ( humidity  .AND.  cloud_physics )  THEN
2781                dopr_index(i) = 51
2782                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2783                hom(:,2,51,:) = SPREAD( zw, 2, statistic_regions+1 )
2784             ELSE
2785                message_string = 'data_output_pr = ' //                        &
2786                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2787                                 'lemented for cloud_physics = .FALSE. an&' // &
2788                                 'd humidity = .FALSE.'
2789                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
2790             ENDIF
2791
2792          CASE ( 'w*qv*' )
2793             IF ( humidity  .AND.  .NOT. cloud_physics )                       &
2794             THEN
2795                dopr_index(i) = 49
2796                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2797                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
2798             ELSEIF( humidity .AND. cloud_physics ) THEN
2799                dopr_index(i) = 52
2800                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2801                hom(:,2,52,:) = SPREAD( zw, 2, statistic_regions+1 )
2802             ELSE
2803                message_string = 'data_output_pr = ' //                        &
2804                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2805                                 'lemented for cloud_physics = .FALSE. an&' // &
2806                                 'd humidity = .FALSE.'
2807                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
2808             ENDIF
2809
2810          CASE ( 'wqv' )
2811             IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
2812                dopr_index(i) = 50
2813                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2814                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
2815             ELSEIF ( humidity  .AND.  cloud_physics )  THEN
2816                dopr_index(i) = 53
2817                dopr_unit(i)  = TRIM ( waterflux_output_unit )
2818                hom(:,2,53,:) = SPREAD( zw, 2, statistic_regions+1 )
2819             ELSE
2820                message_string = 'data_output_pr = ' //                        &
2821                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2822                                 'lemented for cloud_physics = .FALSE. an&' // &
2823                                 'd humidity = .FALSE.'
2824                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
2825             ENDIF
2826
2827          CASE ( 'ql' )
2828             IF (  .NOT.  cloud_physics  .AND.  .NOT.  cloud_droplets )  THEN
2829                message_string = 'data_output_pr = ' //                        &
2830                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2831                                 'lemented for cloud_physics = .FALSE. or'  // &
2832                                 '&cloud_droplets = .FALSE.'
2833                CALL message( 'check_parameters', 'PA0096', 1, 2, 0, 6, 0 )
2834             ELSE
2835                dopr_index(i) = 54
2836                dopr_unit(i)  = 'kg/kg'
2837                hom(:,2,54,:)  = SPREAD( zu, 2, statistic_regions+1 )
2838             ENDIF
2839
2840          CASE ( 'w*u*u*:dz' )
2841             dopr_index(i) = 55
2842             dopr_unit(i)  = 'm2/s3'
2843             hom(:,2,55,:) = SPREAD( zu, 2, statistic_regions+1 )
2844
2845          CASE ( 'w*p*:dz' )
2846             dopr_index(i) = 56
2847             dopr_unit(i)  = 'm2/s3'
2848             hom(:,2,56,:) = SPREAD( zw, 2, statistic_regions+1 )
2849
2850          CASE ( 'w"e:dz' )
2851             dopr_index(i) = 57
2852             dopr_unit(i)  = 'm2/s3'
2853             hom(:,2,57,:) = SPREAD( zu, 2, statistic_regions+1 )
2854
2855
2856          CASE ( 'u"pt"' )
2857             dopr_index(i) = 58
2858             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2859             hom(:,2,58,:) = SPREAD( zu, 2, statistic_regions+1 )
2860
2861          CASE ( 'u*pt*' )
2862             dopr_index(i) = 59
2863             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2864             hom(:,2,59,:) = SPREAD( zu, 2, statistic_regions+1 )
2865
2866          CASE ( 'upt_t' )
2867             dopr_index(i) = 60
2868             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2869             hom(:,2,60,:) = SPREAD( zu, 2, statistic_regions+1 )
2870
2871          CASE ( 'v"pt"' )
2872             dopr_index(i) = 61
2873             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2874             hom(:,2,61,:) = SPREAD( zu, 2, statistic_regions+1 )
2875
2876          CASE ( 'v*pt*' )
2877             dopr_index(i) = 62
2878             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2879             hom(:,2,62,:) = SPREAD( zu, 2, statistic_regions+1 )
2880
2881          CASE ( 'vpt_t' )
2882             dopr_index(i) = 63
2883             dopr_unit(i)  = TRIM ( heatflux_output_unit )
2884             hom(:,2,63,:) = SPREAD( zu, 2, statistic_regions+1 )
2885
2886          CASE ( 'rho_ocean' )
2887             IF (  .NOT.  ocean ) THEN
2888                message_string = 'data_output_pr = ' //                        &
2889                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2890                                 'lemented for ocean = .FALSE.'
2891                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2892             ELSE
2893                dopr_index(i) = 64
2894                dopr_unit(i)  = 'kg/m3'
2895                hom(:,2,64,:) = SPREAD( zu, 2, statistic_regions+1 )
2896                IF ( data_output_pr(i)(1:1) == '#' )  THEN
2897                   dopr_initial_index(i) = 77
2898                   hom(:,2,77,:)         = SPREAD( zu, 2, statistic_regions+1 )
2899                   hom(nzb,2,77,:)       = 0.0_wp    ! because zu(nzb) is negative
2900                   data_output_pr(i)     = data_output_pr(i)(2:)
2901                ENDIF
2902             ENDIF
2903
2904          CASE ( 'w"sa"' )
2905             IF (  .NOT.  ocean ) THEN
2906                message_string = 'data_output_pr = ' //                        &
2907                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2908                                 'lemented for ocean = .FALSE.'
2909                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2910             ELSE
2911                dopr_index(i) = 65
2912                dopr_unit(i)  = 'psu m/s'
2913                hom(:,2,65,:) = SPREAD( zw, 2, statistic_regions+1 )
2914             ENDIF
2915
2916          CASE ( 'w*sa*' )
2917             IF (  .NOT. ocean  ) THEN
2918                message_string = 'data_output_pr = ' //                        &
2919                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2920                                 'lemented for ocean = .FALSE.'
2921                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2922             ELSE
2923                dopr_index(i) = 66
2924                dopr_unit(i)  = 'psu m/s'
2925                hom(:,2,66,:) = SPREAD( zw, 2, statistic_regions+1 )
2926             ENDIF
2927
2928          CASE ( 'wsa' )
2929             IF (  .NOT.  ocean ) THEN
2930                message_string = 'data_output_pr = ' //                        &
2931                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2932                                 'lemented for ocean = .FALSE.'
2933                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2934             ELSE
2935                dopr_index(i) = 67
2936                dopr_unit(i)  = 'psu m/s'
2937                hom(:,2,67,:) = SPREAD( zw, 2, statistic_regions+1 )
2938             ENDIF
2939
2940          CASE ( 'w*p*' )
2941             dopr_index(i) = 68
2942             dopr_unit(i)  = 'm3/s3'
2943             hom(:,2,68,:) = SPREAD( zu, 2, statistic_regions+1 )
2944
2945          CASE ( 'w"e' )
2946             dopr_index(i) = 69
2947             dopr_unit(i)  = 'm3/s3'
2948             hom(:,2,69,:) = SPREAD( zu, 2, statistic_regions+1 )
2949
2950          CASE ( 'q*2' )
2951             IF (  .NOT.  humidity )  THEN
2952                message_string = 'data_output_pr = ' //                        &
2953                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2954                                 'lemented for humidity = .FALSE.'
2955                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
2956             ELSE
2957                dopr_index(i) = 70
2958                dopr_unit(i)  = 'kg2/kg2'
2959                hom(:,2,70,:) = SPREAD( zu, 2, statistic_regions+1 )
2960             ENDIF
2961
2962          CASE ( 'prho' )
2963             IF (  .NOT.  ocean ) THEN
2964                message_string = 'data_output_pr = ' //                        &
2965                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2966                                 'lemented for ocean = .FALSE.'
2967                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
2968             ELSE
2969                dopr_index(i) = 71
2970                dopr_unit(i)  = 'kg/m3'
2971                hom(:,2,71,:) = SPREAD( zu, 2, statistic_regions+1 )
2972             ENDIF
2973
2974          CASE ( 'hyp' )
2975             dopr_index(i) = 72
2976             dopr_unit(i)  = 'hPa'
2977             hom(:,2,72,:) = SPREAD( zu, 2, statistic_regions+1 )
2978
2979          CASE ( 'rho_air' )
2980             dopr_index(i)  = 119
2981             dopr_unit(i)   = 'kg/m3'
2982             hom(:,2,119,:) = SPREAD( zu, 2, statistic_regions+1 )
2983
2984          CASE ( 'rho_air_zw' )
2985             dopr_index(i)  = 120
2986             dopr_unit(i)   = 'kg/m3'
2987             hom(:,2,120,:) = SPREAD( zw, 2, statistic_regions+1 )
2988
2989          CASE ( 'nc' )
2990             IF (  .NOT.  cloud_physics )  THEN
2991                message_string = 'data_output_pr = ' //                        &
2992                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2993                                 'lemented for cloud_physics = .FALSE.'
2994                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
2995             ELSEIF ( .NOT.  microphysics_morrison )  THEN
2996                message_string = 'data_output_pr = ' //                        &
2997                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2998                                 'lemented for cloud_scheme /= morrison'
2999                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
3000             ELSE
3001                dopr_index(i) = 89
3002                dopr_unit(i)  = '1/m3'
3003                hom(:,2,89,:)  = SPREAD( zu, 2, statistic_regions+1 )
3004             ENDIF
3005
3006          CASE ( 'nr' )
3007             IF (  .NOT.  cloud_physics )  THEN
3008                message_string = 'data_output_pr = ' //                        &
3009                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3010                                 'lemented for cloud_physics = .FALSE.'
3011                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
3012             ELSEIF ( .NOT.  microphysics_seifert )  THEN
3013                message_string = 'data_output_pr = ' //                        &
3014                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3015                                 'lemented for cloud_scheme /= seifert_beheng'
3016                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
3017             ELSE
3018                dopr_index(i) = 73
3019                dopr_unit(i)  = '1/m3'
3020                hom(:,2,73,:)  = SPREAD( zu, 2, statistic_regions+1 )
3021             ENDIF
3022
3023          CASE ( 'qr' )
3024             IF (  .NOT.  cloud_physics )  THEN
3025                message_string = 'data_output_pr = ' //                        &
3026                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3027                                 'lemented for cloud_physics = .FALSE.'
3028                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
3029             ELSEIF ( .NOT.  microphysics_seifert )  THEN
3030                message_string = 'data_output_pr = ' //                        &
3031                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3032                                 'lemented for cloud_scheme /= seifert_beheng'
3033                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
3034             ELSE
3035                dopr_index(i) = 74
3036                dopr_unit(i)  = 'kg/kg'
3037                hom(:,2,74,:)  = SPREAD( zu, 2, statistic_regions+1 )
3038             ENDIF
3039
3040          CASE ( 'qc' )
3041             IF (  .NOT.  cloud_physics )  THEN
3042                message_string = 'data_output_pr = ' //                        &
3043                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3044                                 'lemented for cloud_physics = .FALSE.'
3045                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
3046             ELSE
3047                dopr_index(i) = 75
3048                dopr_unit(i)  = 'kg/kg'
3049                hom(:,2,75,:)  = SPREAD( zu, 2, statistic_regions+1 )
3050             ENDIF
3051
3052          CASE ( 'prr' )
3053             IF (  .NOT.  cloud_physics )  THEN
3054                message_string = 'data_output_pr = ' //                        &
3055                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3056                                 'lemented for cloud_physics = .FALSE.'
3057                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
3058             ELSEIF ( microphysics_sat_adjust )  THEN
3059                message_string = 'data_output_pr = ' //                        &
3060                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
3061                                 'ilable for cloud_scheme = saturation_adjust'
3062                CALL message( 'check_parameters', 'PA0422', 1, 2, 0, 6, 0 )
3063             ELSE
3064                dopr_index(i) = 76
3065                dopr_unit(i)  = 'kg/kg m/s'
3066                hom(:,2,76,:)  = SPREAD( zu, 2, statistic_regions+1 )
3067             ENDIF
3068
3069          CASE ( 'ug' )
3070             dopr_index(i) = 78
3071             dopr_unit(i)  = 'm/s'
3072             hom(:,2,78,:) = SPREAD( zu, 2, statistic_regions+1 )
3073
3074          CASE ( 'vg' )
3075             dopr_index(i) = 79
3076             dopr_unit(i)  = 'm/s'
3077             hom(:,2,79,:) = SPREAD( zu, 2, statistic_regions+1 )
3078
3079          CASE ( 'w_subs' )
3080             IF (  .NOT.  large_scale_subsidence )  THEN
3081                message_string = 'data_output_pr = ' //                        &
3082                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3083                                 'lemented for large_scale_subsidence = .FALSE.'
3084                CALL message( 'check_parameters', 'PA0382', 1, 2, 0, 6, 0 )
3085             ELSE
3086                dopr_index(i) = 80
3087                dopr_unit(i)  = 'm/s'
3088                hom(:,2,80,:) = SPREAD( zu, 2, statistic_regions+1 )
3089             ENDIF
3090
3091          CASE ( 's*2' )
3092             IF (  .NOT.  passive_scalar )  THEN
3093                message_string = 'data_output_pr = ' //                        &
3094                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
3095                                 'lemented for passive_scalar = .FALSE.'
3096                CALL message( 'check_parameters', 'PA0185', 1, 2, 0, 6, 0 )
3097             ELSE
3098                dopr_index(i) = 116
3099                dopr_unit(i)  = 'kg2/m6'
3100                hom(:,2,116,:) = SPREAD( zu, 2, statistic_regions+1 )
3101             ENDIF
3102
3103
3104
3105          CASE DEFAULT
3106
3107             CALL lsm_check_data_output_pr( data_output_pr(i), i, unit,        &
3108                                            dopr_unit(i) )
3109
3110             IF ( unit == 'illegal' )  THEN
3111                CALL lsf_nudging_check_data_output_pr( data_output_pr(i), i,   &
3112                                                    unit, dopr_unit(i) )
3113             ENDIF
3114
3115             IF ( unit == 'illegal' )  THEN
3116                CALL radiation_check_data_output_pr( data_output_pr(i), i,     &
3117                                                     unit, dopr_unit(i) )
3118             ENDIF
3119!
3120!--          Block of gust module profile outputs
3121             IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
3122                   CALL gust_check_data_output_pr( data_output_pr(i), i, unit, &
3123                                                   dopr_unit(i) )
3124             ENDIF
3125
3126             IF ( unit == 'illegal' )  THEN                                       
3127                CALL chem_check_data_output_pr( data_output_pr(i), i,          &
3128                                                unit, dopr_unit(i) )
3129             ENDIF
3130
3131             IF ( unit == 'illegal' )  THEN
3132                unit = ''
3133                CALL user_check_data_output_pr( data_output_pr(i), i, unit )
3134             ENDIF
3135
3136             IF ( unit == 'illegal' )  THEN
3137                IF ( data_output_pr_user(1) /= ' ' )  THEN
3138                   message_string = 'illegal value for data_output_pr or ' //  &
3139                                    'data_output_pr_user = "' //               &
3140                                    TRIM( data_output_pr(i) ) // '"'
3141                   CALL message( 'check_parameters', 'PA0097', 1, 2, 0, 6, 0 )
3142                ELSE
3143                   message_string = 'illegal value for data_output_pr = "' //  &
3144                                    TRIM( data_output_pr(i) ) // '"'
3145                   CALL message( 'check_parameters', 'PA0098', 1, 2, 0, 6, 0 )
3146                ENDIF
3147             ENDIF
3148
3149       END SELECT
3150
3151    ENDDO
3152
3153
3154!
3155!-- Append user-defined data output variables to the standard data output
3156    IF ( data_output_user(1) /= ' ' )  THEN
3157       i = 1
3158       DO  WHILE ( data_output(i) /= ' '  .AND.  i <= 500 )
3159          i = i + 1
3160       ENDDO
3161       j = 1
3162       DO  WHILE ( data_output_user(j) /= ' '  .AND.  j <= 500 )
3163          IF ( i > 500 )  THEN
3164             message_string = 'number of output quantitities given by data' // &
3165                '_output and data_output_user exceeds the limit of 500'
3166             CALL message( 'check_parameters', 'PA0102', 1, 2, 0, 6, 0 )
3167          ENDIF
3168          data_output(i) = data_output_user(j)
3169          i = i + 1
3170          j = j + 1
3171       ENDDO
3172    ENDIF
3173
3174!
3175!-- Check and set steering parameters for 2d/3d data output and averaging
3176    i   = 1
3177    DO  WHILE ( data_output(i) /= ' '  .AND.  i <= 500 )
3178!
3179!--    Check for data averaging
3180       ilen = LEN_TRIM( data_output(i) )
3181       j = 0                                                 ! no data averaging
3182       IF ( ilen > 3 )  THEN
3183          IF ( data_output(i)(ilen-2:ilen) == '_av' )  THEN
3184             j = 1                                           ! data averaging
3185             data_output(i) = data_output(i)(1:ilen-3)
3186          ENDIF
3187       ENDIF
3188!
3189!--    Check for cross section or volume data
3190       ilen = LEN_TRIM( data_output(i) )
3191       k = 0                                                   ! 3d data
3192       var = data_output(i)(1:ilen)
3193       IF ( ilen > 3 )  THEN
3194          IF ( data_output(i)(ilen-2:ilen) == '_xy'  .OR.                      &
3195               data_output(i)(ilen-2:ilen) == '_xz'  .OR.                      &
3196               data_output(i)(ilen-2:ilen) == '_yz' )  THEN
3197             k = 1                                             ! 2d data
3198             var = data_output(i)(1:ilen-3)
3199          ENDIF
3200       ENDIF
3201
3202!
3203!--    Check for allowed value and set units
3204       SELECT CASE ( TRIM( var ) )
3205
3206          CASE ( 'e' )
3207             IF ( constant_diffusion )  THEN
3208                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3209                                 'res constant_diffusion = .FALSE.'
3210                CALL message( 'check_parameters', 'PA0103', 1, 2, 0, 6, 0 )
3211             ENDIF
3212             unit = 'm2/s2'
3213
3214          CASE ( 'lpt' )
3215             IF (  .NOT.  cloud_physics )  THEN
3216                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3217                         'res cloud_physics = .TRUE.'
3218                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3219             ENDIF
3220             unit = 'K'
3221
3222          CASE ( 'nc' )
3223             IF (  .NOT.  cloud_physics )  THEN
3224                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3225                         'res cloud_physics = .TRUE.'
3226                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3227             ELSEIF ( .NOT.  microphysics_morrison )  THEN
3228                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3229                         'res = microphysics morrison '
3230                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
3231             ENDIF
3232             unit = '1/m3'
3233
3234          CASE ( 'nr' )
3235             IF (  .NOT.  cloud_physics )  THEN
3236                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3237                         'res cloud_physics = .TRUE.'
3238                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3239             ELSEIF ( .NOT.  microphysics_seifert )  THEN
3240                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3241                         'res cloud_scheme = seifert_beheng'
3242                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
3243             ENDIF
3244             unit = '1/m3'
3245
3246          CASE ( 'pc', 'pr' )
3247             IF (  .NOT.  particle_advection )  THEN
3248                message_string = 'output of "' // TRIM( var ) // '" requir' // &
3249                   'es a "particles_par"-NAMELIST in the parameter file (PARIN)'
3250                CALL message( 'check_parameters', 'PA0104', 1, 2, 0, 6, 0 )
3251             ENDIF
3252             IF ( TRIM( var ) == 'pc' )  unit = 'number'
3253             IF ( TRIM( var ) == 'pr' )  unit = 'm'
3254
3255          CASE ( 'prr' )
3256             IF (  .NOT.  cloud_physics )  THEN
3257                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3258                         'res cloud_physics = .TRUE.'
3259                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3260             ELSEIF ( microphysics_sat_adjust )  THEN
3261                message_string = 'output of "' // TRIM( var ) // '" is ' //  &
3262                         'not available for cloud_scheme = saturation_adjust'
3263                CALL message( 'check_parameters', 'PA0423', 1, 2, 0, 6, 0 )
3264             ENDIF
3265             unit = 'kg/kg m/s'
3266
3267          CASE ( 'q', 'vpt' )
3268             IF (  .NOT.  humidity )  THEN
3269                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3270                                 'res humidity = .TRUE.'
3271                CALL message( 'check_parameters', 'PA0105', 1, 2, 0, 6, 0 )
3272             ENDIF
3273             IF ( TRIM( var ) == 'q'   )  unit = 'kg/kg'
3274             IF ( TRIM( var ) == 'vpt' )  unit = 'K'
3275
3276          CASE ( 'qc' )
3277             IF (  .NOT.  cloud_physics )  THEN
3278                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3279                         'res cloud_physics = .TRUE.'
3280                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3281             ENDIF
3282             unit = 'kg/kg'
3283
3284          CASE ( 'ql' )
3285             IF ( .NOT.  ( cloud_physics  .OR.  cloud_droplets ) )  THEN
3286                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3287                         'res cloud_physics = .TRUE. or cloud_droplets = .TRUE.'
3288                CALL message( 'check_parameters', 'PA0106', 1, 2, 0, 6, 0 )
3289             ENDIF
3290             unit = 'kg/kg'
3291
3292          CASE ( 'ql_c', 'ql_v', 'ql_vp' )
3293             IF (  .NOT.  cloud_droplets )  THEN
3294                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3295                                 'res cloud_droplets = .TRUE.'
3296                CALL message( 'check_parameters', 'PA0107', 1, 2, 0, 6, 0 )
3297             ENDIF
3298             IF ( TRIM( var ) == 'ql_c'  )  unit = 'kg/kg'
3299             IF ( TRIM( var ) == 'ql_v'  )  unit = 'm3'
3300             IF ( TRIM( var ) == 'ql_vp' )  unit = 'none'
3301
3302          CASE ( 'qr' )
3303             IF (  .NOT.  cloud_physics )  THEN
3304                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3305                         'res cloud_physics = .TRUE.'
3306                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3307             ELSEIF ( .NOT.  microphysics_seifert ) THEN
3308                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3309                         'res cloud_scheme = seifert_beheng'
3310                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
3311             ENDIF
3312             unit = 'kg/kg'
3313
3314          CASE ( 'qv' )
3315             IF (  .NOT.  cloud_physics )  THEN
3316                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3317                                 'res cloud_physics = .TRUE.'
3318                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3319             ENDIF
3320             unit = 'kg/kg'
3321
3322          CASE ( 'rho_ocean' )
3323             IF (  .NOT.  ocean )  THEN
3324                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3325                                 'res ocean = .TRUE.'
3326                CALL message( 'check_parameters', 'PA0109', 1, 2, 0, 6, 0 )
3327             ENDIF
3328             unit = 'kg/m3'
3329
3330          CASE ( 's' )
3331             IF (  .NOT.  passive_scalar )  THEN
3332                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3333                                 'res passive_scalar = .TRUE.'
3334                CALL message( 'check_parameters', 'PA0110', 1, 2, 0, 6, 0 )
3335             ENDIF
3336             unit = 'kg/m3'
3337
3338          CASE ( 'sa' )
3339             IF (  .NOT.  ocean )  THEN
3340                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3341                                 'res ocean = .TRUE.'
3342                CALL message( 'check_parameters', 'PA0109', 1, 2, 0, 6, 0 )
3343             ENDIF
3344             unit = 'psu'
3345
3346          CASE ( 'p', 'pt', 'u', 'v', 'w' )
3347             IF ( TRIM( var ) == 'p'  )  unit = 'Pa'
3348             IF ( TRIM( var ) == 'pt' )  unit = 'K'
3349             IF ( TRIM( var ) == 'u'  )  unit = 'm/s'
3350             IF ( TRIM( var ) == 'v'  )  unit = 'm/s'
3351             IF ( TRIM( var ) == 'w'  )  unit = 'm/s'
3352             CONTINUE
3353
3354          CASE ( 'ghf*', 'lwp*', 'ol*', 'pra*', 'prr*', 'qsws*', 'r_a*',       &
3355                 'shf*', 'ssws*', 't*', 'tsurf*', 'u*', 'z0*', 'z0h*', 'z0q*' )
3356             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
3357                message_string = 'illegal value for data_output: "' //         &
3358                                 TRIM( var ) // '" & only 2d-horizontal ' //   &
3359                                 'cross sections are allowed for this value'
3360                CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
3361             ENDIF
3362
3363             IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. cloud_physics )  THEN
3364                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3365                                 'res cloud_physics = .TRUE.'
3366                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
3367             ENDIF
3368             IF ( TRIM( var ) == 'pra*'  .AND.                                 &
3369                  .NOT. ( microphysics_kessler .OR. microphysics_seifert ) )  THEN
3370                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3371                                 'res cloud_scheme = kessler or seifert_beheng'
3372                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
3373             ENDIF
3374             IF ( TRIM( var ) == 'pra*'  .AND.  j == 1 )  THEN
3375                message_string = 'temporal averaging of precipitation ' //     &
3376                          'amount "' // TRIM( var ) // '" is not possible'
3377                CALL message( 'check_parameters', 'PA0113', 1, 2, 0, 6, 0 )
3378             ENDIF
3379             IF ( TRIM( var ) == 'prr*'  .AND.                                 &
3380                  .NOT. ( microphysics_kessler .OR. microphysics_seifert ) )  THEN
3381                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3382                                 'res cloud_scheme = kessler or seifert_beheng'
3383                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
3384             ENDIF
3385             IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT.  humidity )  THEN
3386                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3387                                 'res humidity = .TRUE.'
3388                CALL message( 'check_parameters', 'PA0322', 1, 2, 0, 6, 0 )
3389             ENDIF
3390
3391          IF ( TRIM( var ) == 'ghf*'  .AND.  .NOT.  land_surface )  THEN
3392             message_string = 'output of "' // TRIM( var ) // '" requi' //     &
3393                              'res land_surface = .TRUE.'
3394             CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
3395          ENDIF
3396
3397             IF ( ( TRIM( var ) == 'r_a*' .OR.  TRIM( var ) == 'ghf*' )        &
3398                 .AND.  .NOT.  land_surface  .AND.  .NOT.  urban_surface )     &         
3399             THEN
3400                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3401                                 'res land_surface = .TRUE. or ' //            &
3402                                 'urban_surface = .TRUE.'
3403                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
3404             ENDIF
3405             IF ( TRIM( var ) == 'ssws*'  .AND.  .NOT.  passive_scalar )  THEN
3406                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
3407                                 'res passive_scalar = .TRUE.'
3408                CALL message( 'check_parameters', 'PA0361', 1, 2, 0, 6, 0 )
3409             ENDIF
3410
3411             IF ( TRIM( var ) == 'ghf*'   )  unit = 'W/m2'
3412             IF ( TRIM( var ) == 'lwp*'   )  unit = 'kg/m2'
3413             IF ( TRIM( var ) == 'ol*'    )  unit = 'm'
3414             IF ( TRIM( var ) == 'pra*'   )  unit = 'mm'
3415             IF ( TRIM( var ) == 'prr*'   )  unit = 'mm/s'
3416             IF ( TRIM( var ) == 'qsws*'  )  unit = 'kgm/kgs'
3417             IF ( TRIM( var ) == 'r_a*'   )  unit = 's/m'     
3418             IF ( TRIM( var ) == 'shf*'   )  unit = 'K*m/s'
3419             IF ( TRIM( var ) == 'ssws*'  )  unit = 'kg/m2*s'
3420             IF ( TRIM( var ) == 't*'     )  unit = 'K'
3421             IF ( TRIM( var ) == 'tsurf*' )  unit = 'K' 
3422             IF ( TRIM( var ) == 'u*'     )  unit = 'm/s'
3423             IF ( TRIM( var ) == 'z0*'    )  unit = 'm'
3424             IF ( TRIM( var ) == 'z0h*'   )  unit = 'm'
3425!
3426!--          Output of surface latent and sensible heat flux will be in W/m2
3427!--          in case of natural- and urban-type surfaces, even if
3428!--          flux_output_mode is set to kinematic units.
3429             IF ( land_surface  .OR.  urban_surface )  THEN
3430                IF ( TRIM( var ) == 'shf*'   )  unit = 'W/m2'
3431                IF ( TRIM( var ) == 'qsws*'  )  unit = 'W/m2'
3432             ENDIF
3433
3434          CASE DEFAULT
3435
3436             CALL tcm_check_data_output ( var, unit, i, ilen, k )
3437
3438             IF ( unit == 'illegal' )  THEN
3439                CALL lsm_check_data_output ( var, unit, i, ilen, k )
3440             ENDIF
3441
3442             IF ( unit == 'illegal' )  THEN
3443                CALL radiation_check_data_output( var, unit, i, ilen, k )
3444             ENDIF
3445
3446!
3447!--          Block of gust module outputs
3448             IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
3449                CALL gust_check_data_output ( var, unit )
3450             ENDIF
3451
3452!
3453!--          Block of chemistry model outputs
3454             IF ( unit == 'illegal'  .AND.  air_chemistry                      &
3455                                     .AND.  var(1:3) == 'kc_' )  THEN
3456                CALL chem_check_data_output( var, unit, i, ilen, k )
3457             ENDIF
3458
3459!
3460!--          Block of urban surface model outputs
3461             IF ( unit == 'illegal' .AND. urban_surface .AND. var(1:4) == 'usm_' ) THEN
3462                 CALL usm_check_data_output( var, unit )
3463             ENDIF
3464
3465!
3466!--          Block of plant canopy model outputs
3467             IF ( unit == 'illegal' .AND. plant_canopy .AND. var(1:4) == 'pcm_' ) THEN
3468                 CALL pcm_check_data_output( var, unit )
3469             ENDIF
3470
3471!
3472!--          Block of uv exposure model outputs
3473             IF ( unit == 'illegal' .AND. uv_exposure .AND. var(1:5) == 'uvem_' )  THEN
3474                CALL uvem_check_data_output( var, unit, i, ilen, k )
3475             ENDIF
3476
3477             IF ( unit == 'illegal' )  THEN
3478                unit = ''
3479                CALL user_check_data_output( var, unit )
3480             ENDIF
3481
3482             IF ( unit == 'illegal' )  THEN
3483                IF ( data_output_user(1) /= ' ' )  THEN
3484                   message_string = 'illegal value for data_output or ' //     &
3485                         'data_output_user = "' // TRIM( data_output(i) ) // '"'
3486                   CALL message( 'check_parameters', 'PA0114', 1, 2, 0, 6, 0 )
3487                ELSE
3488                   message_string = 'illegal value for data_output = "' //     &
3489                                    TRIM( data_output(i) ) // '"'
3490                   CALL message( 'check_parameters', 'PA0115', 1, 2, 0, 6, 0 )
3491                ENDIF
3492             ENDIF
3493
3494       END SELECT
3495!
3496!--    Set the internal steering parameters appropriately
3497       IF ( k == 0 )  THEN
3498          do3d_no(j)              = do3d_no(j) + 1
3499          do3d(j,do3d_no(j))      = data_output(i)
3500          do3d_unit(j,do3d_no(j)) = unit
3501       ELSE
3502          do2d_no(j)              = do2d_no(j) + 1
3503          do2d(j,do2d_no(j))      = data_output(i)
3504          do2d_unit(j,do2d_no(j)) = unit
3505          IF ( data_output(i)(ilen-2:ilen) == '_xy' )  THEN
3506             data_output_xy(j) = .TRUE.
3507          ENDIF
3508          IF ( data_output(i)(ilen-2:ilen) == '_xz' )  THEN
3509             data_output_xz(j) = .TRUE.
3510          ENDIF
3511          IF ( data_output(i)(ilen-2:ilen) == '_yz' )  THEN
3512             data_output_yz(j) = .TRUE.
3513          ENDIF
3514       ENDIF
3515
3516       IF ( j == 1 )  THEN
3517!
3518!--       Check, if variable is already subject to averaging
3519          found = .FALSE.
3520          DO  k = 1, doav_n
3521             IF ( TRIM( doav(k) ) == TRIM( var ) )  found = .TRUE.
3522          ENDDO
3523
3524          IF ( .NOT. found )  THEN
3525             doav_n = doav_n + 1
3526             doav(doav_n) = var
3527          ENDIF
3528       ENDIF
3529
3530       i = i + 1
3531    ENDDO
3532
3533!
3534!-- Averaged 2d or 3d output requires that an averaging interval has been set
3535    IF ( doav_n > 0  .AND.  averaging_interval == 0.0_wp )  THEN
3536       WRITE( message_string, * )  'output of averaged quantity "',            &
3537                                   TRIM( doav(1) ), '_av" requires to set a ', &
3538                                   'non-zero & averaging interval'
3539       CALL message( 'check_parameters', 'PA0323', 1, 2, 0, 6, 0 )
3540    ENDIF
3541
3542!
3543!-- Check sectional planes and store them in one shared array
3544    IF ( ANY( section_xy > nz + 1 ) )  THEN
3545       WRITE( message_string, * )  'section_xy must be <= nz + 1 = ', nz + 1
3546       CALL message( 'check_parameters', 'PA0319', 1, 2, 0, 6, 0 )
3547    ENDIF
3548    IF ( ANY( section_xz > ny + 1 ) )  THEN
3549       WRITE( message_string, * )  'section_xz must be <= ny + 1 = ', ny + 1
3550       CALL message( 'check_parameters', 'PA0320', 1, 2, 0, 6, 0 )
3551    ENDIF
3552    IF ( ANY( section_yz > nx + 1 ) )  THEN
3553       WRITE( message_string, * )  'section_yz must be <= nx + 1 = ', nx + 1
3554       CALL message( 'check_parameters', 'PA0321', 1, 2, 0, 6, 0 )
3555    ENDIF
3556    section(:,1) = section_xy
3557    section(:,2) = section_xz
3558    section(:,3) = section_yz
3559
3560!
3561!-- Upper plot limit for 2D vertical sections
3562    IF ( z_max_do2d == -1.0_wp )  z_max_do2d = zu(nzt)
3563    IF ( z_max_do2d < zu(nzb+1)  .OR.  z_max_do2d > zu(nzt) )  THEN
3564       WRITE( message_string, * )  'z_max_do2d = ', z_max_do2d,                &
3565                    ' must be >= ', zu(nzb+1), '(zu(nzb+1)) and <= ', zu(nzt), &
3566                    ' (zu(nzt))'
3567       CALL message( 'check_parameters', 'PA0116', 1, 2, 0, 6, 0 )
3568    ENDIF
3569
3570!
3571!-- Upper plot limit for 3D arrays
3572    IF ( nz_do3d == -9999 )  nz_do3d = nzt + 1
3573
3574!
3575!-- Set output format string (used in header)
3576    SELECT CASE ( netcdf_data_format )
3577       CASE ( 1 )
3578          netcdf_data_format_string = 'netCDF classic'
3579       CASE ( 2 )
3580          netcdf_data_format_string = 'netCDF 64bit offset'
3581       CASE ( 3 )
3582          netcdf_data_format_string = 'netCDF4/HDF5'
3583       CASE ( 4 )
3584          netcdf_data_format_string = 'netCDF4/HDF5 classic'
3585       CASE ( 5 )
3586          netcdf_data_format_string = 'parallel netCDF4/HDF5'
3587       CASE ( 6 )
3588          netcdf_data_format_string = 'parallel netCDF4/HDF5 classic'
3589
3590    END SELECT
3591
3592!
3593!-- Check mask conditions
3594    DO mid = 1, max_masks
3595       IF ( data_output_masks(mid,1) /= ' '  .OR.                              &
3596            data_output_masks_user(mid,1) /= ' ' ) THEN
3597          masks = masks + 1
3598       ENDIF
3599    ENDDO
3600
3601    IF ( masks < 0  .OR.  masks > max_masks )  THEN
3602       WRITE( message_string, * )  'illegal value: masks must be >= 0 and ',   &
3603            '<= ', max_masks, ' (=max_masks)'
3604       CALL message( 'check_parameters', 'PA0325', 1, 2, 0, 6, 0 )
3605    ENDIF
3606    IF ( masks > 0 )  THEN
3607       mask_scale(1) = mask_scale_x
3608       mask_scale(2) = mask_scale_y
3609       mask_scale(3) = mask_scale_z
3610       IF ( ANY( mask_scale <= 0.0_wp ) )  THEN
3611          WRITE( message_string, * )                                           &
3612               'illegal value: mask_scale_x, mask_scale_y and mask_scale_z',   &
3613               'must be > 0.0'
3614          CALL message( 'check_parameters', 'PA0326', 1, 2, 0, 6, 0 )
3615       ENDIF
3616!
3617!--    Generate masks for masked data output
3618!--    Parallel netcdf output is not tested so far for masked data, hence
3619!--    netcdf_data_format is switched back to non-paralell output.
3620       netcdf_data_format_save = netcdf_data_format
3621       IF ( netcdf_data_format > 4 )  THEN
3622          IF ( netcdf_data_format == 5 ) netcdf_data_format = 3
3623          IF ( netcdf_data_format == 6 ) netcdf_data_format = 4
3624          message_string = 'netCDF file formats '//                            &
3625                           '5 (parallel netCDF 4) and ' //                     &
3626                           '6 (parallel netCDF 4 Classic model) '//            &
3627                           '&are currently not supported (not yet tested) ' // &
3628                           'for masked data.&Using respective non-parallel' // &
3629                           ' output for masked data.'
3630          CALL message( 'check_parameters', 'PA0383', 0, 0, 0, 6, 0 )
3631       ENDIF
3632       CALL init_masks
3633       netcdf_data_format = netcdf_data_format_save
3634    ENDIF
3635
3636!
3637!-- Check the NetCDF data format
3638    IF ( netcdf_data_format > 2 )  THEN
3639#if defined( __netcdf4 )
3640       CONTINUE
3641#else
3642       message_string = 'netCDF: netCDF4 format requested but no ' //          &
3643                        'cpp-directive __netcdf4 given & switch '  //          &
3644                        'back to 64-bit offset format'
3645       CALL message( 'check_parameters', 'PA0171', 0, 1, 0, 6, 0 )
3646       netcdf_data_format = 2
3647#endif
3648    ENDIF
3649    IF ( netcdf_data_format > 4 )  THEN
3650#if defined( __netcdf4 ) && defined( __netcdf4_parallel )
3651       CONTINUE
3652#else
3653       message_string = 'netCDF: netCDF4 parallel output requested but no ' // &
3654                        'cpp-directive __netcdf4_parallel given & switch '  // &
3655                        'back to netCDF4 non-parallel output'
3656       CALL message( 'check_parameters', 'PA0099', 0, 1, 0, 6, 0 )
3657       netcdf_data_format = netcdf_data_format - 2
3658#endif
3659    ENDIF
3660
3661!
3662!-- Calculate fixed number of output time levels for parallel netcdf output.
3663!-- The time dimension has to be defined as limited for parallel output,
3664!-- because otherwise the I/O performance drops significantly.
3665    IF ( netcdf_data_format > 4 )  THEN
3666
3667!
3668!--    Check if any of the follwoing data output interval is 0.0s, which is
3669!--    not allowed for parallel output.
3670       CALL check_dt_do( dt_do3d,    'dt_do3d'    )
3671       CALL check_dt_do( dt_do2d_xy, 'dt_do2d_xy' )
3672       CALL check_dt_do( dt_do2d_xz, 'dt_do2d_xz' )
3673       CALL check_dt_do( dt_do2d_yz, 'dt_do2d_yz' )
3674
3675       ntdim_3d(0)    = INT( ( end_time - skip_time_do3d ) / dt_do3d )
3676       IF ( do3d_at_begin ) ntdim_3d(0) = ntdim_3d(0) + 1
3677       ntdim_3d(1)    = INT( ( end_time - skip_time_data_output_av )           &
3678                             / dt_data_output_av )
3679       ntdim_2d_xy(0) = INT( ( end_time - skip_time_do2d_xy ) / dt_do2d_xy )
3680       ntdim_2d_xz(0) = INT( ( end_time - skip_time_do2d_xz ) / dt_do2d_xz )
3681       ntdim_2d_yz(0) = INT( ( end_time - skip_time_do2d_yz ) / dt_do2d_yz )
3682       IF ( do2d_at_begin )  THEN
3683          ntdim_2d_xy(0) = ntdim_2d_xy(0) + 1
3684          ntdim_2d_xz(0) = ntdim_2d_xz(0) + 1
3685          ntdim_2d_yz(0) = ntdim_2d_yz(0) + 1
3686       ENDIF
3687       ntdim_2d_xy(1) = ntdim_3d(1)
3688       ntdim_2d_xz(1) = ntdim_3d(1)
3689       ntdim_2d_yz(1) = ntdim_3d(1)
3690
3691    ENDIF
3692
3693!
3694!-- Check, whether a constant diffusion coefficient shall be used
3695    IF ( km_constant /= -1.0_wp )  THEN
3696       IF ( km_constant < 0.0_wp )  THEN
3697          WRITE( message_string, * )  'km_constant = ', km_constant, ' < 0.0'
3698          CALL message( 'check_parameters', 'PA0121', 1, 2, 0, 6, 0 )
3699       ELSE
3700          IF ( prandtl_number < 0.0_wp )  THEN
3701             WRITE( message_string, * )  'prandtl_number = ', prandtl_number,  &
3702                                         ' < 0.0'
3703             CALL message( 'check_parameters', 'PA0122', 1, 2, 0, 6, 0 )
3704          ENDIF
3705          constant_diffusion = .TRUE.
3706
3707          IF ( constant_flux_layer )  THEN
3708             message_string = 'constant_flux_layer is not allowed with fixed ' &
3709                              // 'value of km'
3710             CALL message( 'check_parameters', 'PA0123', 1, 2, 0, 6, 0 )
3711          ENDIF
3712       ENDIF
3713    ENDIF
3714
3715!
3716!-- In case of non-cyclic lateral boundaries and a damping layer for the
3717!-- potential temperature, check the width of the damping layer
3718    IF ( bc_lr /= 'cyclic' ) THEN
3719       IF ( pt_damping_width < 0.0_wp  .OR.                                    &
3720            pt_damping_width > REAL( (nx+1) * dx ) )  THEN
3721          message_string = 'pt_damping_width out of range'
3722          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
3723       ENDIF
3724    ENDIF
3725
3726    IF ( bc_ns /= 'cyclic' )  THEN
3727       IF ( pt_damping_width < 0.0_wp  .OR.                                    &
3728            pt_damping_width > REAL( (ny+1) * dy ) )  THEN
3729          message_string = 'pt_damping_width out of range'
3730          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
3731       ENDIF
3732    ENDIF
3733
3734!
3735!-- Check value range for zeta = z/L
3736    IF ( zeta_min >= zeta_max )  THEN
3737       WRITE( message_string, * )  'zeta_min = ', zeta_min, ' must be less ',  &
3738                                   'than zeta_max = ', zeta_max
3739       CALL message( 'check_parameters', 'PA0125', 1, 2, 0, 6, 0 )
3740    ENDIF
3741
3742!
3743!-- Check random generator
3744    IF ( (random_generator /= 'system-specific'      .AND.                     &
3745          random_generator /= 'random-parallel'   )  .AND.                     &
3746          random_generator /= 'numerical-recipes' )  THEN
3747       message_string = 'unknown random generator: random_generator = "' //    &
3748                        TRIM( random_generator ) // '"'
3749       CALL message( 'check_parameters', 'PA0135', 1, 2, 0, 6, 0 )
3750    ENDIF
3751
3752!
3753!-- Determine upper and lower hight level indices for random perturbations
3754    IF ( disturbance_level_b == -9999999.9_wp )  THEN
3755       IF ( ocean )  THEN
3756          disturbance_level_b     = zu((nzt*2)/3)
3757          disturbance_level_ind_b = ( nzt * 2 ) / 3
3758       ELSE
3759          disturbance_level_b     = zu(nzb+3)
3760          disturbance_level_ind_b = nzb + 3
3761       ENDIF
3762    ELSEIF ( disturbance_level_b < zu(3) )  THEN
3763       WRITE( message_string, * )  'disturbance_level_b = ',                   &
3764                           disturbance_level_b, ' must be >= ', zu(3), '(zu(3))'
3765       CALL message( 'check_parameters', 'PA0126', 1, 2, 0, 6, 0 )
3766    ELSEIF ( disturbance_level_b > zu(nzt-2) )  THEN
3767       WRITE( message_string, * )  'disturbance_level_b = ',                   &
3768                   disturbance_level_b, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
3769       CALL message( 'check_parameters', 'PA0127', 1, 2, 0, 6, 0 )
3770    ELSE
3771       DO  k = 3, nzt-2
3772          IF ( disturbance_level_b <= zu(k) )  THEN
3773             disturbance_level_ind_b = k
3774             EXIT
3775          ENDIF
3776       ENDDO
3777    ENDIF
3778
3779    IF ( disturbance_level_t == -9999999.9_wp )  THEN
3780       IF ( ocean )  THEN
3781          disturbance_level_t     = zu(nzt-3)
3782          disturbance_level_ind_t = nzt - 3
3783       ELSE
3784          disturbance_level_t     = zu(nzt/3)
3785          disturbance_level_ind_t = nzt / 3
3786       ENDIF
3787    ELSEIF ( disturbance_level_t > zu(nzt-2) )  THEN
3788       WRITE( message_string, * )  'disturbance_level_t = ',                   &
3789                   disturbance_level_t, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
3790       CALL message( 'check_parameters', 'PA0128', 1, 2, 0, 6, 0 )
3791    ELSEIF ( disturbance_level_t < disturbance_level_b )  THEN
3792       WRITE( message_string, * )  'disturbance_level_t = ',                   &
3793                   disturbance_level_t, ' must be >= disturbance_level_b = ',  &
3794                   disturbance_level_b
3795       CALL message( 'check_parameters', 'PA0129', 1, 2, 0, 6, 0 )
3796    ELSE
3797       DO  k = 3, nzt-2
3798          IF ( disturbance_level_t <= zu(k) )  THEN
3799             disturbance_level_ind_t = k
3800             EXIT
3801          ENDIF
3802       ENDDO
3803    ENDIF
3804
3805!
3806!-- Check again whether the levels determined this way are ok.
3807!-- Error may occur at automatic determination and too few grid points in
3808!-- z-direction.
3809    IF ( disturbance_level_ind_t < disturbance_level_ind_b )  THEN
3810       WRITE( message_string, * )  'disturbance_level_ind_t = ',               &
3811                disturbance_level_ind_t, ' must be >= disturbance_level_ind_b = ', &
3812                disturbance_level_ind_b
3813       CALL message( 'check_parameters', 'PA0130', 1, 2, 0, 6, 0 )
3814    ENDIF
3815
3816!
3817!-- Determine the horizontal index range for random perturbations.
3818!-- In case of non-cyclic horizontal boundaries, no perturbations are imposed
3819!-- near the inflow and the perturbation area is further limited to ...(1)
3820!-- after the initial phase of the flow.
3821
3822    IF ( bc_lr /= 'cyclic' )  THEN
3823       IF ( inflow_disturbance_begin == -1 )  THEN
3824          inflow_disturbance_begin = MIN( 10, nx/2 )
3825       ENDIF
3826       IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > nx )&
3827       THEN
3828          message_string = 'inflow_disturbance_begin out of range'
3829          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
3830       ENDIF
3831       IF ( inflow_disturbance_end == -1 )  THEN
3832          inflow_disturbance_end = MIN( 100, 3*nx/4 )
3833       ENDIF
3834       IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > nx )    &
3835       THEN
3836          message_string = 'inflow_disturbance_end out of range'
3837          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
3838       ENDIF
3839    ELSEIF ( bc_ns /= 'cyclic' )  THEN
3840       IF ( inflow_disturbance_begin == -1 )  THEN
3841          inflow_disturbance_begin = MIN( 10, ny/2 )
3842       ENDIF
3843       IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > ny )&
3844       THEN
3845          message_string = 'inflow_disturbance_begin out of range'
3846          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
3847       ENDIF
3848       IF ( inflow_disturbance_end == -1 )  THEN
3849          inflow_disturbance_end = MIN( 100, 3*ny/4 )
3850       ENDIF
3851       IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > ny )    &
3852       THEN
3853          message_string = 'inflow_disturbance_end out of range'
3854          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
3855       ENDIF
3856    ENDIF
3857
3858    IF ( random_generator == 'random-parallel' )  THEN
3859       dist_nxl = nxl;  dist_nxr = nxr
3860       dist_nys = nys;  dist_nyn = nyn
3861       IF ( bc_lr == 'radiation/dirichlet' )  THEN
3862          dist_nxr    = MIN( nx - inflow_disturbance_begin, nxr )
3863          dist_nxl(1) = MAX( nx - inflow_disturbance_end, nxl )
3864       ELSEIF ( bc_lr == 'dirichlet/radiation' )  THEN
3865          dist_nxl    = MAX( inflow_disturbance_begin, nxl )
3866          dist_nxr(1) = MIN( inflow_disturbance_end, nxr )
3867       ELSEIF ( bc_lr == 'nested'  .OR.  bc_lr == 'forcing' )  THEN
3868          dist_nxl = MAX( inflow_disturbance_begin, nxl )
3869       ENDIF
3870       IF ( bc_ns == 'dirichlet/radiation' )  THEN
3871          dist_nyn    = MIN( ny - inflow_disturbance_begin, nyn )
3872          dist_nys(1) = MAX( ny - inflow_disturbance_end, nys )
3873       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
3874          dist_nys    = MAX( inflow_disturbance_begin, nys )
3875          dist_nyn(1) = MIN( inflow_disturbance_end, nyn )
3876       ELSEIF ( bc_ns == 'nested'  .OR.  bc_ns == 'forcing' )  THEN
3877          dist_nys = MAX( inflow_disturbance_begin, nys )
3878       ENDIF
3879    ELSE
3880       dist_nxl = 0;  dist_nxr = nx
3881       dist_nys = 0;  dist_nyn = ny
3882       IF ( bc_lr == 'radiation/dirichlet' )  THEN
3883          dist_nxr    = nx - inflow_disturbance_begin
3884          dist_nxl(1) = nx - inflow_disturbance_end
3885       ELSEIF ( bc_lr == 'dirichlet/radiation' )  THEN
3886          dist_nxl    = inflow_disturbance_begin
3887          dist_nxr(1) = inflow_disturbance_end
3888       ENDIF
3889       IF ( bc_ns == 'dirichlet/radiation' )  THEN
3890          dist_nyn    = ny - inflow_disturbance_begin
3891          dist_nys(1) = ny - inflow_disturbance_end
3892       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
3893          dist_nys    = inflow_disturbance_begin
3894          dist_nyn(1) = inflow_disturbance_end
3895       ENDIF
3896    ENDIF
3897
3898!
3899!-- A turbulent inflow requires Dirichlet conditions at the respective inflow
3900!-- boundary (so far, a turbulent inflow is realized from the left side only)
3901    IF ( turbulent_inflow  .AND.  bc_lr /= 'dirichlet/radiation' )  THEN
3902       message_string = 'turbulent_inflow = .T. requires a Dirichlet ' //      &
3903                        'condition at the inflow boundary'
3904       CALL message( 'check_parameters', 'PA0133', 1, 2, 0, 6, 0 )
3905    ENDIF
3906
3907!
3908!-- Turbulent inflow requires that 3d arrays have been cyclically filled with
3909!-- data from prerun in the first main run
3910    IF ( turbulent_inflow  .AND.  initializing_actions /= 'cyclic_fill'  .AND. &
3911         initializing_actions /= 'read_restart_data' )  THEN
3912       message_string = 'turbulent_inflow = .T. requires ' //                  &
3913                        'initializing_actions = ''cyclic_fill'' or ' //        &
3914                        'initializing_actions = ''read_restart_data'' '
3915       CALL message( 'check_parameters', 'PA0055', 1, 2, 0, 6, 0 )
3916    ENDIF
3917
3918!
3919!-- In case of turbulent inflow calculate the index of the recycling plane
3920    IF ( turbulent_inflow )  THEN
3921       IF ( recycling_width <= dx  .OR.  recycling_width >= nx * dx )  THEN
3922          WRITE( message_string, * )  'illegal value for recycling_width:', &
3923                                      ' ', recycling_width
3924          CALL message( 'check_parameters', 'PA0134', 1, 2, 0, 6, 0 )
3925       ENDIF
3926!
3927!--    Calculate the index
3928       recycling_plane = recycling_width / dx
3929!
3930!--    Because the y-shift is done with a distance of INT( npey / 2 ) no shift
3931!--    is possible if there is only one PE in y direction.
3932       IF ( recycling_yshift .AND. pdims(2) < 2 )  THEN
3933          WRITE( message_string, * )  'recycling_yshift = .T. requires more',  &
3934                                      ' than one processor in y direction'
3935          CALL message( 'check_parameters', 'PA0421', 1, 2, 0, 6, 0 )
3936       ENDIF
3937    ENDIF
3938
3939
3940    IF ( turbulent_outflow )  THEN
3941!
3942!--    Turbulent outflow requires Dirichlet conditions at the respective inflow
3943!--    boundary (so far, a turbulent outflow is realized at the right side only)
3944       IF ( bc_lr /= 'dirichlet/radiation' )  THEN
3945          message_string = 'turbulent_outflow = .T. requires ' //              &
3946                           'bc_lr = "dirichlet/radiation"'
3947          CALL message( 'check_parameters', 'PA0038', 1, 2, 0, 6, 0 )
3948       ENDIF
3949!
3950!--    The ouflow-source plane must lay inside the model domain
3951       IF ( outflow_source_plane < dx  .OR.  &
3952            outflow_source_plane > nx * dx )  THEN
3953          WRITE( message_string, * )  'illegal value for outflow_source'//     &
3954                                      '_plane: ', outflow_source_plane
3955          CALL message( 'check_parameters', 'PA0145', 1, 2, 0, 6, 0 )
3956       ENDIF
3957    ENDIF
3958
3959!
3960!-- Determine damping level index for 1D model
3961    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
3962       IF ( damp_level_1d == -1.0_wp )  THEN
3963          damp_level_1d     = zu(nzt+1)
3964          damp_level_ind_1d = nzt + 1
3965       ELSEIF ( damp_level_1d < 0.0_wp  .OR.  damp_level_1d > zu(nzt+1) )  THEN
3966          WRITE( message_string, * )  'damp_level_1d = ', damp_level_1d,       &
3967                 ' must be >= 0.0 and <= ', zu(nzt+1), '(zu(nzt+1))'
3968          CALL message( 'check_parameters', 'PA0136', 1, 2, 0, 6, 0 )
3969       ELSE
3970          DO  k = 1, nzt+1
3971             IF ( damp_level_1d <= zu(k) )  THEN
3972                damp_level_ind_1d = k
3973                EXIT
3974             ENDIF
3975          ENDDO
3976       ENDIF
3977    ENDIF
3978
3979!
3980!-- Check some other 1d-model parameters
3981    IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                   &
3982         TRIM( mixing_length_1d ) /= 'blackadar' )  THEN
3983       message_string = 'mixing_length_1d = "' // TRIM( mixing_length_1d ) //  &
3984                        '" is unknown'
3985       CALL message( 'check_parameters', 'PA0137', 1, 2, 0, 6, 0 )
3986    ENDIF
3987    IF ( TRIM( dissipation_1d ) /= 'as_in_3d_model'  .AND.                     &
3988         TRIM( dissipation_1d ) /= 'detering'  .AND.                           &
3989         TRIM( dissipation_1d ) /= 'prognostic' )  THEN
3990       message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) //      &
3991                        '" is unknown'
3992       CALL message( 'check_parameters', 'PA0138', 1, 2, 0, 6, 0 )
3993    ENDIF
3994
3995!
3996!-- Set time for the next user defined restart (time_restart is the
3997!-- internal parameter for steering restart events)
3998    IF ( restart_time /= 9999999.9_wp )  THEN
3999       IF ( restart_time > time_since_reference_point )  THEN
4000          time_restart = restart_time
4001       ENDIF
4002    ELSE
4003!
4004!--    In case of a restart run, set internal parameter to default (no restart)
4005!--    if the NAMELIST-parameter restart_time is omitted
4006       time_restart = 9999999.9_wp
4007    ENDIF
4008
4009!
4010!-- Check pressure gradient conditions
4011    IF ( dp_external  .AND.  conserve_volume_flow )  THEN
4012       WRITE( message_string, * )  'Both dp_external and conserve_volume_flo', &
4013            'w are .TRUE. but one of them must be .FALSE.'
4014       CALL message( 'check_parameters', 'PA0150', 1, 2, 0, 6, 0 )
4015    ENDIF
4016    IF ( dp_external )  THEN
4017       IF ( dp_level_b < zu(nzb)  .OR.  dp_level_b > zu(nzt) )  THEN
4018          WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ', &
4019               ' of range'
4020          CALL message( 'check_parameters', 'PA0151', 1, 2, 0, 6, 0 )
4021       ENDIF
4022       IF ( .NOT. ANY( dpdxy /= 0.0_wp ) )  THEN
4023          WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is ze', &
4024               'ro, i.e. the external pressure gradient & will not be applied'
4025          CALL message( 'check_parameters', 'PA0152', 0, 1, 0, 6, 0 )
4026       ENDIF
4027    ENDIF
4028    IF ( ANY( dpdxy /= 0.0_wp )  .AND.  .NOT.  dp_external )  THEN
4029       WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ',     &
4030            '.FALSE., i.e. the external pressure gradient & will not be applied'
4031       CALL message( 'check_parameters', 'PA0153', 0, 1, 0, 6, 0 )
4032    ENDIF
4033    IF ( conserve_volume_flow )  THEN
4034       IF ( TRIM( conserve_volume_flow_mode ) == 'default' )  THEN
4035
4036          conserve_volume_flow_mode = 'initial_profiles'
4037
4038       ELSEIF ( TRIM( conserve_volume_flow_mode ) /= 'initial_profiles' .AND.  &
4039            TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' )  THEN
4040          WRITE( message_string, * )  'unknown conserve_volume_flow_mode: ',   &
4041               conserve_volume_flow_mode
4042          CALL message( 'check_parameters', 'PA0154', 1, 2, 0, 6, 0 )
4043       ENDIF
4044       IF ( (bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic')  .AND.                &
4045          TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
4046          WRITE( message_string, * )  'non-cyclic boundary conditions ',       &
4047               'require  conserve_volume_flow_mode = ''initial_profiles'''
4048          CALL message( 'check_parameters', 'PA0155', 1, 2, 0, 6, 0 )
4049       ENDIF
4050    ENDIF
4051    IF ( ( u_bulk /= 0.0_wp  .OR.  v_bulk /= 0.0_wp )  .AND.                   &
4052         ( .NOT. conserve_volume_flow  .OR.                                    &
4053         TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' ) )  THEN
4054       WRITE( message_string, * )  'nonzero bulk velocity requires ',          &
4055            'conserve_volume_flow = .T. and ',                                 &
4056            'conserve_volume_flow_mode = ''bulk_velocity'''
4057       CALL message( 'check_parameters', 'PA0157', 1, 2, 0, 6, 0 )
4058    ENDIF
4059
4060!
4061!-- Check particle attributes
4062    IF ( particle_color /= 'none' )  THEN
4063       IF ( particle_color /= 'absuv'  .AND.  particle_color /= 'pt*'  .AND.   &
4064            particle_color /= 'z' )  THEN
4065          message_string = 'illegal value for parameter particle_color: ' //   &
4066                           TRIM( particle_color)
4067          CALL message( 'check_parameters', 'PA0313', 1, 2, 0, 6, 0 )
4068       ELSE
4069          IF ( color_interval(2) <= color_interval(1) )  THEN
4070             message_string = 'color_interval(2) <= color_interval(1)'
4071             CALL message( 'check_parameters', 'PA0315', 1, 2, 0, 6, 0 )
4072          ENDIF
4073       ENDIF
4074    ENDIF
4075
4076    IF ( particle_dvrpsize /= 'none' )  THEN
4077       IF ( particle_dvrpsize /= 'absw' )  THEN
4078          message_string = 'illegal value for parameter particle_dvrpsize:' // &
4079                           ' ' // TRIM( particle_color)
4080          CALL message( 'check_parameters', 'PA0314', 1, 2, 0, 6, 0 )
4081       ELSE
4082          IF ( dvrpsize_interval(2) <= dvrpsize_interval(1) )  THEN
4083             message_string = 'dvrpsize_interval(2) <= dvrpsize_interval(1)'
4084             CALL message( 'check_parameters', 'PA0316', 1, 2, 0, 6, 0 )
4085          ENDIF
4086       ENDIF
4087    ENDIF
4088
4089!
4090!-- Prevent empty time records in volume, cross-section and masked data in case
4091!-- of non-parallel netcdf-output in restart runs
4092    IF ( netcdf_data_format < 5 )  THEN
4093       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
4094          do3d_time_count    = 0
4095          do2d_xy_time_count = 0
4096          do2d_xz_time_count = 0
4097          do2d_yz_time_count = 0
4098          domask_time_count  = 0
4099       ENDIF
4100    ENDIF
4101
4102!
4103!-- Check for valid setting of most_method
4104    IF ( TRIM( most_method ) /= 'circular'  .AND.                              &
4105         TRIM( most_method ) /= 'newton'    .AND.                              &
4106         TRIM( most_method ) /= 'lookup' )  THEN
4107       message_string = 'most_method = "' // TRIM( most_method ) //            &
4108                        '" is unknown'
4109       CALL message( 'check_parameters', 'PA0416', 1, 2, 0, 6, 0 )
4110    ENDIF
4111
4112!
4113!-- Check roughness length, which has to be smaller than dz/2
4114    IF ( ( constant_flux_layer .OR.  &
4115           INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 ) &
4116         .AND. roughness_length >= 0.5 * dz )  THEN
4117       message_string = 'roughness_length must be smaller than dz/2'
4118       CALL message( 'check_parameters', 'PA0424', 1, 2, 0, 6, 0 )
4119    ENDIF
4120
4121!
4122!-- Vertical nesting: check fine and coarse grid compatibility for data exchange
4123    IF ( vnested )  CALL vnest_check_parameters
4124
4125!
4126!-- Check if topography is read from file in case of complex terrain simulations
4127    IF ( complex_terrain  .AND.  TRIM( topography ) /= 'read_from_file' )  THEN
4128       message_string = 'complex_terrain requires topography' //               &
4129                        ' = ''read_from_file'''
4130       CALL message( 'check_parameters', 'PA0472', 1, 2, 0, 6, 0 )
4131    ENDIF
4132
4133!
4134!-- Check if vertical grid stretching is switched off in case of complex
4135!-- terrain simulations
4136    IF ( complex_terrain  .AND.  dz_stretch_level < 100000.0_wp )  THEN
4137       message_string = 'Vertical grid stretching is not allowed for ' //      &
4138                        'complex_terrain = .T.'
4139       CALL message( 'check_parameters', 'PA0473', 1, 2, 0, 6, 0 )
4140    ENDIF
4141
4142    CALL location_message( 'finished', .TRUE. )
4143!
4144!-- Check &userpar parameters
4145    CALL user_check_parameters
4146
4147 CONTAINS
4148
4149!------------------------------------------------------------------------------!
4150! Description:
4151! ------------
4152!> Check the length of data output intervals. In case of parallel NetCDF output
4153!> the time levels of the output files need to be fixed. Therefore setting the
4154!> output interval to 0.0s (usually used to output each timestep) is not
4155!> possible as long as a non-fixed timestep is used.
4156!------------------------------------------------------------------------------!
4157
4158    SUBROUTINE check_dt_do( dt_do, dt_do_name )
4159
4160       IMPLICIT NONE
4161
4162       CHARACTER (LEN=*), INTENT (IN) :: dt_do_name !< parin variable name
4163
4164       REAL(wp), INTENT (INOUT)       :: dt_do      !< data output interval
4165
4166       IF ( dt_do == 0.0_wp )  THEN
4167          IF ( dt_fixed )  THEN
4168             WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //     &
4169                    'timestep is wanted (' // dt_do_name // ' = 0.0).&'//      &
4170                    'Setting the output interval to the fixed timestep '//     &
4171                    'dt = ', dt, 's.'
4172             CALL message( 'check_parameters', 'PA0060', 0, 0, 0, 6, 0 )
4173             dt_do = dt
4174          ELSE
4175             message_string = dt_do_name // ' = 0.0 while using a ' //         &
4176                              'variable timestep and parallel netCDF4 ' //     &
4177                              'is not allowed.'
4178             CALL message( 'check_parameters', 'PA0081', 1, 2, 0, 6, 0 )
4179          ENDIF
4180       ENDIF
4181
4182    END SUBROUTINE check_dt_do
4183
4184
4185
4186
4187!------------------------------------------------------------------------------!
4188! Description:
4189! ------------
4190!> Inititalizes the vertical profiles of scalar quantities.
4191!------------------------------------------------------------------------------!
4192
4193    SUBROUTINE init_vertical_profiles( vertical_gradient_level_ind,            &
4194                                       vertical_gradient_level,                &
4195                                       vertical_gradient,                      &
4196                                       pr_init, surface_value, bc_t_val )
4197
4198
4199       IMPLICIT NONE
4200
4201       INTEGER(iwp) ::  i     !< counter
4202       INTEGER(iwp), DIMENSION(1:10) ::  vertical_gradient_level_ind !< vertical grid indices for gradient levels
4203
4204       REAL(wp)     ::  bc_t_val      !< model top gradient
4205       REAL(wp)     ::  gradient      !< vertica gradient of the respective quantity
4206       REAL(wp)     ::  surface_value !< surface value of the respecitve quantity
4207
4208
4209       REAL(wp), DIMENSION(0:nz+1) ::  pr_init                 !< initialisation profile
4210       REAL(wp), DIMENSION(1:10)   ::  vertical_gradient       !< given vertical gradient
4211       REAL(wp), DIMENSION(1:10)   ::  vertical_gradient_level !< given vertical gradient level
4212
4213       i = 1
4214       gradient = 0.0_wp
4215
4216       IF (  .NOT.  ocean )  THEN
4217
4218          vertical_gradient_level_ind(1) = 0
4219          DO  k = 1, nzt+1
4220             IF ( i < 11 )  THEN
4221                IF ( vertical_gradient_level(i) < zu(k)  .AND.            &
4222                     vertical_gradient_level(i) >= 0.0_wp )  THEN
4223                   gradient = vertical_gradient(i) / 100.0_wp
4224                   vertical_gradient_level_ind(i) = k - 1
4225                   i = i + 1
4226                ENDIF
4227             ENDIF
4228             IF ( gradient /= 0.0_wp )  THEN
4229                IF ( k /= 1 )  THEN
4230                   pr_init(k) = pr_init(k-1) + dzu(k) * gradient
4231                ELSE
4232                   pr_init(k) = pr_init(k-1) + dzu(k) * gradient
4233                ENDIF
4234             ELSE
4235                pr_init(k) = pr_init(k-1)
4236             ENDIF
4237   !
4238   !--       Avoid negative values
4239             IF ( pr_init(k) < 0.0_wp )  THEN
4240                pr_init(k) = 0.0_wp
4241             ENDIF
4242          ENDDO
4243
4244       ELSE
4245
4246          vertical_gradient_level_ind(1) = nzt+1
4247          DO  k = nzt, 0, -1
4248             IF ( i < 11 )  THEN
4249                IF ( vertical_gradient_level(i) > zu(k)  .AND.            &
4250                     vertical_gradient_level(i) <= 0.0_wp )  THEN
4251                   gradient = vertical_gradient(i) / 100.0_wp
4252                   vertical_gradient_level_ind(i) = k + 1
4253                   i = i + 1
4254                ENDIF
4255             ENDIF
4256             IF ( gradient /= 0.0_wp )  THEN
4257                IF ( k /= nzt )  THEN
4258                   pr_init(k) = pr_init(k+1) - dzu(k+1) * gradient
4259                ELSE
4260                   pr_init(k)   = surface_value - 0.5_wp * dzu(k+1) * gradient
4261                   pr_init(k+1) = surface_value + 0.5_wp * dzu(k+1) * gradient
4262                ENDIF
4263             ELSE
4264                pr_init(k) = pr_init(k+1)
4265             ENDIF
4266   !
4267   !--       Avoid negative humidities
4268             IF ( pr_init(k) < 0.0_wp )  THEN
4269                pr_init(k) = 0.0_wp
4270             ENDIF
4271          ENDDO
4272
4273       ENDIF
4274
4275!
4276!--    In case of no given gradients, choose zero gradient conditions
4277       IF ( vertical_gradient_level(1) == -999999.9_wp )  THEN
4278          vertical_gradient_level(1) = 0.0_wp
4279       ENDIF
4280!
4281!--    Store gradient at the top boundary for possible Neumann boundary condition
4282       bc_t_val  = ( pr_init(nzt+1) - pr_init(nzt) ) / dzu(nzt+1)
4283
4284    END SUBROUTINE init_vertical_profiles
4285
4286
4287
4288!------------------------------------------------------------------------------!
4289! Description:
4290! ------------
4291!> Set the bottom and top boundary conditions for humidity and scalars.
4292!------------------------------------------------------------------------------!
4293
4294    SUBROUTINE set_bc_scalars( sq, bc_b, bc_t, ibc_b, ibc_t, err_nr_b, err_nr_t )
4295
4296
4297       IMPLICIT NONE
4298
4299       CHARACTER (LEN=1)   ::  sq                       !<
4300       CHARACTER (LEN=*)   ::  bc_b
4301       CHARACTER (LEN=*)   ::  bc_t
4302       CHARACTER (LEN=*)   ::  err_nr_b
4303       CHARACTER (LEN=*)   ::  err_nr_t
4304
4305       INTEGER(iwp)        ::  ibc_b
4306       INTEGER(iwp)        ::  ibc_t
4307
4308!
4309!--    Set Integer flags and check for possilbe errorneous settings for bottom
4310!--    boundary condition
4311       IF ( bc_b == 'dirichlet' )  THEN
4312          ibc_b = 0
4313       ELSEIF ( bc_b == 'neumann' )  THEN
4314          ibc_b = 1
4315       ELSE
4316          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) //  &
4317                           '_b ="' // TRIM( bc_b ) // '"'
4318          CALL message( 'check_parameters', err_nr_b, 1, 2, 0, 6, 0 )
4319       ENDIF
4320!
4321!--    Set Integer flags and check for possilbe errorneous settings for top
4322!--    boundary condition
4323       IF ( bc_t == 'dirichlet' )  THEN
4324          ibc_t = 0
4325       ELSEIF ( bc_t == 'neumann' )  THEN
4326          ibc_t = 1
4327       ELSEIF ( bc_t == 'initial_gradient' )  THEN
4328          ibc_t = 2
4329       ELSEIF ( bc_t == 'nested'  .OR.  bc_t == 'forcing' )  THEN
4330          ibc_t = 3
4331       ELSE
4332          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) //  &
4333                           '_t ="' // TRIM( bc_t ) // '"'
4334          CALL message( 'check_parameters', err_nr_t, 1, 2, 0, 6, 0 )
4335       ENDIF
4336
4337
4338    END SUBROUTINE set_bc_scalars
4339
4340
4341
4342!------------------------------------------------------------------------------!
4343! Description:
4344! ------------
4345!> Check for consistent settings of bottom boundary conditions for humidity
4346!> and scalars.
4347!------------------------------------------------------------------------------!
4348
4349    SUBROUTINE check_bc_scalars( sq, bc_b, ibc_b,                 &
4350                                 err_nr_1, err_nr_2,       &
4351                                 constant_flux, surface_initial_change )
4352
4353
4354       IMPLICIT NONE
4355
4356       CHARACTER (LEN=1)   ::  sq                       !<
4357       CHARACTER (LEN=*)   ::  bc_b
4358       CHARACTER (LEN=*)   ::  err_nr_1
4359       CHARACTER (LEN=*)   ::  err_nr_2
4360
4361       INTEGER(iwp)        ::  ibc_b
4362
4363       LOGICAL             ::  constant_flux
4364
4365       REAL(wp)            ::  surface_initial_change
4366
4367!
4368!--    A given surface value implies Dirichlet boundary condition for
4369!--    the respective quantity. In this case specification of a constant flux is
4370!--    forbidden. However, an exception is made for large-scale forcing as well
4371!--    as land-surface model.
4372       IF ( .NOT. land_surface  .AND.  .NOT. large_scale_forcing )  THEN
4373          IF ( ibc_b == 0  .AND.  constant_flux )  THEN
4374             message_string = 'boundary condition: bc_' // TRIM( sq ) // '_b ' //  &
4375                              '= "' // TRIM( bc_b ) // '" is not allowed with ' // &
4376                              'prescribed surface flux'
4377             CALL message( 'check_parameters', err_nr_1, 1, 2, 0, 6, 0 )
4378          ENDIF
4379       ENDIF
4380       IF ( constant_flux  .AND.  surface_initial_change /= 0.0_wp )  THEN
4381          WRITE( message_string, * )  'a prescribed surface flux is not allo', &
4382                 'wed with ', sq, '_surface_initial_change (/=0) = ',          &
4383                 surface_initial_change
4384          CALL message( 'check_parameters', err_nr_2, 1, 2, 0, 6, 0 )
4385       ENDIF
4386
4387
4388    END SUBROUTINE check_bc_scalars
4389
4390
4391
4392 END SUBROUTINE check_parameters
Note: See TracBrowser for help on using the repository browser.