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

Last change on this file since 1830 was 1830, checked in by maronga, 8 years ago

last commit documented

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