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

Last change on this file since 2305 was 2300, checked in by raasch, 7 years ago

NEC related code partly removed, host variable partly removed, host specific code completely removed, default values for host, loop_optimization and termination time_needed changed

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