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

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

preliminary version for coupled runs

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