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

Last change on this file since 214 was 214, checked in by raasch, 15 years ago

further replacement of output messages

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