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

Last change on this file since 3522 was 3517, checked in by gronemeier, 5 years ago

bugfix: renamed w*2pt* and w*pt*2 in w*2theta* and w*theta*2, respectively (check_parameters)

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