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

Last change on this file since 1069 was 1069, checked in by maronga, 11 years ago

allow usage of topography in combination with cloud physics, allow usage of topography in coupled ocean model, minor changes in mbuild and mrun

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