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

Last change on this file since 1485 was 1485, checked in by kanani, 10 years ago

last commit documented

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