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

Last change on this file since 105 was 104, checked in by raasch, 17 years ago

trying to make creation of intercommunicator more stable

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