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

Last change on this file since 673 was 673, checked in by suehring, 14 years ago

Right computation of the pressure using Runge-Kutta weighting coefficients. Consideration of the pressure gradient during the time integration removed. Removed bugfix concerning velocity variances.

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