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

Last change on this file since 3452 was 3452, checked in by schwenkel, 5 years ago

Bugfix for profiles output

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