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

Last change on this file since 2809 was 2798, checked in by suehring, 6 years ago

Bugfix initialization of %pt_surface array; Output of surface temperature also for default-type surfaces

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