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

Last change on this file since 1015 was 1015, checked in by raasch, 12 years ago

Starting with changes required for GPU optimization. OpenACC statements for using NVIDIA GPUs added.
Adjustment of mixing length to the Prandtl mixing length at first grid point above ground removed.
mask array is set zero for ghost boundaries

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