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

Last change on this file since 108 was 108, checked in by letzel, 17 years ago
  • Improved coupler: evaporation - salinity-flux coupling for humidity = .T.,

avoid MPI hangs when coupled runs terminate, add DOC/app/chapter_3.8;

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