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

Last change on this file since 1931 was 1931, checked in by suehring, 8 years ago

Rename multigrid into multigrid_noopt and multigrid_fast into multigrid, subroutines poismg is renamed into poismg_noopt and poismg_fast_mod into poismg_mod

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