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

Last change on this file since 2272 was 2271, checked in by sward, 7 years ago

error messages and numbers updated

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