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

Last change on this file since 807 was 807, checked in by maronga, 12 years ago

new utility check_namelist_files implemented

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