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

Last change on this file since 1437 was 1430, checked in by knoop, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 150.5 KB
RevLine 
[1]1 SUBROUTINE check_parameters
2
[1036]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!
[1310]17! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]18!--------------------------------------------------------------------------------!
19!
[484]20! Current revisions:
[1]21! -----------------
[1366]22!
[1430]23!
[1366]24! Former revisions:
25! -----------------
26! $Id: check_parameters.f90 1430 2014-07-15 12:57:11Z raasch $
27!
[1430]28! 1429 2014-07-15 12:53:45Z knoop
29! run_description_header exended to provide ensemble_member_nr if specified
30!
[1426]31! 1425 2014-07-05 10:57:53Z knoop
32! bugfix: perturbation domain modified for parallel random number generator
33!
[1403]34! 1402 2014-05-09 14:25:13Z raasch
35! location messages modified
36!
[1401]37! 1400 2014-05-09 14:03:54Z knoop
38! Check random generator extended by option random-parallel
39!
[1385]40! 1384 2014-05-02 14:31:06Z raasch
41! location messages added
42!
[1366]43! 1365 2014-04-22 15:03:56Z boeske
[1365]44! Usage of large scale forcing for pt and q enabled:
45! output for profiles of large scale advection (td_lsa_lpt, td_lsa_q),
46! large scale subsidence (td_sub_lpt, td_sub_q)
47! and nudging tendencies (td_nud_lpt, td_nud_q, td_nud_u and td_nud_v) added,
48! check if use_subsidence_tendencies is used correctly
[1362]49!
50! 1361 2014-04-16 15:17:48Z hoffmann
51! PA0363 removed
52! PA0362 changed
53!
[1360]54! 1359 2014-04-11 17:15:14Z hoffmann
[1359]55! Do not allow the execution of PALM with use_particle_tails, since particle
56! tails are currently not supported by our new particle structure.
57!
58! PA0084 not necessary for new particle structure
[1329]59!
[1354]60! 1353 2014-04-08 15:21:23Z heinze
61! REAL constants provided with KIND-attribute
62!
[1331]63! 1330 2014-03-24 17:29:32Z suehring
64! In case of SGS-particle velocity advection of TKE is also allowed with
65! dissipative 5th-order scheme.
66!
[1329]67! 1327 2014-03-21 11:00:16Z raasch
[1327]68! "baroclinicity" renamed "baroclinity", "ocean version" replaced by "ocean mode"
69! bugfix: duplicate error message 56 removed,
70! check of data_output_format and do3d_compress removed
[1321]71!
[1323]72! 1322 2014-03-20 16:38:49Z raasch
73! some REAL constants defined as wp-kind
74!
[1321]75! 1320 2014-03-20 08:40:49Z raasch
76! Kind-parameters added to all INTEGER and REAL declaration statements,
[1320]77! kinds are defined in new module kinds,
78! revision history before 2012 removed,
79! comment fields (!:) to be used for variable explanations added to
80! all variable declaration statements
[1309]81!
82! 1308 2014-03-13 14:58:42Z fricke
[1308]83! +netcdf_data_format_save
84! Calculate fixed number of output time levels for parallel netcdf output.
85! For masked data, parallel netcdf output is not tested so far, hence
86! netcdf_data_format is switched back to non-paralell output.
[1242]87!
[1300]88! 1299 2014-03-06 13:15:21Z heinze
89! enable usage of large_scale subsidence in combination with large_scale_forcing
90! output for profile of large scale vertical velocity w_subs added
91!
[1277]92! 1276 2014-01-15 13:40:41Z heinze
93! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
94!
[1242]95! 1241 2013-10-30 11:36:58Z heinze
[1241]96! output for profiles of ug and vg added
97! set surface_heatflux and surface_waterflux also in dependence on
98! large_scale_forcing
99! checks for nudging and large scale forcing from external file
[1054]100!
[1237]101! 1236 2013-09-27 07:21:13Z raasch
102! check number of spectra levels
103!
[1217]104! 1216 2013-08-26 09:31:42Z raasch
105! check for transpose_compute_overlap (temporary)
106!
[1215]107! 1214 2013-08-21 12:29:17Z kanani
108! additional check for simultaneous use of vertical grid stretching
109! and particle advection
110!
[1213]111! 1212 2013-08-15 08:46:27Z raasch
112! checks for poisfft_hybrid removed
113!
[1211]114! 1210 2013-08-14 10:58:20Z raasch
115! check for fftw
116!
[1182]117! 1179 2013-06-14 05:57:58Z raasch
118! checks and settings of buoyancy parameters and switches revised,
119! initial profile for rho added to hom (id=77)
120!
[1175]121! 1174 2013-05-31 10:28:08Z gryschka
122! Bugfix in computing initial profiles for ug, vg, lad, q in case of Atmosphere
123!
[1160]124! 1159 2013-05-21 11:58:22Z fricke
125! bc_lr/ns_dirneu/neudir removed
126!
[1116]127! 1115 2013-03-26 18:16:16Z hoffmann
128! unused variables removed
129! drizzle can be used without precipitation
130!
[1112]131! 1111 2013-03-08 23:54:10Z raasch
132! ibc_p_b = 2 removed
133!
[1104]134! 1103 2013-02-20 02:15:53Z raasch
135! Bugfix: turbulent inflow must not require cyclic fill in restart runs
136!
[1093]137! 1092 2013-02-02 11:24:22Z raasch
138! unused variables removed
139!
[1070]140! 1069 2012-11-28 16:18:43Z maronga
141! allow usage of topography in combination with cloud physics
142!
[1066]143! 1065 2012-11-22 17:42:36Z hoffmann
144! Bugfix: It is not allowed to use cloud_scheme = seifert_beheng without
145!         precipitation in order to save computational resources.
146!
[1061]147! 1060 2012-11-21 07:19:51Z raasch
148! additional check for parameter turbulent_inflow
149!
[1054]150! 1053 2012-11-13 17:11:03Z hoffmann
[1053]151! necessary changes for the new two-moment cloud physics scheme added:
152! - check cloud physics scheme (Kessler or Seifert and Beheng)
153! - plant_canopy is not allowed
154! - currently, only cache loop_optimization is allowed
155! - initial profiles of nr, qr
156! - boundary condition of nr, qr
157! - check output quantities (qr, nr, prr)
[979]158!
[1037]159! 1036 2012-10-22 13:43:42Z raasch
160! code put under GPL (PALM 3.9)
161!
[1035]162! 1031/1034 2012-10-22 11:32:49Z raasch
163! check of netcdf4 parallel file support
164!
[1020]165! 1019 2012-09-28 06:46:45Z raasch
166! non-optimized version of prognostic_equations not allowed any more
167!
[1017]168! 1015 2012-09-27 09:23:24Z raasch
169! acc allowed for loop optimization,
170! checks for adjustment of mixing length to the Prandtl mixing length removed
171!
[1004]172! 1003 2012-09-14 14:35:53Z raasch
173! checks for cases with unequal subdomain sizes removed
174!
[1002]175! 1001 2012-09-13 14:08:46Z raasch
176! all actions concerning leapfrog- and upstream-spline-scheme removed
177!
[997]178! 996 2012-09-07 10:41:47Z raasch
179! little reformatting
[1001]180
[979]181! 978 2012-08-09 08:28:32Z fricke
[978]182! setting of bc_lr/ns_dirneu/neudir
183! outflow damping layer removed
184! check for z0h*
185! check for pt_damping_width
[667]186!
[965]187! 964 2012-07-26 09:14:24Z raasch
188! check of old profil-parameters removed
189!
[941]190! 940 2012-07-09 14:31:00Z raasch
191! checks for parameter neutral
192!
[925]193! 924 2012-06-06 07:44:41Z maronga
194! Bugfix: preprocessor directives caused error during compilation
195!
[893]196! 892 2012-05-02 13:51:44Z maronga
197! Bugfix for parameter file check ( excluding __netcdf4 )
198!
[867]199! 866 2012-03-28 06:44:41Z raasch
200! use only 60% of the geostrophic wind as translation speed in case of Galilean
201! transformation and use_ug_for_galilei_tr = .T. in order to mimimize the
202! timestep
203!
[863]204! 861 2012-03-26 14:18:34Z suehring
205! Check for topography and ws-scheme removed.
206! Check for loop_optimization = 'vector' and ws-scheme removed.
207!
[846]208! 845 2012-03-07 10:23:05Z maronga
209! Bugfix: exclude __netcdf4 directive part from namelist file check compilation
210!
[829]211! 828 2012-02-21 12:00:36Z raasch
212! check of collision_kernel extended
213!
[826]214! 825 2012-02-19 03:03:44Z raasch
215! check for collision_kernel and curvature_solution_effects
216!
[810]217! 809 2012-01-30 13:32:58Z maronga
218! Bugfix: replaced .AND. and .NOT. with && and ! in the preprocessor directives
219!
[808]220! 807 2012-01-25 11:53:51Z maronga
221! New cpp directive "__check" implemented which is used by check_namelist_files
222!
[1]223! Revision 1.1  1997/08/26 06:29:23  raasch
224! Initial revision
225!
226!
227! Description:
228! ------------
229! Check control parameters and deduce further quantities.
230!------------------------------------------------------------------------------!
231
232    USE arrays_3d
[824]233    USE cloud_parameters
[1]234    USE constants
235    USE control_parameters
[264]236    USE dvrp_variables
[1]237    USE grid_variables
238    USE indices
[1320]239    USE kinds
[1]240    USE model_1d
241    USE netcdf_control
242    USE particle_attributes
243    USE pegrid
244    USE profil_parameter
[1236]245    USE spectrum
246    USE statistics
[411]247    USE subsidence_mod
[1241]248    USE statistics
[1]249    USE transpose_indices
250
251    IMPLICIT NONE
252
[1320]253    CHARACTER (LEN=1)   ::  sq                       !:
254    CHARACTER (LEN=6)   ::  var                      !:
255    CHARACTER (LEN=7)   ::  unit                     !:
256    CHARACTER (LEN=8)   ::  date                     !:
257    CHARACTER (LEN=10)  ::  time                     !:
258    CHARACTER (LEN=40)  ::  coupling_string          !:
259    CHARACTER (LEN=100) ::  action                   !:
[1]260
[1320]261    INTEGER(iwp) ::  i                               !:
262    INTEGER(iwp) ::  ilen                            !:
263    INTEGER(iwp) ::  iremote = 0                     !:
264    INTEGER(iwp) ::  j                               !:
265    INTEGER(iwp) ::  k                               !:
266    INTEGER(iwp) ::  kk                              !:
267    INTEGER(iwp) ::  netcdf_data_format_save         !:
268    INTEGER(iwp) ::  position                        !:
269    INTEGER(iwp) ::  prec                            !:
270   
271    LOGICAL     ::  found                            !:
272    LOGICAL     ::  ldum                             !:
273   
274    REAL(wp)    ::  gradient                         !:
[1353]275    REAL(wp)    ::  remote = 0.0_wp                  !:
[1320]276    REAL(wp)    ::  simulation_time_since_reference  !:
[1]277
[1384]278
[1402]279    CALL location_message( 'checking parameters', .FALSE. )
[1384]280
[1]281!
[1216]282!-- Check for overlap combinations, which are not realized yet
283    IF ( transpose_compute_overlap )  THEN
284       IF ( numprocs == 1 )  STOP '+++ transpose-compute-overlap not implemented for single PE runs'
285#if defined( __openacc )
286       STOP '+++ transpose-compute-overlap not implemented for GPU usage'
287#endif
288    ENDIF
289
290!
[1]291!-- Warning, if host is not set
292    IF ( host(1:1) == ' ' )  THEN
[213]293       message_string = '"host" is not set. Please check that environment ' // &
294                        'variable "localhost" & is set before running PALM'
[226]295       CALL message( 'check_parameters', 'PA0001', 0, 0, 0, 6, 0 )
[1]296    ENDIF
297
298!
[102]299!-- Check the coupling mode
300    IF ( coupling_mode /= 'uncoupled'            .AND.  &
301         coupling_mode /= 'atmosphere_to_ocean'  .AND.  &
302         coupling_mode /= 'ocean_to_atmosphere' )  THEN
[213]303       message_string = 'illegal coupling mode: ' // TRIM( coupling_mode )
[226]304       CALL message( 'check_parameters', 'PA0002', 1, 2, 0, 6, 0 )
[102]305    ENDIF
306
307!
[108]308!-- Check dt_coupling, restart_time, dt_restart, end_time, dx, dy, nx and ny
[667]309    IF ( coupling_mode /= 'uncoupled')  THEN
[213]310
[1322]311       IF ( dt_coupling == 9999999.9_wp )  THEN
[213]312          message_string = 'dt_coupling is not set but required for coup' // &
313                           'ling mode "' //  TRIM( coupling_mode ) // '"'
[226]314          CALL message( 'check_parameters', 'PA0003', 1, 2, 0, 6, 0 )
[108]315       ENDIF
[213]316
[206]317#if defined( __parallel )
[807]318
319!
320!--    NOTE: coupled runs have not been implemented in the check_namelist_files
321!--    program.
322!--    check_namelist_files will need the following information of the other
323!--    model (atmosphere/ocean).
[845]324!       dt_coupling = remote
325!       dt_max = remote
326!       restart_time = remote
327!       dt_restart= remote
328!       simulation_time_since_reference = remote
329!       dx = remote
[807]330
331
[809]332#if ! defined( __check )
[667]333       IF ( myid == 0 ) THEN
334          CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter, &
335                         ierr )
336          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter, &
337                         status, ierr )
338       ENDIF
339       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]340#endif     
[108]341       IF ( dt_coupling /= remote )  THEN
[213]342          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
343                 '": dt_coupling = ', dt_coupling, '& is not equal to ',       &
344                 'dt_coupling_remote = ', remote
[226]345          CALL message( 'check_parameters', 'PA0004', 1, 2, 0, 6, 0 )
[108]346       ENDIF
[1353]347       IF ( dt_coupling <= 0.0_wp )  THEN
[809]348#if ! defined( __check )
[667]349          IF ( myid == 0  ) THEN
350             CALL MPI_SEND( dt_max, 1, MPI_REAL, target_id, 19, comm_inter, ierr )
351             CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter, &
352                            status, ierr )
353          ENDIF   
354          CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]355#endif         
[109]356          dt_coupling = MAX( dt_max, remote )
[213]357          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
358                 '": dt_coupling <= 0.0 & is not allowed and is reset to ',    &
359                 'MAX(dt_max(A,O)) = ', dt_coupling
[226]360          CALL message( 'check_parameters', 'PA0005', 0, 1, 0, 6, 0 )
[109]361       ENDIF
[809]362#if ! defined( __check )
[667]363       IF ( myid == 0 ) THEN
364          CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, &
365                         ierr )
366          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter, &
367                         status, ierr )
368       ENDIF
369       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]370#endif     
[108]371       IF ( restart_time /= remote )  THEN
[213]372          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
373                 '": restart_time = ', restart_time, '& is not equal to ',     &
374                 'restart_time_remote = ', remote
[226]375          CALL message( 'check_parameters', 'PA0006', 1, 2, 0, 6, 0 )
[108]376       ENDIF
[809]377#if ! defined( __check )
[667]378       IF ( myid == 0 ) THEN
379          CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter, &
380                         ierr )
381          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter, &
382                         status, ierr )
383       ENDIF   
384       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]385#endif     
[108]386       IF ( dt_restart /= remote )  THEN
[213]387          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
388                 '": dt_restart = ', dt_restart, '& is not equal to ',         &
389                 'dt_restart_remote = ', remote
[226]390          CALL message( 'check_parameters', 'PA0007', 1, 2, 0, 6, 0 )
[108]391       ENDIF
[213]392
[291]393       simulation_time_since_reference = end_time - coupling_start_time
[809]394#if ! defined( __check )
[667]395       IF  ( myid == 0 ) THEN
396          CALL MPI_SEND( simulation_time_since_reference, 1, MPI_REAL, target_id, &
397                         14, comm_inter, ierr )
398          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter, &
399                         status, ierr )   
400       ENDIF
401       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]402#endif     
[291]403       IF ( simulation_time_since_reference /= remote )  THEN
[213]404          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
[291]405                 '": simulation_time_since_reference = ',                      &
406                 simulation_time_since_reference, '& is not equal to ',        &
407                 'simulation_time_since_reference_remote = ', remote
[226]408          CALL message( 'check_parameters', 'PA0008', 1, 2, 0, 6, 0 )
[108]409       ENDIF
[213]410
[809]411#if ! defined( __check )
[667]412       IF ( myid == 0 ) THEN
413          CALL MPI_SEND( dx, 1, MPI_REAL, target_id, 15, comm_inter, ierr )
414          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter, &
415                                                             status, ierr )
[108]416       ENDIF
[667]417       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[213]418
[807]419#endif
[667]420       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
421
422          IF ( dx < remote ) THEN
423             WRITE( message_string, * ) 'coupling mode "', &
424                   TRIM( coupling_mode ),                  &
425           '": dx in Atmosphere is not equal to or not larger then dx in ocean'
426             CALL message( 'check_parameters', 'PA0009', 1, 2, 0, 6, 0 )
427          ENDIF
428
429          IF ( (nx_a+1)*dx /= (nx_o+1)*remote )  THEN
430             WRITE( message_string, * ) 'coupling mode "', &
431                    TRIM( coupling_mode ), &
432             '": Domain size in x-direction is not equal in ocean and atmosphere'
433             CALL message( 'check_parameters', 'PA0010', 1, 2, 0, 6, 0 )
434          ENDIF
435
[108]436       ENDIF
[213]437
[809]438#if ! defined( __check )
[667]439       IF ( myid == 0) THEN
440          CALL MPI_SEND( dy, 1, MPI_REAL, target_id, 16, comm_inter, ierr )
441          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter, &
442                         status, ierr )
[108]443       ENDIF
[667]444       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
[807]445#endif
[667]446       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
447
448          IF ( dy < remote )  THEN
449             WRITE( message_string, * ) 'coupling mode "', &
450                    TRIM( coupling_mode ), &
451                 '": dy in Atmosphere is not equal to or not larger then dy in ocean'
452             CALL message( 'check_parameters', 'PA0011', 1, 2, 0, 6, 0 )
453          ENDIF
454
455          IF ( (ny_a+1)*dy /= (ny_o+1)*remote )  THEN
456             WRITE( message_string, * ) 'coupling mode "', &
457                   TRIM( coupling_mode ), &
458             '": Domain size in y-direction is not equal in ocean and atmosphere'
459             CALL message( 'check_parameters', 'PA0012', 1, 2, 0, 6, 0 )
460          ENDIF
461
462          IF ( MOD(nx_o+1,nx_a+1) /= 0 )  THEN
463             WRITE( message_string, * ) 'coupling mode "', &
464                   TRIM( coupling_mode ), &
465             '": nx+1 in ocean is not divisible without remainder with nx+1 in', & 
466             ' atmosphere'
467             CALL message( 'check_parameters', 'PA0339', 1, 2, 0, 6, 0 )
468          ENDIF
469
470          IF ( MOD(ny_o+1,ny_a+1) /= 0 )  THEN
471             WRITE( message_string, * ) 'coupling mode "', &
472                   TRIM( coupling_mode ), &
473             '": ny+1 in ocean is not divisible without remainder with ny+1 in', & 
474             ' atmosphere'
475             CALL message( 'check_parameters', 'PA0340', 1, 2, 0, 6, 0 )
476          ENDIF
477
[108]478       ENDIF
[222]479#else
480       WRITE( message_string, * ) 'coupling requires PALM to be called with', &
481            ' ''mrun -K parallel'''
[226]482       CALL message( 'check_parameters', 'PA0141', 1, 2, 0, 6, 0 )
[108]483#endif
484    ENDIF
485
[809]486#if defined( __parallel ) && ! defined ( __check )
[108]487!
488!-- Exchange via intercommunicator
[667]489    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. myid == 0 )  THEN
[206]490       CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter, &
491                      ierr )
[667]492    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' .AND. myid == 0)  THEN
[206]493       CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19, &
494                      comm_inter, status, ierr )
[108]495    ENDIF
[667]496    CALL MPI_BCAST( humidity_remote, 1, MPI_LOGICAL, 0, comm2d, ierr)
497   
[108]498#endif
499
500
501!
[1]502!-- Generate the file header which is used as a header for most of PALM's
503!-- output files
504    CALL DATE_AND_TIME( date, time )
505    run_date = date(7:8)//'-'//date(5:6)//'-'//date(3:4)
506    run_time = time(1:2)//':'//time(3:4)//':'//time(5:6)
[102]507    IF ( coupling_mode == 'uncoupled' )  THEN
508       coupling_string = ''
509    ELSEIF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
510       coupling_string = ' coupled (atmosphere)'
511    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
512       coupling_string = ' coupled (ocean)'
513    ENDIF       
[1]514
[1429]515    IF ( ensemble_member_nr /= 0 )  THEN
516       WRITE ( run_description_header,                                         &
517                  '(A,2X,A,2X,A,A,A,I2.2,A,2X,A,I2.2,2X,A,A,2X,A,1X,A)' )      &
518              TRIM( version ), TRIM( revision ), 'run: ',                      &
519              TRIM( run_identifier ), '.', runnr, TRIM( coupling_string ),     &
520              'en-no: ', ensemble_member_nr,'host: ', TRIM( host ),            &
521              run_date, run_time
522    ELSE
523       WRITE ( run_description_header,                                         &
524                  '(A,2X,A,2X,A,A,A,I2.2,A,2X,A,A,2X,A,1X,A)' )                &
525              TRIM( version ), TRIM( revision ), 'run: ',                      &
526              TRIM( run_identifier ), '.', runnr, TRIM( coupling_string ),     &
[102]527              'host: ', TRIM( host ), run_date, run_time
[1429]528    ENDIF
[1]529!
[63]530!-- Check the general loop optimization method
531    IF ( loop_optimization == 'default' )  THEN
532       IF ( host(1:3) == 'nec' )  THEN
533          loop_optimization = 'vector'
534       ELSE
535          loop_optimization = 'cache'
536       ENDIF
537    ENDIF
538
[1015]539    SELECT CASE ( TRIM( loop_optimization ) )
540
[1019]541       CASE ( 'acc', 'cache', 'vector' )
[1015]542          CONTINUE
543
544       CASE DEFAULT
545          message_string = 'illegal value given for loop_optimization: "' // &
546                           TRIM( loop_optimization ) // '"'
547          CALL message( 'check_parameters', 'PA0013', 1, 2, 0, 6, 0 )
548
549    END SELECT
550
[63]551!
[1214]552!-- Check if vertical grid stretching is used together with particles
[1353]553    IF ( dz_stretch_level < 100000.0_wp .AND. particle_advection )  THEN
[1214]554       message_string = 'Vertical grid stretching is not allowed together ' // &
555                        'with particle advection.'
556       CALL message( 'check_parameters', 'PA0017', 1, 2, 0, 6, 0 )
557    ENDIF
558
559!
[1359]560!--
561    IF ( use_particle_tails )  THEN
562       message_string = 'Particle tails are currently not available due ' //   &
563                        'to the new particle structure.'
564       CALL message( 'check_parameters', 'PA0392', 1, 2, 0, 6, 0 )
565    ENDIF
566
567!
[1]568!-- Check topography setting (check for illegal parameter combinations)
569    IF ( topography /= 'flat' )  THEN
570       action = ' '
[861]571       IF ( scalar_advec /= 'pw-scheme' .AND. scalar_advec /= 'ws-scheme')  THEN
[1]572          WRITE( action, '(A,A)' )  'scalar_advec = ', scalar_advec
573       ENDIF
[861]574       IF ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' ) &
575       THEN
[1]576          WRITE( action, '(A,A)' )  'momentum_advec = ', momentum_advec
577       ENDIF
[114]578       IF ( psolver == 'sor' )  THEN
[1]579          WRITE( action, '(A,A)' )  'psolver = ', psolver
580       ENDIF
581       IF ( sloping_surface )  THEN
582          WRITE( action, '(A)' )  'sloping surface = .TRUE.'
583       ENDIF
584       IF ( galilei_transformation )  THEN
585          WRITE( action, '(A)' )  'galilei_transformation = .TRUE.'
586       ENDIF
[1115]587       IF ( cloud_physics )  THEN
588          WRITE( action, '(A)' )  'cloud_physics = .TRUE.'
589       ENDIF
[1]590       IF ( cloud_droplets )  THEN
[1115]591          WRITE( action, '(A)' )  'cloud_droplets = .TRUE.'
[1]592       ENDIF
593       IF ( .NOT. prandtl_layer )  THEN
594          WRITE( action, '(A)' )  'prandtl_layer = .FALSE.'
595       ENDIF
596       IF ( action /= ' ' )  THEN
[213]597          message_string = 'a non-flat topography does not allow ' // &
598                           TRIM( action )
[226]599          CALL message( 'check_parameters', 'PA0014', 1, 2, 0, 6, 0 )
[1]600       ENDIF
[256]601!
602!--    In case of non-flat topography, check whether the convention how to
603!--    define the topography grid has been set correctly, or whether the default
604!--    is applicable. If this is not possible, abort.
605       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
606          IF ( TRIM( topography ) /= 'single_building' .AND.  &
607               TRIM( topography ) /= 'single_street_canyon' .AND.  &
608               TRIM( topography ) /= 'read_from_file' )  THEN
609!--          The default value is not applicable here, because it is only valid
610!--          for the two standard cases 'single_building' and 'read_from_file'
611!--          defined in init_grid.
612             WRITE( message_string, * )  &
613                  'The value for "topography_grid_convention" ',  &
614                  'is not set. Its default value is & only valid for ',  &
615                  '"topography" = ''single_building'', ',  &
616                  '''single_street_canyon'' & or ''read_from_file''.',  &
617                  ' & Choose ''cell_edge'' or ''cell_center''.'
618             CALL message( 'user_check_parameters', 'PA0239', 1, 2, 0, 6, 0 )
619          ELSE
620!--          The default value is applicable here.
621!--          Set convention according to topography.
622             IF ( TRIM( topography ) == 'single_building' .OR.  &
623                  TRIM( topography ) == 'single_street_canyon' )  THEN
624                topography_grid_convention = 'cell_edge'
625             ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
626                topography_grid_convention = 'cell_center'
627             ENDIF
628          ENDIF
629       ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.  &
630                TRIM( topography_grid_convention ) /= 'cell_center' )  THEN
631          WRITE( message_string, * )  &
632               'The value for "topography_grid_convention" is ', &
633               'not recognized. & Choose ''cell_edge'' or ''cell_center''.'
634          CALL message( 'user_check_parameters', 'PA0240', 1, 2, 0, 6, 0 )
635       ENDIF
636
[1]637    ENDIF
[94]638
[1]639!
[94]640!-- Check ocean setting
641    IF ( ocean )  THEN
[332]642
[94]643       action = ' '
644       IF ( action /= ' ' )  THEN
[213]645          message_string = 'ocean = .T. does not allow ' // TRIM( action )
[226]646          CALL message( 'check_parameters', 'PA0015', 1, 2, 0, 6, 0 )
[94]647       ENDIF
648
[332]649    ELSEIF ( TRIM( coupling_mode ) == 'uncoupled'  .AND.  &
650             TRIM( coupling_char ) == '_O' )  THEN
[343]651
[94]652!
[332]653!--    Check whether an (uncoupled) atmospheric run has been declared as an
654!--    ocean run (this setting is done via mrun-option -y)
[343]655
[291]656       message_string = 'ocean = .F. does not allow coupling_char = "' // &
657                        TRIM( coupling_char ) // '" set by mrun-option "-y"'
658       CALL message( 'check_parameters', 'PA0317', 1, 2, 0, 6, 0 )
[332]659
[291]660    ENDIF
661!
[1053]662!-- Check cloud scheme
663    IF ( cloud_scheme == 'seifert_beheng' )  THEN
664       icloud_scheme = 0
665    ELSEIF ( cloud_scheme == 'kessler' )  THEN
666       icloud_scheme = 1
667    ELSE
668       message_string = 'unknown cloud microphysics scheme cloud_scheme ="' // &
669                        TRIM( cloud_scheme ) // '"'
670       CALL message( 'check_parameters', 'PA0357', 1, 2, 0, 6, 0 )
671    ENDIF
672!
[1]673!-- Check whether there are any illegal values
674!-- Pressure solver:
[1212]675    IF ( psolver /= 'poisfft'  .AND. &
[1]676         psolver /= 'sor'  .AND.  psolver /= 'multigrid' )  THEN
[213]677       message_string = 'unknown solver for perturbation pressure: psolver' // &
678                        ' = "' // TRIM( psolver ) // '"'
[226]679       CALL message( 'check_parameters', 'PA0016', 1, 2, 0, 6, 0 )
[1]680    ENDIF
681
682    IF ( psolver == 'multigrid' )  THEN
683       IF ( cycle_mg == 'w' )  THEN
684          gamma_mg = 2
685       ELSEIF ( cycle_mg == 'v' )  THEN
686          gamma_mg = 1
687       ELSE
[213]688          message_string = 'unknown multigrid cycle: cycle_mg = "' // &
689                           TRIM( cycle_mg ) // '"'
[226]690          CALL message( 'check_parameters', 'PA0020', 1, 2, 0, 6, 0 )
[1]691       ENDIF
692    ENDIF
693
694    IF ( fft_method /= 'singleton-algorithm'  .AND.  &
695         fft_method /= 'temperton-algorithm'  .AND.  &
[1210]696         fft_method /= 'fftw'                 .AND.  &
[1]697         fft_method /= 'system-specific' )  THEN
[213]698       message_string = 'unknown fft-algorithm: fft_method = "' // &
699                        TRIM( fft_method ) // '"'
[226]700       CALL message( 'check_parameters', 'PA0021', 1, 2, 0, 6, 0 )
[1]701    ENDIF
[667]702   
703    IF( momentum_advec == 'ws-scheme' .AND. & 
[688]704        .NOT. call_psolver_at_all_substeps  ) THEN
[667]705        message_string = 'psolver must be called at each RK3 substep when "'//&
706                      TRIM(momentum_advec) // ' "is used for momentum_advec'
[685]707        CALL message( 'check_parameters', 'PA0344', 1, 2, 0, 6, 0 )
[667]708    END IF
[1]709!
710!-- Advection schemes:
[1001]711    IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' ) &
712    THEN
[214]713       message_string = 'unknown advection scheme: momentum_advec = "' // &
714                        TRIM( momentum_advec ) // '"'
[226]715       CALL message( 'check_parameters', 'PA0022', 1, 2, 0, 6, 0 )
[1]716    ENDIF
[1001]717    IF ( ( momentum_advec == 'ws-scheme' .OR.  scalar_advec == 'ws-scheme' )   &
718           .AND. ( timestep_scheme == 'euler' .OR.                             &
719                   timestep_scheme == 'runge-kutta-2' ) )                      &
720    THEN
[667]721       message_string = 'momentum_advec or scalar_advec = "' &
722         // TRIM( momentum_advec ) // '" is not allowed with timestep_scheme = "' // &
723         TRIM( timestep_scheme ) // '"'
[226]724       CALL message( 'check_parameters', 'PA0023', 1, 2, 0, 6, 0 )
[1]725    ENDIF
[667]726    IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' .AND. &
[1001]727         scalar_advec /= 'bc-scheme' )                                         &
728    THEN
[214]729       message_string = 'unknown advection scheme: scalar_advec = "' // &
730                        TRIM( scalar_advec ) // '"'
[226]731       CALL message( 'check_parameters', 'PA0024', 1, 2, 0, 6, 0 )
[1]732    ENDIF
[1353]733    IF ( scalar_advec == 'bc-scheme'  .AND.  loop_optimization == 'cache' )    &
[1019]734    THEN
735       message_string = 'advection_scheme scalar_advec = "' &
736         // TRIM( scalar_advec ) // '" not implemented for & loop_optimization = "' // &
737         TRIM( loop_optimization ) // '"'
738       CALL message( 'check_parameters', 'PA0026', 1, 2, 0, 6, 0 )
739    ENDIF
[1]740
[1353]741    IF ( use_sgs_for_particles  .AND.  .NOT. use_upstream_for_tke .AND.        &
[1330]742         scalar_advec /= 'ws-scheme' )  THEN
[1]743       use_upstream_for_tke = .TRUE.
[1353]744       message_string = 'use_upstream_for_tke set .TRUE. because ' //          &
745                        'use_sgs_for_particles = .TRUE. '          //          &
[1330]746                        'and scalar_advec /= ws-scheme'
[226]747       CALL message( 'check_parameters', 'PA0025', 0, 1, 0, 6, 0 )
[1]748    ENDIF
749
[824]750    IF ( use_sgs_for_particles  .AND.  curvature_solution_effects )  THEN
[1353]751       message_string = 'use_sgs_for_particles = .TRUE. not allowed with ' //  &
[824]752                        'curvature_solution_effects = .TRUE.'
753       CALL message( 'check_parameters', 'PA0349', 1, 2, 0, 6, 0 )
754    ENDIF
755
[1]756!
[1019]757!-- Set LOGICAL switches to enhance performance
758    IF ( momentum_advec == 'ws-scheme' )    ws_scheme_mom = .TRUE.
759    IF ( scalar_advec   == 'ws-scheme'   )  ws_scheme_sca = .TRUE.
760
761!
[1]762!-- Timestep schemes:
763    SELECT CASE ( TRIM( timestep_scheme ) )
764
765       CASE ( 'euler' )
766          intermediate_timestep_count_max = 1
767
768       CASE ( 'runge-kutta-2' )
769          intermediate_timestep_count_max = 2
770
771       CASE ( 'runge-kutta-3' )
772          intermediate_timestep_count_max = 3
773
774       CASE DEFAULT
[1353]775          message_string = 'unknown timestep scheme: timestep_scheme = "' //   &
[214]776                           TRIM( timestep_scheme ) // '"'
[226]777          CALL message( 'check_parameters', 'PA0027', 1, 2, 0, 6, 0 )
[1]778
779    END SELECT
780
[1353]781    IF ( (momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme')   &
[667]782         .AND. timestep_scheme(1:5) == 'runge' ) THEN
[214]783       message_string = 'momentum advection scheme "' // &
784                        TRIM( momentum_advec ) // '" & does not work with ' // &
785                        'timestep_scheme "' // TRIM( timestep_scheme ) // '"'
[226]786       CALL message( 'check_parameters', 'PA0029', 1, 2, 0, 6, 0 )
[1]787    ENDIF
788
[825]789!
790!-- Collision kernels:
791    SELECT CASE ( TRIM( collision_kernel ) )
792
[828]793       CASE ( 'hall', 'hall_fast' )
[825]794          hall_kernel = .TRUE.
795
796       CASE ( 'palm' )
797          palm_kernel = .TRUE.
798
[828]799       CASE ( 'wang', 'wang_fast' )
[825]800          wang_kernel = .TRUE.
801
802       CASE ( 'none' )
803
804
805       CASE DEFAULT
806          message_string = 'unknown collision kernel: collision_kernel = "' // &
807                           TRIM( collision_kernel ) // '"'
808          CALL message( 'check_parameters', 'PA0350', 1, 2, 0, 6, 0 )
809
810    END SELECT
[828]811    IF ( collision_kernel(6:9) == 'fast' )  use_kernel_tables = .TRUE.
[825]812
[147]813    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.  &
[328]814         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
[1]815!
[214]816!--    No restart run: several initialising actions are possible
[1]817       action = initializing_actions
818       DO WHILE ( TRIM( action ) /= '' )
819          position = INDEX( action, ' ' )
820          SELECT CASE ( action(1:position-1) )
821
822             CASE ( 'set_constant_profiles', 'set_1d-model_profiles', &
[46]823                    'by_user', 'initialize_vortex',     'initialize_ptanom' )
[1]824                action = action(position+1:)
825
826             CASE DEFAULT
[214]827                message_string = 'initializing_action = "' // &
828                                 TRIM( action ) // '" unkown or not allowed'
[226]829                CALL message( 'check_parameters', 'PA0030', 1, 2, 0, 6, 0 )
[1]830
831          END SELECT
832       ENDDO
833    ENDIF
[214]834
[680]835    IF ( TRIM( initializing_actions ) == 'initialize_vortex' .AND. &
836         conserve_volume_flow ) THEN
837         message_string = 'initializing_actions = "initialize_vortex"' // &
838                        ' ist not allowed with conserve_volume_flow = .T.'
839       CALL message( 'check_parameters', 'PA0343', 1, 2, 0, 6, 0 )
840    ENDIF       
841
842
[1]843    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND. &
844         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[214]845       message_string = 'initializing_actions = "set_constant_profiles"' // &
846                        ' and "set_1d-model_profiles" are not allowed ' //  &
847                        'simultaneously'
[226]848       CALL message( 'check_parameters', 'PA0031', 1, 2, 0, 6, 0 )
[1]849    ENDIF
[214]850
[46]851    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND. &
852         INDEX( initializing_actions, 'by_user' ) /= 0 )  THEN
[214]853       message_string = 'initializing_actions = "set_constant_profiles"' // &
854                        ' and "by_user" are not allowed simultaneously'
[226]855       CALL message( 'check_parameters', 'PA0032', 1, 2, 0, 6, 0 )
[46]856    ENDIF
[214]857
[46]858    IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND. &
859         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[214]860       message_string = 'initializing_actions = "by_user" and ' // &
861                        '"set_1d-model_profiles" are not allowed simultaneously'
[226]862       CALL message( 'check_parameters', 'PA0033', 1, 2, 0, 6, 0 )
[46]863    ENDIF
[1]864
[75]865    IF ( cloud_physics  .AND.  .NOT. humidity )  THEN
[214]866       WRITE( message_string, * ) 'cloud_physics = ', cloud_physics, ' is ', &
867              'not allowed with humidity = ', humidity
[226]868       CALL message( 'check_parameters', 'PA0034', 1, 2, 0, 6, 0 )
[1]869    ENDIF
870
[72]871    IF ( precipitation  .AND.  .NOT.  cloud_physics )  THEN
[214]872       WRITE( message_string, * ) 'precipitation = ', precipitation, ' is ', &
873              'not allowed with cloud_physics = ', cloud_physics
[226]874       CALL message( 'check_parameters', 'PA0035', 1, 2, 0, 6, 0 )
[72]875    ENDIF
876
[75]877    IF ( humidity  .AND.  sloping_surface )  THEN
[214]878       message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' // &
879                        'are not allowed simultaneously'
[226]880       CALL message( 'check_parameters', 'PA0036', 1, 2, 0, 6, 0 )
[1]881    ENDIF
882
[75]883    IF ( passive_scalar  .AND.  humidity )  THEN
[214]884       message_string = 'humidity = .TRUE. and passive_scalar = .TRUE. ' // &
885                        'is not allowed simultaneously'
[226]886       CALL message( 'check_parameters', 'PA0038', 1, 2, 0, 6, 0 )
[1]887    ENDIF
888
[1353]889    IF ( plant_canopy .AND. ( drag_coefficient == 0.0_wp ) ) THEN
[214]890       message_string = 'plant_canopy = .TRUE. requires a non-zero drag ' // &
891                        'coefficient & given value is drag_coefficient = 0.0'
[226]892       CALL message( 'check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
[138]893    ENDIF
894
[1053]895    IF ( plant_canopy  .AND.  cloud_physics  .AND.  icloud_scheme == 0 ) THEN
896       message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' //  &
897                        ' seifert_beheng'
898       CALL message( 'check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
899    ENDIF
900
[1361]901    IF ( .NOT. ( loop_optimization == 'cache'  .OR.                            &
902                 loop_optimization == 'vector' )                               &
903         .AND.  cloud_physics  .AND.  icloud_scheme == 0 )  THEN
[1053]904       message_string = 'cloud_scheme = seifert_beheng requires ' // &
[1361]905                        'loop_optimization = "cache" or "vector"'
[1053]906       CALL message( 'check_parameters', 'PA0362', 1, 2, 0, 6, 0 )
907    ENDIF 
908
[1]909!
910!-- In case of no model continuation run, check initialising parameters and
911!-- deduce further quantities
912    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
913
914!
[767]915!--    Initial profiles for 1D and 3D model, respectively (u,v further below)
[1]916       pt_init = pt_surface
[1053]917       IF ( humidity )  THEN
918          q_init  = q_surface
919       ENDIF
[94]920       IF ( ocean )           sa_init = sa_surface
921       IF ( passive_scalar )  q_init  = s_surface
[1353]922       IF ( plant_canopy )    lad = 0.0_wp
[1]923
924!
925!--
926!--    If required, compute initial profile of the geostrophic wind
927!--    (component ug)
928       i = 1
[1353]929       gradient = 0.0_wp
[97]930
931       IF ( .NOT. ocean )  THEN
932
933          ug_vertical_gradient_level_ind(1) = 0
934          ug(0) = ug_surface
935          DO  k = 1, nzt+1
[177]936             IF ( i < 11 ) THEN
937                IF ( ug_vertical_gradient_level(i) < zu(k)  .AND. &
[1353]938                     ug_vertical_gradient_level(i) >= 0.0_wp )  THEN
939                   gradient = ug_vertical_gradient(i) / 100.0_wp
[177]940                   ug_vertical_gradient_level_ind(i) = k - 1
941                   i = i + 1
[1]942                ENDIF
[177]943             ENDIF       
[1353]944             IF ( gradient /= 0.0_wp )  THEN
[97]945                IF ( k /= 1 )  THEN
946                   ug(k) = ug(k-1) + dzu(k) * gradient
947                ELSE
[1174]948                   ug(k) = ug_surface + dzu(k) * gradient
[97]949                ENDIF
[1]950             ELSE
[97]951                ug(k) = ug(k-1)
[1]952             ENDIF
[97]953          ENDDO
[1]954
[97]955       ELSE
956
957          ug_vertical_gradient_level_ind(1) = nzt+1
[121]958          ug(nzt+1) = ug_surface
[667]959          DO  k = nzt, nzb, -1
[177]960             IF ( i < 11 ) THEN
961                IF ( ug_vertical_gradient_level(i) > zu(k)  .AND. &
[1353]962                     ug_vertical_gradient_level(i) <= 0.0_wp )  THEN
963                   gradient = ug_vertical_gradient(i) / 100.0_wp
[177]964                   ug_vertical_gradient_level_ind(i) = k + 1
965                   i = i + 1
[97]966                ENDIF
967             ENDIF
[1353]968             IF ( gradient /= 0.0_wp )  THEN
[97]969                IF ( k /= nzt )  THEN
970                   ug(k) = ug(k+1) - dzu(k+1) * gradient
971                ELSE
[1353]972                   ug(k)   = ug_surface - 0.5_wp * dzu(k+1) * gradient
973                   ug(k+1) = ug_surface + 0.5_wp * dzu(k+1) * gradient
[97]974                ENDIF
975             ELSE
976                ug(k) = ug(k+1)
977             ENDIF
978          ENDDO
979
980       ENDIF
981
[1]982!
[767]983!--    In case of no given gradients for ug, choose a zero gradient
[1322]984       IF ( ug_vertical_gradient_level(1) == -9999999.9_wp )  THEN
[1353]985          ug_vertical_gradient_level(1) = 0.0_wp
[1]986       ENDIF 
987
988!
989!--
990!--    If required, compute initial profile of the geostrophic wind
991!--    (component vg)
992       i = 1
[1353]993       gradient = 0.0_wp
[97]994
995       IF ( .NOT. ocean )  THEN
996
997          vg_vertical_gradient_level_ind(1) = 0
998          vg(0) = vg_surface
999          DO  k = 1, nzt+1
[177]1000             IF ( i < 11 ) THEN
1001                IF ( vg_vertical_gradient_level(i) < zu(k)  .AND. &
[1353]1002                     vg_vertical_gradient_level(i) >= 0.0_wp )  THEN
1003                   gradient = vg_vertical_gradient(i) / 100.0_wp
[177]1004                   vg_vertical_gradient_level_ind(i) = k - 1
1005                   i = i + 1
[1]1006                ENDIF
1007             ENDIF
[1353]1008             IF ( gradient /= 0.0_wp )  THEN
[97]1009                IF ( k /= 1 )  THEN
1010                   vg(k) = vg(k-1) + dzu(k) * gradient
1011                ELSE
[1174]1012                   vg(k) = vg_surface + dzu(k) * gradient
[97]1013                ENDIF
[1]1014             ELSE
[97]1015                vg(k) = vg(k-1)
[1]1016             ENDIF
[97]1017          ENDDO
[1]1018
[97]1019       ELSE
1020
[121]1021          vg_vertical_gradient_level_ind(1) = nzt+1
1022          vg(nzt+1) = vg_surface
[667]1023          DO  k = nzt, nzb, -1
[177]1024             IF ( i < 11 ) THEN
1025                IF ( vg_vertical_gradient_level(i) > zu(k)  .AND. &
[1353]1026                     vg_vertical_gradient_level(i) <= 0.0_wp )  THEN
1027                   gradient = vg_vertical_gradient(i) / 100.0_wp
[177]1028                   vg_vertical_gradient_level_ind(i) = k + 1
1029                   i = i + 1
[97]1030                ENDIF
1031             ENDIF
[1353]1032             IF ( gradient /= 0.0_wp )  THEN
[97]1033                IF ( k /= nzt )  THEN
1034                   vg(k) = vg(k+1) - dzu(k+1) * gradient
1035                ELSE
[1353]1036                   vg(k)   = vg_surface - 0.5_wp * dzu(k+1) * gradient
1037                   vg(k+1) = vg_surface + 0.5_wp * dzu(k+1) * gradient
[97]1038                ENDIF
1039             ELSE
1040                vg(k) = vg(k+1)
1041             ENDIF
1042          ENDDO
1043
1044       ENDIF
1045
[1]1046!
[767]1047!--    In case of no given gradients for vg, choose a zero gradient
[1322]1048       IF ( vg_vertical_gradient_level(1) == -9999999.9_wp )  THEN
[1353]1049          vg_vertical_gradient_level(1) = 0.0_wp
[1]1050       ENDIF
1051
1052!
[767]1053!--    Let the initial wind profiles be the calculated ug/vg profiles or
1054!--    interpolate them from wind profile data (if given)
[1322]1055       IF ( u_profile(1) == 9999999.9_wp  .AND.  v_profile(1) == 9999999.9_wp )  THEN
[767]1056
1057          u_init = ug
1058          v_init = vg
1059
[1353]1060       ELSEIF ( u_profile(1) == 0.0_wp  .AND.  v_profile(1) == 0.0_wp )  THEN
[767]1061
[1353]1062          IF ( uv_heights(1) /= 0.0_wp )  THEN
[767]1063             message_string = 'uv_heights(1) must be 0.0'
1064             CALL message( 'check_parameters', 'PA0345', 1, 2, 0, 6, 0 )
1065          ENDIF
1066
1067          use_prescribed_profile_data = .TRUE.
1068
1069          kk = 1
[1353]1070          u_init(0) = 0.0_wp
1071          v_init(0) = 0.0_wp
[767]1072
1073          DO  k = 1, nz+1
1074
1075             IF ( kk < 100 )  THEN
1076                DO WHILE ( uv_heights(kk+1) <= zu(k) )
1077                   kk = kk + 1
1078                   IF ( kk == 100 )  EXIT
1079                ENDDO
1080             ENDIF
1081
[1322]1082             IF ( kk < 100 .AND. uv_heights(kk+1) /= 9999999.9_wp )  THEN
[767]1083                u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
1084                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
1085                                       ( u_profile(kk+1) - u_profile(kk) )
1086                v_init(k) = v_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
1087                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
1088                                       ( v_profile(kk+1) - v_profile(kk) )
1089             ELSE
1090                u_init(k) = u_profile(kk)
1091                v_init(k) = v_profile(kk)
1092             ENDIF
1093
1094          ENDDO
1095
1096       ELSE
1097
1098          message_string = 'u_profile(1) and v_profile(1) must be 0.0'
1099          CALL message( 'check_parameters', 'PA0346', 1, 2, 0, 6, 0 )
1100
1101       ENDIF
1102
1103!
[94]1104!--    Compute initial temperature profile using the given temperature gradients
[940]1105       IF ( .NOT. neutral )  THEN
[94]1106
[940]1107          i = 1
[1353]1108          gradient = 0.0_wp
[94]1109
[940]1110          IF ( .NOT. ocean )  THEN
1111
1112             pt_vertical_gradient_level_ind(1) = 0
1113             DO  k = 1, nzt+1
1114                IF ( i < 11 ) THEN
1115                   IF ( pt_vertical_gradient_level(i) < zu(k)  .AND. &
[1353]1116                        pt_vertical_gradient_level(i) >= 0.0_wp )  THEN
1117                      gradient = pt_vertical_gradient(i) / 100.0_wp
[940]1118                      pt_vertical_gradient_level_ind(i) = k - 1
1119                      i = i + 1
1120                   ENDIF
[1]1121                ENDIF
[1353]1122                IF ( gradient /= 0.0_wp )  THEN
[940]1123                   IF ( k /= 1 )  THEN
1124                      pt_init(k) = pt_init(k-1) + dzu(k) * gradient
1125                   ELSE
[1174]1126                      pt_init(k) = pt_surface   + dzu(k) * gradient
[940]1127                   ENDIF
[94]1128                ELSE
[940]1129                   pt_init(k) = pt_init(k-1)
[94]1130                ENDIF
[940]1131             ENDDO
[1]1132
[940]1133          ELSE
[94]1134
[940]1135             pt_vertical_gradient_level_ind(1) = nzt+1
1136             DO  k = nzt, 0, -1
1137                IF ( i < 11 ) THEN
1138                   IF ( pt_vertical_gradient_level(i) > zu(k)  .AND. &
[1353]1139                        pt_vertical_gradient_level(i) <= 0.0_wp )  THEN
1140                      gradient = pt_vertical_gradient(i) / 100.0_wp
[940]1141                      pt_vertical_gradient_level_ind(i) = k + 1
1142                      i = i + 1
1143                   ENDIF
[94]1144                ENDIF
[1353]1145                IF ( gradient /= 0.0_wp )  THEN
[940]1146                   IF ( k /= nzt )  THEN
1147                      pt_init(k) = pt_init(k+1) - dzu(k+1) * gradient
1148                   ELSE
[1353]1149                      pt_init(k)   = pt_surface - 0.5_wp * dzu(k+1) * gradient
1150                      pt_init(k+1) = pt_surface + 0.5_wp * dzu(k+1) * gradient
[940]1151                   ENDIF
[94]1152                ELSE
[940]1153                   pt_init(k) = pt_init(k+1)
[94]1154                ENDIF
[940]1155             ENDDO
[94]1156
[940]1157          ENDIF
1158
[94]1159       ENDIF
1160
[1]1161!
1162!--    In case of no given temperature gradients, choose gradient of neutral
1163!--    stratification
[1322]1164       IF ( pt_vertical_gradient_level(1) == -9999999.9_wp )  THEN
[1353]1165          pt_vertical_gradient_level(1) = 0.0_wp
[1]1166       ENDIF
1167
1168!
[94]1169!--    Store temperature gradient at the top boundary for possible Neumann
[1]1170!--    boundary condition
[19]1171       bc_pt_t_val = ( pt_init(nzt+1) - pt_init(nzt) ) / dzu(nzt+1)
[1]1172
1173!
1174!--    If required, compute initial humidity or scalar profile using the given
1175!--    humidity/scalar gradient. In case of scalar transport, initially store
1176!--    values of the scalar parameters on humidity parameters
1177       IF ( passive_scalar )  THEN
1178          bc_q_b                    = bc_s_b
1179          bc_q_t                    = bc_s_t
1180          q_surface                 = s_surface
1181          q_surface_initial_change  = s_surface_initial_change
1182          q_vertical_gradient       = s_vertical_gradient
1183          q_vertical_gradient_level = s_vertical_gradient_level
1184          surface_waterflux         = surface_scalarflux
[407]1185          wall_humidityflux         = wall_scalarflux
[1]1186       ENDIF
1187
[75]1188       IF ( humidity  .OR.  passive_scalar )  THEN
[1]1189
1190          i = 1
[1353]1191          gradient = 0.0_wp
[1]1192          q_vertical_gradient_level_ind(1) = 0
1193          DO  k = 1, nzt+1
[177]1194             IF ( i < 11 ) THEN
1195                IF ( q_vertical_gradient_level(i) < zu(k)  .AND. &
[1353]1196                     q_vertical_gradient_level(i) >= 0.0_wp )  THEN
1197                   gradient = q_vertical_gradient(i) / 100.0_wp
[177]1198                   q_vertical_gradient_level_ind(i) = k - 1
1199                   i = i + 1
[1]1200                ENDIF
1201             ENDIF
[1353]1202             IF ( gradient /= 0.0_wp )  THEN
[1]1203                IF ( k /= 1 )  THEN
1204                   q_init(k) = q_init(k-1) + dzu(k) * gradient
1205                ELSE
[1174]1206                   q_init(k) = q_init(k-1) + dzu(k) * gradient
[1]1207                ENDIF
1208             ELSE
1209                q_init(k) = q_init(k-1)
1210             ENDIF
[72]1211!
1212!--          Avoid negative humidities
[1353]1213             IF ( q_init(k) < 0.0_wp )  THEN
1214                q_init(k) = 0.0_wp
[72]1215             ENDIF
[1]1216          ENDDO
1217
1218!
1219!--       In case of no given humidity gradients, choose zero gradient
1220!--       conditions
[1353]1221          IF ( q_vertical_gradient_level(1) == -1.0_wp )  THEN
1222             q_vertical_gradient_level(1) = 0.0_wp
[1]1223          ENDIF
1224!
[1053]1225!--       Store humidity, rain water content and rain drop concentration
1226!--       gradient at the top boundary for possile Neumann boundary condition
1227          bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
[1]1228       ENDIF
1229
[94]1230!
1231!--    If required, compute initial salinity profile using the given salinity
1232!--    gradients
1233       IF ( ocean )  THEN
1234
1235          i = 1
[1353]1236          gradient = 0.0_wp
[94]1237
1238          sa_vertical_gradient_level_ind(1) = nzt+1
1239          DO  k = nzt, 0, -1
[177]1240             IF ( i < 11 ) THEN
1241                IF ( sa_vertical_gradient_level(i) > zu(k)  .AND. &
[1353]1242                     sa_vertical_gradient_level(i) <= 0.0_wp )  THEN
1243                   gradient = sa_vertical_gradient(i) / 100.0_wp
[177]1244                   sa_vertical_gradient_level_ind(i) = k + 1
1245                   i = i + 1
[94]1246                ENDIF
1247             ENDIF
[1353]1248             IF ( gradient /= 0.0_wp )  THEN
[94]1249                IF ( k /= nzt )  THEN
1250                   sa_init(k) = sa_init(k+1) - dzu(k+1) * gradient
1251                ELSE
[1353]1252                   sa_init(k)   = sa_surface - 0.5_wp * dzu(k+1) * gradient
1253                   sa_init(k+1) = sa_surface + 0.5_wp * dzu(k+1) * gradient
[94]1254                ENDIF
1255             ELSE
1256                sa_init(k) = sa_init(k+1)
1257             ENDIF
1258          ENDDO
1259
1260       ENDIF
1261
[138]1262!
[388]1263!--    If required compute the profile of leaf area density used in the plant
1264!--    canopy model
[138]1265       IF ( plant_canopy ) THEN
1266       
1267          i = 1
[1353]1268          gradient = 0.0_wp
[1]1269
[138]1270          IF ( .NOT. ocean ) THEN
[153]1271
1272             lad(0) = lad_surface
[138]1273 
1274             lad_vertical_gradient_level_ind(1) = 0
1275             DO k = 1, pch_index
[177]1276                IF ( i < 11 ) THEN
1277                   IF ( lad_vertical_gradient_level(i) < zu(k) .AND.  &
[1353]1278                        lad_vertical_gradient_level(i) >= 0.0_wp ) THEN
[177]1279                      gradient = lad_vertical_gradient(i)
1280                      lad_vertical_gradient_level_ind(i) = k - 1
1281                      i = i + 1
[138]1282                   ENDIF
1283                ENDIF
[1353]1284                IF ( gradient /= 0.0_wp ) THEN
[138]1285                   IF ( k /= 1 ) THEN
1286                      lad(k) = lad(k-1) + dzu(k) * gradient
1287                   ELSE
[1174]1288                      lad(k) = lad_surface + dzu(k) *gradient
[138]1289                   ENDIF
1290                ELSE
1291                   lad(k) = lad(k-1)
1292                ENDIF
1293             ENDDO
1294
1295          ENDIF
1296
[1]1297!
[388]1298!--       In case of no given leaf area density gradients, choose a vanishing
1299!--       gradient
[1322]1300          IF ( lad_vertical_gradient_level(1) == -9999999.9_wp ) THEN
[1353]1301             lad_vertical_gradient_level(1) = 0.0_wp
[138]1302          ENDIF
1303
1304       ENDIF
1305         
1306    ENDIF
[411]1307
1308!
[1365]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!
[411]1321!-- Initialize large scale subsidence if required
[1299]1322    If ( large_scale_subsidence )  THEN
[1322]1323       IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp .AND. &
[1299]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
[667]1330
[1322]1331       IF ( subs_vertical_gradient_level(1) == -9999999.9_wp .AND. &
[1299]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
[1322]1340        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp )  THEN
[1299]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
[138]1347!
[1]1348!-- Compute Coriolis parameter
[1353]1349    f  = 2.0_wp * omega * SIN( phi / 180.0_wp * pi )
1350    fs = 2.0_wp * omega * COS( phi / 180.0_wp * pi )
[1]1351
1352!
[1179]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.
[1322]1360       IF ( pt_reference == 9999999.9_wp )  pt_reference = pt_surface
[1353]1361       vpt_reference = pt_reference * ( 1.0_wp + 0.61_wp * q_surface )
[1179]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
[57]1367
1368!
[1179]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
[97]1374
1375!
1376!-- Sign of buoyancy/stability terms
[1353]1377    IF ( ocean )  atmos_ocean_sign = -1.0_wp
[97]1378
1379!
[108]1380!-- Ocean version must use flux boundary conditions at the top
1381    IF ( ocean .AND. .NOT. use_top_fluxes )  THEN
[1327]1382       message_string = 'use_top_fluxes must be .TRUE. in ocean mode'
[226]1383       CALL message( 'check_parameters', 'PA0042', 1, 2, 0, 6, 0 )
[108]1384    ENDIF
[97]1385
1386!
[1]1387!-- In case of a given slope, compute the relevant quantities
[1353]1388    IF ( alpha_surface /= 0.0_wp )  THEN
1389       IF ( ABS( alpha_surface ) > 90.0_wp )  THEN
[215]1390          WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface, &
1391                                     ' ) must be < 90.0'
[226]1392          CALL message( 'check_parameters', 'PA0043', 1, 2, 0, 6, 0 )
[1]1393       ENDIF
1394       sloping_surface = .TRUE.
[1353]1395       cos_alpha_surface = COS( alpha_surface / 180.0_wp * pi )
1396       sin_alpha_surface = SIN( alpha_surface / 180.0_wp * pi )
[1]1397    ENDIF
1398
1399!
1400!-- Check time step and cfl_factor
[1353]1401    IF ( dt /= -1.0_wp )  THEN
1402       IF ( dt <= 0.0_wp  .AND.  dt /= -1.0_wp )  THEN
[215]1403          WRITE( message_string, * ) 'dt = ', dt , ' <= 0.0'
[226]1404          CALL message( 'check_parameters', 'PA0044', 1, 2, 0, 6, 0 )
[1]1405       ENDIF
1406       dt_3d = dt
1407       dt_fixed = .TRUE.
1408    ENDIF
1409
[1353]1410    IF ( cfl_factor <= 0.0_wp  .OR.  cfl_factor > 1.0_wp )  THEN
1411       IF ( cfl_factor == -1.0_wp )  THEN
[1001]1412          IF ( timestep_scheme == 'runge-kutta-2' )  THEN
[1353]1413             cfl_factor = 0.8_wp
[1001]1414          ELSEIF ( timestep_scheme == 'runge-kutta-3' )  THEN
[1353]1415             cfl_factor = 0.9_wp
[1]1416          ELSE
[1353]1417             cfl_factor = 0.9_wp
[1]1418          ENDIF
1419       ELSE
[215]1420          WRITE( message_string, * ) 'cfl_factor = ', cfl_factor, &
1421                 ' out of range & 0.0 < cfl_factor <= 1.0 is required'
[226]1422          CALL message( 'check_parameters', 'PA0045', 1, 2, 0, 6, 0 )
[1]1423       ENDIF
1424    ENDIF
1425
1426!
1427!-- Store simulated time at begin
1428    simulated_time_at_begin = simulated_time
1429
1430!
[291]1431!-- Store reference time for coupled runs and change the coupling flag,
1432!-- if ...
[1353]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
[291]1437          run_coupled = .FALSE.
1438       ENDIF
1439    ENDIF
1440
1441!
[1]1442!-- Set wind speed in the Galilei-transformed system
1443    IF ( galilei_transformation )  THEN
[1353]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
[1327]1454          message_string = 'baroclinity (ug) not allowed simultaneously' // &
[215]1455                           ' with galilei transformation'
[226]1456          CALL message( 'check_parameters', 'PA0046', 1, 2, 0, 6, 0 )
[1353]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
[1327]1460          message_string = 'baroclinity (vg) not allowed simultaneously' // &
[215]1461                           ' with galilei transformation'
[226]1462          CALL message( 'check_parameters', 'PA0047', 1, 2, 0, 6, 0 )
[1]1463       ELSE
[215]1464          message_string = 'variable translation speed used for galilei-' // &
1465             'transformation, which may cause & instabilities in stably ' // &
1466             'stratified regions'
[226]1467          CALL message( 'check_parameters', 'PA0048', 0, 1, 0, 6, 0 )
[1]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
[73]1479    IF ( bc_lr /= 'cyclic'  .AND.  bc_lr /= 'dirichlet/radiation'  .AND. &
[1159]1480         bc_lr /= 'radiation/dirichlet' )  THEN
[215]1481       message_string = 'unknown boundary condition: bc_lr = "' // &
1482                        TRIM( bc_lr ) // '"'
[226]1483       CALL message( 'check_parameters', 'PA0049', 1, 2, 0, 6, 0 )
[1]1484    ENDIF
[73]1485    IF ( bc_ns /= 'cyclic'  .AND.  bc_ns /= 'dirichlet/radiation'  .AND. &
[1159]1486         bc_ns /= 'radiation/dirichlet' )  THEN
[215]1487       message_string = 'unknown boundary condition: bc_ns = "' // &
1488                        TRIM( bc_ns ) // '"'
[226]1489       CALL message( 'check_parameters', 'PA0050', 1, 2, 0, 6, 0 )
[1]1490    ENDIF
1491
1492!
[366]1493!-- Internal variables used for speed optimization in if clauses
[707]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.
[366]1500
1501!
[1]1502!-- Non-cyclic lateral boundaries require the multigrid method and Piascek-
[667]1503!-- Willimas or Wicker - Skamarock advection scheme. Several schemes
1504!-- and tools do not work with non-cyclic boundary conditions.
[1]1505    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1506       IF ( psolver /= 'multigrid' )  THEN
[215]1507          message_string = 'non-cyclic lateral boundaries do not allow ' // &
1508                           'psolver = "' // TRIM( psolver ) // '"'
[226]1509          CALL message( 'check_parameters', 'PA0051', 1, 2, 0, 6, 0 )
[1]1510       ENDIF
[667]1511       IF ( momentum_advec /= 'pw-scheme' .AND. &
1512            momentum_advec /= 'ws-scheme')  THEN
[215]1513          message_string = 'non-cyclic lateral boundaries do not allow ' // &
1514                           'momentum_advec = "' // TRIM( momentum_advec ) // '"'
[226]1515          CALL message( 'check_parameters', 'PA0052', 1, 2, 0, 6, 0 )
[1]1516       ENDIF
[667]1517       IF ( scalar_advec /= 'pw-scheme' .AND. &
1518            scalar_advec /= 'ws-scheme' )  THEN
[215]1519          message_string = 'non-cyclic lateral boundaries do not allow ' // &
1520                           'scalar_advec = "' // TRIM( scalar_advec ) // '"'
[226]1521          CALL message( 'check_parameters', 'PA0053', 1, 2, 0, 6, 0 )
[1]1522       ENDIF
1523       IF ( galilei_transformation )  THEN
[215]1524          message_string = 'non-cyclic lateral boundaries do not allow ' // &
1525                           'galilei_transformation = .T.'
[226]1526          CALL message( 'check_parameters', 'PA0054', 1, 2, 0, 6, 0 )
[1]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
[215]1539          message_string = 'boundary condition bc_e_b changed to "' // &
1540                           TRIM( bc_e_b ) // '"'
[226]1541          CALL message( 'check_parameters', 'PA0057', 0, 1, 0, 6, 0 )
[1]1542       ENDIF
1543    ELSE
[215]1544       message_string = 'unknown boundary condition: bc_e_b = "' // &
1545                        TRIM( bc_e_b ) // '"'
[226]1546       CALL message( 'check_parameters', 'PA0058', 1, 2, 0, 6, 0 )
[1]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
[215]1556       message_string = 'unknown boundary condition: bc_p_b = "' // &
1557                        TRIM( bc_p_b ) // '"'
[226]1558       CALL message( 'check_parameters', 'PA0059', 1, 2, 0, 6, 0 )
[1]1559    ENDIF
[1111]1560
[1]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
[215]1566       message_string = 'unknown boundary condition: bc_p_t = "' // &
1567                        TRIM( bc_p_t ) // '"'
[226]1568       CALL message( 'check_parameters', 'PA0061', 1, 2, 0, 6, 0 )
[1]1569    ENDIF
1570
1571!
1572!-- Boundary conditions for potential temperature
[102]1573    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
1574       ibc_pt_b = 2
[1]1575    ELSE
[102]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
[215]1581          message_string = 'unknown boundary condition: bc_pt_b = "' // &
1582                           TRIM( bc_pt_b ) // '"'
[226]1583          CALL message( 'check_parameters', 'PA0062', 1, 2, 0, 6, 0 )
[1]1584       ENDIF
1585    ENDIF
[102]1586
[1]1587    IF ( bc_pt_t == 'dirichlet' )  THEN
1588       ibc_pt_t = 0
1589    ELSEIF ( bc_pt_t == 'neumann' )  THEN
1590       ibc_pt_t = 1
[19]1591    ELSEIF ( bc_pt_t == 'initial_gradient' )  THEN
1592       ibc_pt_t = 2
[1]1593    ELSE
[215]1594       message_string = 'unknown boundary condition: bc_pt_t = "' // &
1595                        TRIM( bc_pt_t ) // '"'
[226]1596       CALL message( 'check_parameters', 'PA0063', 1, 2, 0, 6, 0 )
[1]1597    ENDIF
1598
[1322]1599    IF ( surface_heatflux == 9999999.9_wp  )  THEN
[1276]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
[1241]1611    ELSE
[1276]1612        constant_heatflux = .TRUE.
[1241]1613        IF ( TRIM( initializing_actions ) /= 'read_restart_data' .AND. &
1614               large_scale_forcing ) THEN
[1276]1615           surface_heatflux = shf_surf(1)
[1241]1616        ENDIF
1617    ENDIF
1618
[1322]1619    IF ( top_heatflux     == 9999999.9_wp )  constant_top_heatflux = .FALSE.
[940]1620
1621    IF ( neutral )  THEN
1622
[1353]1623       IF ( surface_heatflux /= 0.0_wp  .AND.  surface_heatflux /= 9999999.9_wp ) &
[940]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
[1322]1629       IF ( top_heatflux /= 0.0  .AND.  top_heatflux /= 9999999.9_wp ) &
[940]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
[1322]1637    IF ( top_momentumflux_u /= 9999999.9_wp  .AND.  &
1638         top_momentumflux_v /= 9999999.9_wp )  THEN
[103]1639       constant_top_momentumflux = .TRUE.
[1322]1640    ELSEIF (  .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.  &
1641           top_momentumflux_v == 9999999.9_wp ) )  THEN
[215]1642       message_string = 'both, top_momentumflux_u AND top_momentumflux_v ' // &
1643                        'must be set'
[226]1644       CALL message( 'check_parameters', 'PA0064', 1, 2, 0, 6, 0 )
[103]1645    ENDIF
[1]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. &
[1353]1652         surface_heatflux /= 0.0_wp )  THEN
[215]1653       message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //&
1654                        '& is not allowed with constant_heatflux = .TRUE.'
[226]1655       CALL message( 'check_parameters', 'PA0065', 1, 2, 0, 6, 0 )
[1]1656    ENDIF
[1353]1657    IF ( constant_heatflux  .AND.  pt_surface_initial_change /= 0.0_wp )  THEN
[215]1658       WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo', &
1659               'wed with pt_surface_initial_change (/=0) = ', &
1660               pt_surface_initial_change
[226]1661       CALL message( 'check_parameters', 'PA0066', 1, 2, 0, 6, 0 )
[1]1662    ENDIF
1663
1664!
[19]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. &
[1353]1669         top_heatflux /= 0.0_wp )  THEN
[215]1670       message_string = 'boundary_condition: bc_pt_t = "' // TRIM( bc_pt_t ) //&
1671                        '" is not allowed with constant_top_heatflux = .TRUE.'
[226]1672       CALL message( 'check_parameters', 'PA0067', 1, 2, 0, 6, 0 )
[19]1673    ENDIF
1674
1675!
[95]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
[215]1683          message_string = 'unknown boundary condition: bc_sa_t = "' // &
1684                           TRIM( bc_sa_t ) // '"'
[226]1685          CALL message( 'check_parameters', 'PA0068', 1, 2, 0, 6, 0 )
[95]1686       ENDIF
1687
[1322]1688       IF ( top_salinityflux == 9999999.9_wp )  constant_top_salinityflux = .FALSE.
1689       IF ( ibc_sa_t == 1  .AND.   top_salinityflux == 9999999.9_wp )  THEN
[215]1690          message_string = 'boundary condition: bc_sa_t = "' // &
1691                           TRIM( bc_sa_t ) // '" requires to set ' // &
1692                           'top_salinityflux'
[226]1693          CALL message( 'check_parameters', 'PA0069', 1, 2, 0, 6, 0 )
[97]1694       ENDIF
[95]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. &
[1353]1701            top_salinityflux /= 0.0_wp )  THEN
[215]1702          message_string = 'boundary condition: bc_sa_t = "' // &
1703                           TRIM( bc_sa_t ) // '" is not allowed with ' // &
1704                           'constant_top_salinityflux = .TRUE.'
[226]1705          CALL message( 'check_parameters', 'PA0070', 1, 2, 0, 6, 0 )
[95]1706       ENDIF
1707
1708    ENDIF
1709
1710!
[75]1711!-- In case of humidity or passive scalar, set boundary conditions for total
[1]1712!-- water content / scalar
[75]1713    IF ( humidity  .OR.  passive_scalar ) THEN
1714       IF ( humidity )  THEN
[1]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
[215]1724          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
1725                           '_b ="' // TRIM( bc_q_b ) // '"'
[226]1726          CALL message( 'check_parameters', 'PA0071', 1, 2, 0, 6, 0 )
[1]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
[215]1733          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
1734                           '_t ="' // TRIM( bc_q_t ) // '"'
[226]1735          CALL message( 'check_parameters', 'PA0072', 1, 2, 0, 6, 0 )
[1]1736       ENDIF
1737
[1322]1738       IF ( surface_waterflux == 9999999.9_wp  )  THEN
[1276]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
[1241]1750       ELSE
[1276]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
[1241]1756       ENDIF
[1]1757
1758!
1759!--    A given surface humidity implies Dirichlet boundary condition for
[75]1760!--    humidity. In this case specification of a constant water flux is
[1]1761!--    forbidden.
1762       IF ( ibc_q_b == 0  .AND.  constant_waterflux )  THEN
[215]1763          message_string = 'boundary condition: bc_' // TRIM( sq ) // '_b ' // &
1764                           '= "' // TRIM( bc_q_b ) // '" is not allowed wi' // &
1765                           'th prescribed surface flux'
[226]1766          CALL message( 'check_parameters', 'PA0073', 1, 2, 0, 6, 0 )
[1]1767       ENDIF
[1353]1768       IF ( constant_waterflux  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
[215]1769          WRITE( message_string, * )  'a prescribed surface flux is not allo', &
1770                 'wed with ', sq, '_surface_initial_change (/=0) = ', &
1771                 q_surface_initial_change
[226]1772          CALL message( 'check_parameters', 'PA0074', 1, 2, 0, 6, 0 )
[1]1773       ENDIF
[1053]1774
[1]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
[215]1783          message_string = 'boundary condition: bc_uv_b = "' // &
1784               TRIM( bc_uv_b ) // '" is not allowed with prandtl_layer = .TRUE.'
[226]1785          CALL message( 'check_parameters', 'PA0075', 1, 2, 0, 6, 0 )
[1]1786       ENDIF
1787    ELSE
[215]1788       message_string = 'unknown boundary condition: bc_uv_b = "' // &
1789                        TRIM( bc_uv_b ) // '"'
[226]1790       CALL message( 'check_parameters', 'PA0076', 1, 2, 0, 6, 0 )
[1]1791    ENDIF
[667]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
[215]1798
[108]1799    IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1800       bc_uv_t = 'neumann'
[1]1801       ibc_uv_t = 1
1802    ELSE
[132]1803       IF ( bc_uv_t == 'dirichlet' .OR. bc_uv_t == 'dirichlet_0' )  THEN
[108]1804          ibc_uv_t = 0
[767]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
[1353]1809             u_init(nzt+1)    = 0.0_wp
1810             v_init(nzt+1)    = 0.0_wp
[767]1811          ENDIF
[108]1812       ELSEIF ( bc_uv_t == 'neumann' )  THEN
1813          ibc_uv_t = 1
1814       ELSE
[215]1815          message_string = 'unknown boundary condition: bc_uv_t = "' // &
1816                           TRIM( bc_uv_t ) // '"'
[226]1817          CALL message( 'check_parameters', 'PA0077', 1, 2, 0, 6, 0 )
[1]1818       ENDIF
1819    ENDIF
1820
1821!
1822!-- Compute and check, respectively, the Rayleigh Damping parameter
[1353]1823    IF ( rayleigh_damping_factor == -1.0_wp )  THEN
1824       rayleigh_damping_factor = 0.0_wp
[1]1825    ELSE
[1353]1826       IF ( rayleigh_damping_factor < 0.0 .OR. rayleigh_damping_factor > 1.0_wp ) &
[1]1827       THEN
[215]1828          WRITE( message_string, * )  'rayleigh_damping_factor = ', &
1829                              rayleigh_damping_factor, ' out of range [0.0,1.0]'
[226]1830          CALL message( 'check_parameters', 'PA0078', 1, 2, 0, 6, 0 )
[1]1831       ENDIF
1832    ENDIF
1833
[1353]1834    IF ( rayleigh_damping_height == -1.0_wp )  THEN
[108]1835       IF ( .NOT. ocean )  THEN
[1353]1836          rayleigh_damping_height = 0.66666666666_wp * zu(nzt)
[108]1837       ELSE
[1353]1838          rayleigh_damping_height = 0.66666666666_wp * zu(nzb)
[108]1839       ENDIF
[1]1840    ELSE
[108]1841       IF ( .NOT. ocean )  THEN
[1353]1842          IF ( rayleigh_damping_height < 0.0_wp  .OR. &
[108]1843               rayleigh_damping_height > zu(nzt) )  THEN
[215]1844             WRITE( message_string, * )  'rayleigh_damping_height = ', &
1845                   rayleigh_damping_height, ' out of range [0.0,', zu(nzt), ']'
[226]1846             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
[1]1847          ENDIF
[108]1848       ELSE
[1353]1849          IF ( rayleigh_damping_height > 0.0_wp  .OR. &
[108]1850               rayleigh_damping_height < zu(nzb) )  THEN
[215]1851             WRITE( message_string, * )  'rayleigh_damping_height = ', &
1852                   rayleigh_damping_height, ' out of range [0.0,', zu(nzb), ']'
[226]1853             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
[108]1854          ENDIF
[1]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
[215]1863       WRITE ( message_string, * ) 'number of statistic_regions = ', &
1864                   statistic_regions+1, ' but only 10 regions are allowed'
[226]1865       CALL message( 'check_parameters', 'PA0082', 1, 2, 0, 6, 0 )
[1]1866    ENDIF
1867    IF ( normalizing_region > statistic_regions  .OR. &
1868         normalizing_region < 0)  THEN
[215]1869       WRITE ( message_string, * ) 'normalizing_region = ', &
1870                normalizing_region, ' must be >= 0 and <= ',statistic_regions, &
1871                ' (value of statistic_regions)'
[226]1872       CALL message( 'check_parameters', 'PA0083', 1, 2, 0, 6, 0 )
[1]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
[1322]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
[564]1886       DO  mid = 1, max_masks
[1322]1887          IF ( dt_domask(mid) == 9999999.9_wp )  dt_domask(mid)    = dt_data_output
[410]1888       ENDDO
[1]1889    ENDIF
1890
1891!
1892!-- Set the default skip time intervals for data output, if necessary
[1322]1893    IF ( skip_time_dopr    == 9999999.9_wp ) &
[1]1894                                       skip_time_dopr    = skip_time_data_output
[1322]1895    IF ( skip_time_dosp    == 9999999.9_wp ) &
[1]1896                                       skip_time_dosp    = skip_time_data_output
[1322]1897    IF ( skip_time_do2d_xy == 9999999.9_wp ) &
[1]1898                                       skip_time_do2d_xy = skip_time_data_output
[1322]1899    IF ( skip_time_do2d_xz == 9999999.9_wp ) &
[1]1900                                       skip_time_do2d_xz = skip_time_data_output
[1322]1901    IF ( skip_time_do2d_yz == 9999999.9_wp ) &
[1]1902                                       skip_time_do2d_yz = skip_time_data_output
[1322]1903    IF ( skip_time_do3d    == 9999999.9_wp ) &
[1]1904                                       skip_time_do3d    = skip_time_data_output
[1322]1905    IF ( skip_time_data_output_av == 9999999.9_wp ) &
[1]1906                                skip_time_data_output_av = skip_time_data_output
[564]1907    DO  mid = 1, max_masks
[1322]1908       IF ( skip_time_domask(mid) == 9999999.9_wp ) &
[410]1909                                skip_time_domask(mid)    = skip_time_data_output
1910    ENDDO
[1]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
[215]1916       WRITE( message_string, * )  'averaging_interval = ', &
1917             averaging_interval, ' must be <= dt_data_output = ', dt_data_output
[226]1918       CALL message( 'check_parameters', 'PA0085', 1, 2, 0, 6, 0 )
[1]1919    ENDIF
1920
[1322]1921    IF ( averaging_interval_pr == 9999999.9_wp )  THEN
[1]1922       averaging_interval_pr = averaging_interval
1923    ENDIF
1924
1925    IF ( averaging_interval_pr > dt_dopr )  THEN
[215]1926       WRITE( message_string, * )  'averaging_interval_pr = ', &
1927             averaging_interval_pr, ' must be <= dt_dopr = ', dt_dopr
[226]1928       CALL message( 'check_parameters', 'PA0086', 1, 2, 0, 6, 0 )
[1]1929    ENDIF
1930
[1322]1931    IF ( averaging_interval_sp == 9999999.9_wp )  THEN
[1]1932       averaging_interval_sp = averaging_interval
1933    ENDIF
1934
1935    IF ( averaging_interval_sp > dt_dosp )  THEN
[215]1936       WRITE( message_string, * )  'averaging_interval_sp = ', &
1937             averaging_interval_sp, ' must be <= dt_dosp = ', dt_dosp
[226]1938       CALL message( 'check_parameters', 'PA0087', 1, 2, 0, 6, 0 )
[1]1939    ENDIF
1940
1941!
1942!-- Set the default interval for profiles entering the temporal average
[1322]1943    IF ( dt_averaging_input_pr == 9999999.9_wp )  THEN
[1]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)
[1322]1950    IF ( dt_dots == 9999999.9_wp )  THEN
[1353]1951       IF ( averaging_interval_pr == 0.0_wp )  THEN
[1]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
[215]1961       WRITE( message_string, * )  'dt_averaging_input = ', &
1962                dt_averaging_input, ' must be <= averaging_interval = ', &
1963                averaging_interval
[226]1964       CALL message( 'check_parameters', 'PA0088', 1, 2, 0, 6, 0 )
[1]1965    ENDIF
1966
1967    IF ( dt_averaging_input_pr > averaging_interval_pr )  THEN
[215]1968       WRITE( message_string, * )  'dt_averaging_input_pr = ', &
1969                dt_averaging_input_pr, ' must be <= averaging_interval_pr = ', &
1970                averaging_interval_pr
[226]1971       CALL message( 'check_parameters', 'PA0089', 1, 2, 0, 6, 0 )
[1]1972    ENDIF
1973
1974!
[72]1975!-- Set the default value for the integration interval of precipitation amount
1976    IF ( precipitation )  THEN
[1322]1977       IF ( precipitation_amount_interval == 9999999.9_wp )  THEN
[72]1978          precipitation_amount_interval = dt_do2d_xy
1979       ELSE
1980          IF ( precipitation_amount_interval > dt_do2d_xy )  THEN
[215]1981             WRITE( message_string, * )  'precipitation_amount_interval = ', &
1982                 precipitation_amount_interval, ' must not be larger than ', &
1983                 'dt_do2d_xy = ', dt_do2d_xy
[226]1984             CALL message( 'check_parameters', 'PA0090', 1, 2, 0, 6, 0 )
[72]1985          ENDIF
1986       ENDIF
1987    ENDIF
1988
1989!
[1]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
[87]2004             dopr_unit(i)  = 'm/s'
[1]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
[87]2014             dopr_unit(i)  = 'm/s'
2015             hom(:,2,2,:)  = SPREAD( zu, 2, statistic_regions+1 )
[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
[87]2024             dopr_unit(i)  = 'm/s'
2025             hom(:,2,3,:)  = SPREAD( zw, 2, statistic_regions+1 )
[1]2026
2027          CASE ( 'pt', '#pt' )
2028             IF ( .NOT. cloud_physics ) THEN
2029                dopr_index(i) = 4
[87]2030                dopr_unit(i)  = 'K'
[1]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 )
[1353]2035                   hom(nzb,2,7,:)        = 0.0_wp    ! because zu(nzb) is negative
[1]2036                   data_output_pr(i)     = data_output_pr(i)(2:)
2037                ENDIF
2038             ELSE
2039                dopr_index(i) = 43
[87]2040                dopr_unit(i)  = 'K'
[1]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 )
[1353]2045                   hom(nzb,2,28,:)       = 0.0_wp    ! because zu(nzb) is negative
[1]2046                   data_output_pr(i)     = data_output_pr(i)(2:)
2047                ENDIF
2048             ENDIF
2049
2050          CASE ( 'e' )
2051             dopr_index(i)  = 8
[87]2052             dopr_unit(i)   = 'm2/s2'
[1]2053             hom(:,2,8,:)   = SPREAD( zu, 2, statistic_regions+1 )
[1353]2054             hom(nzb,2,8,:) = 0.0_wp
[1]2055
2056          CASE ( 'km', '#km' )
2057             dopr_index(i)  = 9
[87]2058             dopr_unit(i)   = 'm2/s'
[1]2059             hom(:,2,9,:)   = SPREAD( zu, 2, statistic_regions+1 )
[1353]2060             hom(nzb,2,9,:) = 0.0_wp
[1]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
[87]2069             dopr_unit(i)    = 'm2/s'
[1]2070             hom(:,2,10,:)   = SPREAD( zu, 2, statistic_regions+1 )
[1353]2071             hom(nzb,2,10,:) = 0.0_wp
[1]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
[87]2080             dopr_unit(i)    = 'm'
[1]2081             hom(:,2,11,:)   = SPREAD( zu, 2, statistic_regions+1 )
[1353]2082             hom(nzb,2,11,:) = 0.0_wp
[1]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
[87]2091             dopr_unit(i)  = 'm2/s2'
[1]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
[87]2097             dopr_unit(i)  = 'm2/s2'
[1]2098             hom(:,2,13,:) = SPREAD( zw, 2, statistic_regions+1 )
2099
2100          CASE ( 'w"v"' )
2101             dopr_index(i) = 14
[87]2102             dopr_unit(i)  = 'm2/s2'
[1]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
[87]2108             dopr_unit(i)  = 'm2/s2'
[1]2109             hom(:,2,15,:) = SPREAD( zw, 2, statistic_regions+1 )
2110
2111          CASE ( 'w"pt"' )
2112             dopr_index(i) = 16
[87]2113             dopr_unit(i)  = 'K m/s'
[1]2114             hom(:,2,16,:) = SPREAD( zw, 2, statistic_regions+1 )
2115
2116          CASE ( 'w*pt*' )
2117             dopr_index(i) = 17
[87]2118             dopr_unit(i)  = 'K m/s'
[1]2119             hom(:,2,17,:) = SPREAD( zw, 2, statistic_regions+1 )
2120
2121          CASE ( 'wpt' )
2122             dopr_index(i) = 18
[87]2123             dopr_unit(i)  = 'K m/s'
[1]2124             hom(:,2,18,:) = SPREAD( zw, 2, statistic_regions+1 )
2125
2126          CASE ( 'wu' )
2127             dopr_index(i) = 19
[87]2128             dopr_unit(i)  = 'm2/s2'
[1]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
[87]2134             dopr_unit(i)  = 'm2/s2'
[1]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
[87]2140             dopr_unit(i)  = 'K m/s'
[1]2141             hom(:,2,21,:) = SPREAD( zw, 2, statistic_regions+1 )
2142
2143          CASE ( 'wptBC' )
2144             dopr_index(i) = 22
[87]2145             dopr_unit(i)  = 'K m/s'
[1]2146             hom(:,2,22,:) = SPREAD( zw, 2, statistic_regions+1 )
2147
[96]2148          CASE ( 'sa', '#sa' )
2149             IF ( .NOT. ocean )  THEN
[215]2150                message_string = 'data_output_pr = ' // &
2151                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2152                                 'lemented for ocean = .FALSE.'
[226]2153                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
[96]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 )
[1353]2161                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
[96]2162                   data_output_pr(i)     = data_output_pr(i)(2:)
2163                ENDIF
2164             ENDIF
2165
[1]2166          CASE ( 'u*2' )
2167             dopr_index(i) = 30
[87]2168             dopr_unit(i)  = 'm2/s2'
[1]2169             hom(:,2,30,:) = SPREAD( zu, 2, statistic_regions+1 )
2170
2171          CASE ( 'v*2' )
2172             dopr_index(i) = 31
[87]2173             dopr_unit(i)  = 'm2/s2'
[1]2174             hom(:,2,31,:) = SPREAD( zu, 2, statistic_regions+1 )
2175
2176          CASE ( 'w*2' )
2177             dopr_index(i) = 32
[87]2178             dopr_unit(i)  = 'm2/s2'
[1]2179             hom(:,2,32,:) = SPREAD( zw, 2, statistic_regions+1 )
2180
2181          CASE ( 'pt*2' )
2182             dopr_index(i) = 33
[87]2183             dopr_unit(i)  = 'K2'
[1]2184             hom(:,2,33,:) = SPREAD( zu, 2, statistic_regions+1 )
2185
2186          CASE ( 'e*' )
2187             dopr_index(i) = 34
[87]2188             dopr_unit(i)  = 'm2/s2'
[1]2189             hom(:,2,34,:) = SPREAD( zu, 2, statistic_regions+1 )
2190
2191          CASE ( 'w*2pt*' )
2192             dopr_index(i) = 35
[87]2193             dopr_unit(i)  = 'K m2/s2'
[1]2194             hom(:,2,35,:) = SPREAD( zw, 2, statistic_regions+1 )
2195
2196          CASE ( 'w*pt*2' )
2197             dopr_index(i) = 36
[87]2198             dopr_unit(i)  = 'K2 m/s'
[1]2199             hom(:,2,36,:) = SPREAD( zw, 2, statistic_regions+1 )
2200
2201          CASE ( 'w*e*' )
2202             dopr_index(i) = 37
[87]2203             dopr_unit(i)  = 'm3/s3'
[1]2204             hom(:,2,37,:) = SPREAD( zw, 2, statistic_regions+1 )
2205
2206          CASE ( 'w*3' )
2207             dopr_index(i) = 38
[87]2208             dopr_unit(i)  = 'm3/s3'
[1]2209             hom(:,2,38,:) = SPREAD( zw, 2, statistic_regions+1 )
2210
2211          CASE ( 'Sw' )
2212             dopr_index(i) = 39
[89]2213             dopr_unit(i)  = 'none'
[1]2214             hom(:,2,39,:) = SPREAD( zw, 2, statistic_regions+1 )
2215
[232]2216          CASE ( 'p' )
2217             dopr_index(i) = 40
2218             dopr_unit(i)  = 'Pa'
2219             hom(:,2,40,:) = SPREAD( zu, 2, statistic_regions+1 )
2220
[1]2221          CASE ( 'q', '#q' )
[108]2222             IF ( .NOT. humidity )  THEN
[215]2223                message_string = 'data_output_pr = ' // &
2224                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2225                                 'lemented for humidity = .FALSE.'
[226]2226                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
[1]2227             ELSE
2228                dopr_index(i) = 41
[87]2229                dopr_unit(i)  = 'kg/kg'
2230                hom(:,2,41,:) = SPREAD( zu, 2, statistic_regions+1 )
[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 )
[1353]2234                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
[1]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
[215]2241                message_string = 'data_output_pr = ' // &
2242                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2243                                 'lemented for passive_scalar = .FALSE.'
[226]2244                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
[1]2245             ELSE
2246                dopr_index(i) = 41
[87]2247                dopr_unit(i)  = 'kg/m3'
2248                hom(:,2,41,:) = SPREAD( zu, 2, statistic_regions+1 )
[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 )
[1353]2252                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
[1]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
[87]2260                dopr_unit(i)  = 'kg/kg'
2261                hom(:,2,41,:) = SPREAD( zu, 2, statistic_regions+1 )
[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 )
[1353]2265                   hom(nzb,2,26,:)       = 0.0_wp    ! because zu(nzb) is negative
[1]2266                   data_output_pr(i)     = data_output_pr(i)(2:)
2267                ENDIF
2268             ELSE
2269                dopr_index(i) = 42
[87]2270                dopr_unit(i)  = 'kg/kg'
2271                hom(:,2,42,:) = SPREAD( zu, 2, statistic_regions+1 )
[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 )
[1353]2275                   hom(nzb,2,27,:)       = 0.0_wp   ! because zu(nzb) is negative
[1]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
[215]2282                message_string = 'data_output_pr = ' // &
2283                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2284                                 'lemented for cloud_physics = .FALSE.'
[226]2285                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
[1]2286             ELSE
2287                dopr_index(i) = 4
[87]2288                dopr_unit(i)  = 'K'
[1]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 )
[1353]2293                   hom(nzb,2,7,:)        = 0.0_wp    ! because zu(nzb) is negative
[1]2294                   data_output_pr(i)     = data_output_pr(i)(2:)
2295                ENDIF
2296             ENDIF
2297
2298          CASE ( 'vpt', '#vpt' )
2299             dopr_index(i) = 44
[87]2300             dopr_unit(i)  = 'K'
2301             hom(:,2,44,:) = SPREAD( zu, 2, statistic_regions+1 )
[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 )
[1353]2305                hom(nzb,2,29,:)       = 0.0_wp    ! because zu(nzb) is negative
[1]2306                data_output_pr(i)     = data_output_pr(i)(2:)
2307             ENDIF
2308
2309          CASE ( 'w"vpt"' )
2310             dopr_index(i) = 45
[87]2311             dopr_unit(i)  = 'K m/s'
[1]2312             hom(:,2,45,:) = SPREAD( zw, 2, statistic_regions+1 )
2313
2314          CASE ( 'w*vpt*' )
2315             dopr_index(i) = 46
[87]2316             dopr_unit(i)  = 'K m/s'
[1]2317             hom(:,2,46,:) = SPREAD( zw, 2, statistic_regions+1 )
2318
2319          CASE ( 'wvpt' )
2320             dopr_index(i) = 47
[87]2321             dopr_unit(i)  = 'K m/s'
[1]2322             hom(:,2,47,:) = SPREAD( zw, 2, statistic_regions+1 )
2323
2324          CASE ( 'w"q"' )
[108]2325             IF ( .NOT. humidity )  THEN
[215]2326                message_string = 'data_output_pr = ' // &
2327                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2328                                 'lemented for humidity = .FALSE.'
[226]2329                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
[1]2330             ELSE
2331                dopr_index(i) = 48
[87]2332                dopr_unit(i)  = 'kg/kg m/s'
[1]2333                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
2334             ENDIF
2335
2336          CASE ( 'w*q*' )
[108]2337             IF ( .NOT. humidity )  THEN
[215]2338                message_string = 'data_output_pr = ' // &
2339                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2340                                 'lemented for humidity = .FALSE.'
[226]2341                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
[1]2342             ELSE
2343                dopr_index(i) = 49
[87]2344                dopr_unit(i)  = 'kg/kg m/s'
[1]2345                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
2346             ENDIF
2347
2348          CASE ( 'wq' )
[108]2349             IF ( .NOT. humidity )  THEN
[215]2350                message_string = 'data_output_pr = ' // &
2351                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2352                                 'lemented for humidity = .FALSE.'
[226]2353                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
[1]2354             ELSE
2355                dopr_index(i) = 50
[87]2356                dopr_unit(i)  = 'kg/kg m/s'
[1]2357                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
2358             ENDIF
2359
2360          CASE ( 'w"s"' )
2361             IF ( .NOT. passive_scalar ) THEN
[215]2362                message_string = 'data_output_pr = ' // &
2363                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2364                                 'lemented for passive_scalar = .FALSE.'
[226]2365                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
[1]2366             ELSE
2367                dopr_index(i) = 48
[87]2368                dopr_unit(i)  = 'kg/m3 m/s'
[1]2369                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
2370             ENDIF
2371
2372          CASE ( 'w*s*' )
2373             IF ( .NOT. passive_scalar ) THEN
[215]2374                message_string = 'data_output_pr = ' // &
2375                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2376                                 'lemented for passive_scalar = .FALSE.'
[226]2377                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
[1]2378             ELSE
2379                dopr_index(i) = 49
[87]2380                dopr_unit(i)  = 'kg/m3 m/s'
[1]2381                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
2382             ENDIF
2383
2384          CASE ( 'ws' )
2385             IF ( .NOT. passive_scalar ) THEN
[215]2386                message_string = 'data_output_pr = ' // &
2387                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2388                                 'lemented for passive_scalar = .FALSE.'
[226]2389                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
[1]2390             ELSE
2391                dopr_index(i) = 50
[87]2392                dopr_unit(i)  = 'kg/m3 m/s'
[1]2393                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
2394             ENDIF
2395
2396          CASE ( 'w"qv"' )
[75]2397             IF ( humidity  .AND.  .NOT. cloud_physics ) &
[1]2398             THEN
2399                dopr_index(i) = 48
[87]2400                dopr_unit(i)  = 'kg/kg m/s'
[1]2401                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
[75]2402             ELSEIF( humidity .AND. cloud_physics ) THEN
[1]2403                dopr_index(i) = 51
[87]2404                dopr_unit(i)  = 'kg/kg m/s'
[1]2405                hom(:,2,51,:) = SPREAD( zw, 2, statistic_regions+1 )
2406             ELSE
[215]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.'
[226]2411                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
[1]2412             ENDIF
2413
2414          CASE ( 'w*qv*' )
[75]2415             IF ( humidity  .AND.  .NOT. cloud_physics ) &
[1]2416             THEN
2417                dopr_index(i) = 49
[87]2418                dopr_unit(i)  = 'kg/kg m/s'
[1]2419                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
[75]2420             ELSEIF( humidity .AND. cloud_physics ) THEN
[1]2421                dopr_index(i) = 52
[87]2422                dopr_unit(i)  = 'kg/kg m/s'
[1]2423                hom(:,2,52,:) = SPREAD( zw, 2, statistic_regions+1 )
2424             ELSE
[215]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.'
[226]2429                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
[1]2430             ENDIF
2431
2432          CASE ( 'wqv' )
[75]2433             IF ( humidity  .AND.  .NOT. cloud_physics ) &
[1]2434             THEN
2435                dopr_index(i) = 50
[87]2436                dopr_unit(i)  = 'kg/kg m/s'
[1]2437                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
[75]2438             ELSEIF( humidity .AND. cloud_physics ) THEN
[1]2439                dopr_index(i) = 53
[87]2440                dopr_unit(i)  = 'kg/kg m/s'
[1]2441                hom(:,2,53,:) = SPREAD( zw, 2, statistic_regions+1 )
2442             ELSE
[1425]2443                message_string = 'data_output_pr = ' //                        &
[215]2444                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2445                                 'lemented for cloud_physics = .FALSE. an&' // &
2446                                 'd humidity = .FALSE.'
[226]2447                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
[1]2448             ENDIF
2449
2450          CASE ( 'ql' )
2451             IF ( .NOT. cloud_physics  .AND.  .NOT. cloud_droplets )  THEN
[1425]2452                message_string = 'data_output_pr = ' //                        &
[215]2453                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2454                                 'lemented for cloud_physics = .FALSE. or'  // &
2455                                 '&cloud_droplets = .FALSE.'
[226]2456                CALL message( 'check_parameters', 'PA0096', 1, 2, 0, 6, 0 )
[1]2457             ELSE
2458                dopr_index(i) = 54
[87]2459                dopr_unit(i)  = 'kg/kg'
[1]2460                hom(:,2,54,:)  = SPREAD( zu, 2, statistic_regions+1 )
2461             ENDIF
2462
[524]2463          CASE ( 'w*u*u*:dz' )
[1]2464             dopr_index(i) = 55
[87]2465             dopr_unit(i)  = 'm2/s3'
[1]2466             hom(:,2,55,:) = SPREAD( zu, 2, statistic_regions+1 )
2467
[524]2468          CASE ( 'w*p*:dz' )
[1]2469             dopr_index(i) = 56
[87]2470             dopr_unit(i)  = 'm2/s3'
[106]2471             hom(:,2,56,:) = SPREAD( zw, 2, statistic_regions+1 )
[1]2472
[524]2473          CASE ( 'w"e:dz' )
[1]2474             dopr_index(i) = 57
[87]2475             dopr_unit(i)  = 'm2/s3'
[1]2476             hom(:,2,57,:) = SPREAD( zu, 2, statistic_regions+1 )
2477
[667]2478
[1]2479          CASE ( 'u"pt"' )
2480             dopr_index(i) = 58
[87]2481             dopr_unit(i)  = 'K m/s'
[1]2482             hom(:,2,58,:) = SPREAD( zu, 2, statistic_regions+1 )
2483
2484          CASE ( 'u*pt*' )
2485             dopr_index(i) = 59
[87]2486             dopr_unit(i)  = 'K m/s'
[1]2487             hom(:,2,59,:) = SPREAD( zu, 2, statistic_regions+1 )
2488
2489          CASE ( 'upt_t' )
2490             dopr_index(i) = 60
[87]2491             dopr_unit(i)  = 'K m/s'
[1]2492             hom(:,2,60,:) = SPREAD( zu, 2, statistic_regions+1 )
2493
2494          CASE ( 'v"pt"' )
2495             dopr_index(i) = 61
[87]2496             dopr_unit(i)  = 'K m/s'
[1]2497             hom(:,2,61,:) = SPREAD( zu, 2, statistic_regions+1 )
2498             
2499          CASE ( 'v*pt*' )
2500             dopr_index(i) = 62
[87]2501             dopr_unit(i)  = 'K m/s'
[1]2502             hom(:,2,62,:) = SPREAD( zu, 2, statistic_regions+1 )
2503
2504          CASE ( 'vpt_t' )
2505             dopr_index(i) = 63
[87]2506             dopr_unit(i)  = 'K m/s'
[1]2507             hom(:,2,63,:) = SPREAD( zu, 2, statistic_regions+1 )
2508
[96]2509          CASE ( 'rho' )
[388]2510             IF ( .NOT. ocean ) THEN
[1425]2511                message_string = 'data_output_pr = ' //                        &
[388]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 )
[1179]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 )
[1353]2522                   hom(nzb,2,77,:)       = 0.0_wp    ! because zu(nzb) is negative
[1179]2523                   data_output_pr(i)     = data_output_pr(i)(2:)
2524                ENDIF
[388]2525             ENDIF
[1]2526
[96]2527          CASE ( 'w"sa"' )
2528             IF ( .NOT. ocean ) THEN
[1425]2529                message_string = 'data_output_pr = ' //                        &
[215]2530                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2531                                 'lemented for ocean = .FALSE.'
[226]2532                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
[96]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
[1425]2541                message_string = 'data_output_pr = ' //                        &
[215]2542                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2543                                 'lemented for ocean = .FALSE.'
[226]2544                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
[96]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
[1425]2553                message_string = 'data_output_pr = ' //                        &
[215]2554                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2555                                 'lemented for ocean = .FALSE.'
[226]2556                CALL message( 'check_parameters', 'PA0091', 1, 2, 0, 6, 0 )
[96]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
[106]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 )
[96]2567
[106]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
[197]2573          CASE ( 'q*2' )
2574             IF ( .NOT. humidity )  THEN
[1425]2575                message_string = 'data_output_pr = ' //                        &
[215]2576                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
2577                                 'lemented for humidity = .FALSE.'
[226]2578                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
[197]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
[106]2584
[388]2585          CASE ( 'prho' )
2586             IF ( .NOT. ocean ) THEN
[1425]2587                message_string = 'data_output_pr = ' //                        &
[388]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
[531]2599             dopr_unit(i)  = 'dbar'
[388]2600             hom(:,2,72,:) = SPREAD( zu, 2, statistic_regions+1 )
2601
[1053]2602          CASE ( 'nr' )
2603             IF ( .NOT. cloud_physics )  THEN
[1425]2604                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2609                message_string = 'data_output_pr = ' //                        &
[1053]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 )
[1115]2613             ELSEIF ( .NOT. precipitation )  THEN
[1425]2614                message_string = 'data_output_pr = ' //                        &
[1115]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 )
[1053]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
[1425]2626                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2631                message_string = 'data_output_pr = ' //                        &
[1053]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 )
[1115]2635             ELSEIF ( .NOT. precipitation )  THEN
[1425]2636                message_string = 'data_output_pr = ' //                        &
[1115]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 )
[1053]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
[1425]2648                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2653                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2665                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2670                message_string = 'data_output_pr = ' //                        &
[1053]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
[1425]2675                message_string = 'data_output_pr = ' //                        &
[1053]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
[1241]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
[1299]2696          CASE ( 'w_subs' )
2697             IF ( .NOT. large_scale_subsidence )  THEN
[1425]2698                message_string = 'data_output_pr = ' //                        &
[1299]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
[1365]2708          CASE ( 'td_lsa_lpt' )
2709             IF ( .NOT. large_scale_forcing )  THEN
[1425]2710                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2722                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2734                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2746                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2758                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2770                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2782                message_string = 'data_output_pr = ' //                        &
[1365]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
[1425]2794                message_string = 'data_output_pr = ' //                        &
[1365]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
[1]2805          CASE DEFAULT
[87]2806
2807             CALL user_check_data_output_pr( data_output_pr(i), i, unit )
2808
2809             IF ( unit == 'illegal' )  THEN
[215]2810                IF ( data_output_pr_user(1) /= ' ' )  THEN
[1425]2811                   message_string = 'illegal value for data_output_pr or ' //  &
2812                                    'data_output_pr_user = "' //               &
[215]2813                                    TRIM( data_output_pr(i) ) // '"'
[226]2814                   CALL message( 'check_parameters', 'PA0097', 1, 2, 0, 6, 0 )
[215]2815                ELSE
[1425]2816                   message_string = 'illegal value for data_output_pr = "' //  &
[215]2817                                    TRIM( data_output_pr(i) ) // '"'
[226]2818                   CALL message( 'check_parameters', 'PA0098', 1, 2, 0, 6, 0 )
[87]2819                ENDIF
[1]2820             ENDIF
2821
2822       END SELECT
[667]2823
[1]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
[215]2837             message_string = 'number of output quantitities given by data' // &
2838                '_output and data_output_user exceeds the limit of 100'
[226]2839             CALL message( 'check_parameters', 'PA0102', 1, 2, 0, 6, 0 )
[1]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
[1425]2867          IF ( data_output(i)(ilen-2:ilen) == '_xy'  .OR.                      &
2868               data_output(i)(ilen-2:ilen) == '_xz'  .OR.                      &
[1]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
[1425]2880                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2881                                 'res constant_diffusion = .FALSE.'
[226]2882                CALL message( 'check_parameters', 'PA0103', 1, 2, 0, 6, 0 )
[1]2883             ENDIF
2884             unit = 'm2/s2'
2885
[771]2886          CASE ( 'lpt' )
2887             IF ( .NOT. cloud_physics )  THEN
[1425]2888                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[773]2889                         'res cloud_physics = .TRUE.'
2890                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
[771]2891             ENDIF
2892             unit = 'K'
2893
[1053]2894          CASE ( 'nr' )
2895             IF ( .NOT. cloud_physics )  THEN
[1425]2896                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2897                         'res cloud_physics = .TRUE.'
2898                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
2899             ELSEIF ( icloud_scheme /= 0 )  THEN
[1425]2900                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2901                         'res cloud_scheme = seifert_beheng'
2902                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
2903             ENDIF
2904             unit = '1/m3'
2905
[1]2906          CASE ( 'pc', 'pr' )
2907             IF ( .NOT. particle_advection )  THEN
[215]2908                message_string = 'output of "' // TRIM( var ) // '" requir' // &
2909                   'es a "particles_par"-NAMELIST in the parameter file (PARIN)'
[226]2910                CALL message( 'check_parameters', 'PA0104', 1, 2, 0, 6, 0 )
[1]2911             ENDIF
2912             IF ( TRIM( var ) == 'pc' )  unit = 'number'
2913             IF ( TRIM( var ) == 'pr' )  unit = 'm'
2914
[1053]2915          CASE ( 'prr' )
2916             IF ( .NOT. cloud_physics )  THEN
[1425]2917                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2918                         'res cloud_physics = .TRUE.'
2919                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
2920             ELSEIF ( icloud_scheme /= 0 )  THEN
[1425]2921                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2922                         'res cloud_scheme = seifert_beheng'
2923                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
2924             ELSEIF ( .NOT. precipitation )  THEN
[1425]2925                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2926                                 'res precipitation = .TRUE.'
2927                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
2928             ENDIF
2929             unit = 'kg/kg m/s'
2930
[1]2931          CASE ( 'q', 'vpt' )
[75]2932             IF ( .NOT. humidity )  THEN
[1425]2933                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2934                                 'res humidity = .TRUE.'
[226]2935                CALL message( 'check_parameters', 'PA0105', 1, 2, 0, 6, 0 )
[1]2936             ENDIF
2937             IF ( TRIM( var ) == 'q'   )  unit = 'kg/kg'
2938             IF ( TRIM( var ) == 'vpt' )  unit = 'K'
2939
[1053]2940          CASE ( 'qc' )
2941             IF ( .NOT. cloud_physics )  THEN
[1425]2942                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2943                         'res cloud_physics = .TRUE.'
2944                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
2945             ELSEIF ( icloud_scheme /= 0 ) THEN
[1425]2946                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2947                         'res cloud_scheme = seifert_beheng'
2948                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
2949             ENDIF
2950             unit = 'kg/kg'
2951
[1]2952          CASE ( 'ql' )
2953             IF ( .NOT. ( cloud_physics  .OR.  cloud_droplets ) )  THEN
[1425]2954                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2955                         'res cloud_physics = .TRUE. or cloud_droplets = .TRUE.'
[226]2956                CALL message( 'check_parameters', 'PA0106', 1, 2, 0, 6, 0 )
[1]2957             ENDIF
2958             unit = 'kg/kg'
2959
2960          CASE ( 'ql_c', 'ql_v', 'ql_vp' )
2961             IF ( .NOT. cloud_droplets )  THEN
[1425]2962                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2963                                 'res cloud_droplets = .TRUE.'
[226]2964                CALL message( 'check_parameters', 'PA0107', 1, 2, 0, 6, 0 )
[1]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
[1053]2970          CASE ( 'qr' )
2971             IF ( .NOT. cloud_physics )  THEN
[1425]2972                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2973                         'res cloud_physics = .TRUE.'
2974                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
2975             ELSEIF ( icloud_scheme /= 0 ) THEN
[1425]2976                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1053]2977                         'res cloud_scheme = seifert_beheng'
2978                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
[1115]2979             ELSEIF ( .NOT. precipitation )  THEN
[1425]2980                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[1115]2981                                 'res precipitation = .TRUE.'
2982                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
[1053]2983             ENDIF
2984             unit = 'kg/kg'
2985
[1]2986          CASE ( 'qv' )
2987             IF ( .NOT. cloud_physics )  THEN
[1425]2988                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2989                                 'res cloud_physics = .TRUE.'
[226]2990                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
[1]2991             ENDIF
2992             unit = 'kg/kg'
2993
[96]2994          CASE ( 'rho' )
2995             IF ( .NOT. ocean )  THEN
[1425]2996                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]2997                                 'res ocean = .TRUE.'
[226]2998                CALL message( 'check_parameters', 'PA0109', 1, 2, 0, 6, 0 )
[96]2999             ENDIF
3000             unit = 'kg/m3'
3001
[1]3002          CASE ( 's' )
3003             IF ( .NOT. passive_scalar )  THEN
[1425]3004                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]3005                                 'res passive_scalar = .TRUE.'
[226]3006                CALL message( 'check_parameters', 'PA0110', 1, 2, 0, 6, 0 )
[1]3007             ENDIF
3008             unit = 'conc'
3009
[96]3010          CASE ( 'sa' )
3011             IF ( .NOT. ocean )  THEN
[1425]3012                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]3013                                 'res ocean = .TRUE.'
[226]3014                CALL message( 'check_parameters', 'PA0109', 1, 2, 0, 6, 0 )
[96]3015             ENDIF
3016             unit = 'psu'
3017
[978]3018          CASE ( 'u*', 't*', 'lwp*', 'pra*', 'prr*', 'qsws*', 'shf*', 'z0*', 'z0h*' )
[1]3019             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
[1425]3020                message_string = 'illegal value for data_output: "' //         &
3021                                 TRIM( var ) // '" & only 2d-horizontal ' //   &
[215]3022                                 'cross sections are allowed for this value'
[226]3023                CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
[1]3024             ENDIF
3025             IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. cloud_physics )  THEN
[1425]3026                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]3027                                 'res cloud_physics = .TRUE.'
[226]3028                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
[1]3029             ENDIF
[72]3030             IF ( TRIM( var ) == 'pra*'  .AND.  .NOT. precipitation )  THEN
[1425]3031                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]3032                                 'res precipitation = .TRUE.'
[226]3033                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
[72]3034             ENDIF
3035             IF ( TRIM( var ) == 'pra*'  .AND.  j == 1 )  THEN
[1425]3036                message_string = 'temporal averaging of precipitation ' //     &
[215]3037                          'amount "' // TRIM( var ) // '" is not possible'
[226]3038                CALL message( 'check_parameters', 'PA0113', 1, 2, 0, 6, 0 )
[72]3039             ENDIF
3040             IF ( TRIM( var ) == 'prr*'  .AND.  .NOT. precipitation )  THEN
[1425]3041                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[215]3042                                 'res precipitation = .TRUE.'
[226]3043                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
[72]3044             ENDIF
[354]3045             IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT. humidity )  THEN
[1425]3046                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
[354]3047                                 'res humidity = .TRUE.'
3048                CALL message( 'check_parameters', 'PA0322', 1, 2, 0, 6, 0 )
3049             ENDIF
[72]3050
[354]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'
[996]3059             IF ( TRIM( var ) == 'z0h*'   )  unit = 'm'
[72]3060
[1]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
[215]3074                IF ( data_output_user(1) /= ' ' )  THEN
[1425]3075                   message_string = 'illegal value for data_output or ' //     &
[215]3076                         'data_output_user = "' // TRIM( data_output(i) ) // '"'
[226]3077                   CALL message( 'check_parameters', 'PA0114', 1, 2, 0, 6, 0 )
[215]3078                ELSE
[1425]3079                   message_string = 'illegal value for data_output =' //       &
[215]3080                                    TRIM( data_output(i) ) // '"'
[226]3081                   CALL message( 'check_parameters', 'PA0115', 1, 2, 0, 6, 0 )
[1]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!
[376]3125!-- Averaged 2d or 3d output requires that an averaging interval has been set
[1353]3126    IF ( doav_n > 0  .AND.  averaging_interval == 0.0_wp )  THEN
[376]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!
[308]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
[1]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
[1353]3153    IF ( z_max_do2d == -1.0_wp )  z_max_do2d = zu(nzt)
[1]3154    IF ( z_max_do2d < zu(nzb+1)  .OR.  z_max_do2d > zu(nzt) )  THEN
[1425]3155       WRITE( message_string, * )  'z_max_do2d = ', z_max_do2d,                &
[215]3156                    ' must be >= ', zu(nzb+1), '(zu(nzb+1)) and <= ', zu(nzt), &
3157                    ' (zu(nzt))'
[226]3158       CALL message( 'check_parameters', 'PA0116', 1, 2, 0, 6, 0 )
[1]3159    ENDIF
3160
3161!
3162!-- Upper plot limit for 3D arrays
3163    IF ( nz_do3d == -9999 )  nz_do3d = nzt + 1
3164
3165!
[1031]3166!-- Set output format string (used in header)
[1327]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'
[1031]3180
[1327]3181    END SELECT
[1031]3182
[1236]3183#if defined( __spectra )
[1]3184!
[1236]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!
[410]3198!-- Check mask conditions
[553]3199    DO mid = 1, max_masks
[1425]3200       IF ( data_output_masks(mid,1) /= ' ' .OR.                               &
[567]3201            data_output_masks_user(mid,1) /= ' ' ) THEN
[553]3202          masks = masks + 1
3203       ENDIF
3204    ENDDO
3205   
[410]3206    IF ( masks < 0 .OR. masks > max_masks )  THEN
[1425]3207       WRITE( message_string, * )  'illegal value: masks must be >= 0 and ',   &
[410]3208            '<= ', max_masks, ' (=max_masks)'
[564]3209       CALL message( 'check_parameters', 'PA0325', 1, 2, 0, 6, 0 )
[410]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
[1353]3215       IF ( ANY( mask_scale <= 0.0_wp ) )  THEN
[1425]3216          WRITE( message_string, * )                                           &
3217               'illegal value: mask_scale_x, mask_scale_y and mask_scale_z',   &
[410]3218               'must be > 0.0'
[564]3219          CALL message( 'check_parameters', 'PA0326', 1, 2, 0, 6, 0 )
[410]3220       ENDIF
3221!
3222!--    Generate masks for masked data output
[1308]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
[410]3237       CALL init_masks
[1308]3238       netcdf_data_format = netcdf_data_format_save
[410]3239    ENDIF
3240
3241!
[493]3242!-- Check the NetCDF data format
[924]3243#if ! defined ( __check )
[1034]3244    IF ( netcdf_data_format > 2 )  THEN
[924]3245#if defined( __netcdf4 )
[493]3246       CONTINUE
3247#else
[1425]3248       message_string = 'netCDF: netCDF4 format requested but no ' //          &
3249                        'cpp-directive __netcdf4 given & switch '  //          &
[493]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
[1031]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
[892]3264#endif
[1031]3265    ENDIF
3266#endif
[667]3267
[1308]3268!
3269!-- Calculate fixed number of output time levels for parallel netcdf output.
[1327]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
[1425]3276       ntdim_3d(1)    = INT( ( end_time - skip_time_data_output_av )           &
[1327]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
[1308]3285       ENDIF
[1327]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
[1308]3290    ENDIF
3291
[809]3292#if ! defined( __check )
[1031]3293!
[1]3294!-- Check netcdf precison
3295    ldum = .FALSE.
3296    CALL define_netcdf_header( 'ch', ldum, 0 )
[807]3297#endif
[1]3298!
3299!-- Check, whether a constant diffusion coefficient shall be used
[1353]3300    IF ( km_constant /= -1.0_wp )  THEN
3301       IF ( km_constant < 0.0_wp )  THEN
[215]3302          WRITE( message_string, * )  'km_constant = ', km_constant, ' < 0.0'
[226]3303          CALL message( 'check_parameters', 'PA0121', 1, 2, 0, 6, 0 )
[1]3304       ELSE
[1353]3305          IF ( prandtl_number < 0.0_wp )  THEN
[1425]3306             WRITE( message_string, * )  'prandtl_number = ', prandtl_number,  &
[215]3307                                         ' < 0.0'
[226]3308             CALL message( 'check_parameters', 'PA0122', 1, 2, 0, 6, 0 )
[1]3309          ENDIF
3310          constant_diffusion = .TRUE.
3311
3312          IF ( prandtl_layer )  THEN
[1425]3313             message_string = 'prandtl_layer is not allowed with fixed ' //    &
[215]3314                              'value of km'
[226]3315             CALL message( 'check_parameters', 'PA0123', 1, 2, 0, 6, 0 )
[1]3316          ENDIF
3317       ENDIF
3318    ENDIF
3319
3320!
[978]3321!-- In case of non-cyclic lateral boundaries and a damping layer for the
3322!-- potential temperature, check the width of the damping layer
[1]3323    IF ( bc_lr /= 'cyclic' ) THEN
[1425]3324       IF ( pt_damping_width < 0.0_wp  .OR.                                    &
3325            pt_damping_width > REAL( nx * dx ) )  THEN
[978]3326          message_string = 'pt_damping_width out of range'
[226]3327          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
[1]3328       ENDIF
3329    ENDIF
3330
3331    IF ( bc_ns /= 'cyclic' )  THEN
[1425]3332       IF ( pt_damping_width < 0.0_wp  .OR.                                    &
3333            pt_damping_width > REAL( ny * dy ) )  THEN
[978]3334          message_string = 'pt_damping_width out of range'
[226]3335          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
[1]3336       ENDIF
3337    ENDIF
3338
3339!
3340!-- Check value range for rif
3341    IF ( rif_min >= rif_max )  THEN
[1425]3342       WRITE( message_string, * )  'rif_min = ', rif_min, ' must be less ',    &
[215]3343                                   'than rif_max = ', rif_max
[226]3344       CALL message( 'check_parameters', 'PA0125', 1, 2, 0, 6, 0 )
[1]3345    ENDIF
3346
3347!
[1425]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!
[1]3358!-- Determine upper and lower hight level indices for random perturbations
[1322]3359    IF ( disturbance_level_b == -9999999.9_wp )  THEN
[97]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
[1]3367    ELSEIF ( disturbance_level_b < zu(3) )  THEN
[1425]3368       WRITE( message_string, * )  'disturbance_level_b = ',                   &
[215]3369                           disturbance_level_b, ' must be >= ', zu(3), '(zu(3))'
[226]3370       CALL message( 'check_parameters', 'PA0126', 1, 2, 0, 6, 0 )
[1]3371    ELSEIF ( disturbance_level_b > zu(nzt-2) )  THEN
[1425]3372       WRITE( message_string, * )  'disturbance_level_b = ',                   &
[215]3373                   disturbance_level_b, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
[226]3374       CALL message( 'check_parameters', 'PA0127', 1, 2, 0, 6, 0 )
[1]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
[1322]3384    IF ( disturbance_level_t == -9999999.9_wp )  THEN
[97]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
[1]3392    ELSEIF ( disturbance_level_t > zu(nzt-2) )  THEN
[1425]3393       WRITE( message_string, * )  'disturbance_level_t = ',                   &
[215]3394                   disturbance_level_t, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
[226]3395       CALL message( 'check_parameters', 'PA0128', 1, 2, 0, 6, 0 )
[1]3396    ELSEIF ( disturbance_level_t < disturbance_level_b )  THEN
[1425]3397       WRITE( message_string, * )  'disturbance_level_t = ',                   &
3398                   disturbance_level_t, ' must be >= disturbance_level_b = ',  &
[215]3399                   disturbance_level_b
[226]3400       CALL message( 'check_parameters', 'PA0129', 1, 2, 0, 6, 0 )
[1]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
[1425]3415       WRITE( message_string, * )  'disturbance_level_ind_t = ',               &
[215]3416                disturbance_level_ind_t, ' must be >= disturbance_level_b = ', &
3417                disturbance_level_b
[226]3418       CALL message( 'check_parameters', 'PA0130', 1, 2, 0, 6, 0 )
[1]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.
[1425]3426   
[1]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
[215]3433          message_string = 'inflow_disturbance_begin out of range'
[226]3434          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
[1]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
[215]3441          message_string = 'inflow_disturbance_end out of range'
[226]3442          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
[1]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
[215]3450          message_string = 'inflow_disturbance_begin out of range'
[226]3451          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
[1]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
[215]3458          message_string = 'inflow_disturbance_end out of range'
[226]3459          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
[1]3460       ENDIF
3461    ENDIF
3462
[1425]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
[73]3497    ENDIF
[1]3498
3499!
[151]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)
[1159]3502    IF ( turbulent_inflow  .AND.  bc_lr /= 'dirichlet/radiation' )  THEN
[1425]3503       message_string = 'turbulent_inflow = .T. requires a Dirichlet ' //      &
[215]3504                        'condition at the inflow boundary'
[226]3505       CALL message( 'check_parameters', 'PA0133', 1, 2, 0, 6, 0 )
[151]3506    ENDIF
3507
3508!
[1060]3509!-- Turbulent inflow requires that 3d arrays have been cyclically filled with
[1103]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
[1425]3513       message_string = 'turbulent_inflow = .T. requires ' //                  &
[1060]3514                        'initializing_actions = ''cyclic_fill'' '
3515       CALL message( 'check_parameters', 'PA0055', 1, 2, 0, 6, 0 )
3516    ENDIF
3517
3518!
[151]3519!-- In case of turbulent inflow calculate the index of the recycling plane
3520    IF ( turbulent_inflow )  THEN
[1322]3521       IF ( recycling_width == 9999999.9_wp )  THEN
[151]3522!
3523!--       Set the default value for the width of the recycling domain
[1353]3524          recycling_width = 0.1_wp * nx * dx
[151]3525       ELSE
3526          IF ( recycling_width < dx  .OR.  recycling_width > nx * dx )  THEN
[215]3527             WRITE( message_string, * )  'illegal value for recycling_width:', &
3528                                         ' ', recycling_width
[226]3529             CALL message( 'check_parameters', 'PA0134', 1, 2, 0, 6, 0 )
[151]3530          ENDIF
3531       ENDIF
3532!
3533!--    Calculate the index
3534       recycling_plane = recycling_width / dx
3535    ENDIF
3536
3537!
[1]3538!-- Determine damping level index for 1D model
3539    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[1353]3540       IF ( damp_level_1d == -1.0_wp )  THEN
[1]3541          damp_level_1d     = zu(nzt+1)
3542          damp_level_ind_1d = nzt + 1
[1353]3543       ELSEIF ( damp_level_1d < 0.0_wp  .OR.  damp_level_1d > zu(nzt+1) )  THEN
[1425]3544          WRITE( message_string, * )  'damp_level_1d = ', damp_level_1d,       &
[215]3545                 ' must be > 0.0 and < ', zu(nzt+1), '(zu(nzt+1))'
[226]3546          CALL message( 'check_parameters', 'PA0136', 1, 2, 0, 6, 0 )
[1]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
[215]3556
[1]3557!
3558!-- Check some other 1d-model parameters
[1425]3559    IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                   &
[1]3560         TRIM( mixing_length_1d ) /= 'blackadar' )  THEN
[1425]3561       message_string = 'mixing_length_1d = "' // TRIM( mixing_length_1d ) //  &
[215]3562                        '" is unknown'
[226]3563       CALL message( 'check_parameters', 'PA0137', 1, 2, 0, 6, 0 )
[1]3564    ENDIF
[1425]3565    IF ( TRIM( dissipation_1d ) /= 'as_in_3d_model'  .AND.                     &
[1]3566         TRIM( dissipation_1d ) /= 'detering' )  THEN
[1425]3567       message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) //      &
[215]3568                        '" is unknown'
[226]3569       CALL message( 'check_parameters', 'PA0138', 1, 2, 0, 6, 0 )
[1]3570    ENDIF
3571
3572!
3573!-- Set time for the next user defined restart (time_restart is the
3574!-- internal parameter for steering restart events)
[1322]3575    IF ( restart_time /= 9999999.9_wp )  THEN
[291]3576       IF ( restart_time > time_since_reference_point )  THEN
3577          time_restart = restart_time
3578       ENDIF
[1]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
[1322]3583       time_restart = 9999999.9_wp
[1]3584    ENDIF
3585
3586!
3587!-- Set default value of the time needed to terminate a model run
[1353]3588    IF ( termination_time_needed == -1.0_wp )  THEN
[1]3589       IF ( host(1:3) == 'ibm' )  THEN
[1353]3590          termination_time_needed = 300.0_wp
[1]3591       ELSE
[1353]3592          termination_time_needed = 35.0_wp
[1]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
[1353]3602       IF ( termination_time_needed <= 30.0_wp )  THEN
[1425]3603          WRITE( message_string, * )  'termination_time_needed = ',            &
3604                 termination_time_needed, ' must be > 30.0 on host "',         &
[215]3605                 TRIM( host ), '"'
[226]3606          CALL message( 'check_parameters', 'PA0139', 1, 2, 0, 6, 0 )
[1]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
[1353]3613       IF ( termination_time_needed < 300.0_wp )  THEN
[1425]3614          WRITE( message_string, * )  'termination_time_needed = ',            &
3615                 termination_time_needed, ' should be >= 300.0 on host "',     &
[215]3616                 TRIM( host ), '"'
[226]3617          CALL message( 'check_parameters', 'PA0140', 1, 2, 0, 6, 0 )
[1]3618       ENDIF
3619    ENDIF
3620
[217]3621!
[240]3622!-- Check pressure gradient conditions
3623    IF ( dp_external .AND. conserve_volume_flow )  THEN
[388]3624       WRITE( message_string, * )  'Both dp_external and conserve_volume_flo', &
3625            'w are .TRUE. but one of them must be .FALSE.'
[240]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
[1353]3634       IF ( .NOT. ANY( dpdxy /= 0.0_wp ) )  THEN
[388]3635          WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is ze', &
3636               'ro, i.e. the external pressure gradient & will not be applied'
[240]3637          CALL message( 'check_parameters', 'PA0152', 0, 1, 0, 6, 0 )
3638       ENDIF
3639    ENDIF
[1353]3640    IF ( ANY( dpdxy /= 0.0_wp ) .AND. .NOT. dp_external )  THEN
[1425]3641       WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ',     &
[240]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
[241]3645    IF ( conserve_volume_flow )  THEN
3646       IF ( TRIM( conserve_volume_flow_mode ) == 'default' )  THEN
[667]3647
3648          conserve_volume_flow_mode = 'initial_profiles'
3649
[241]3650       ELSEIF ( TRIM( conserve_volume_flow_mode ) /= 'initial_profiles' .AND.  &
[1425]3651            TRIM( conserve_volume_flow_mode ) /= 'inflow_profile' .AND.        &
[241]3652            TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' )  THEN
[1425]3653          WRITE( message_string, * )  'unknown conserve_volume_flow_mode: ',   &
[241]3654               conserve_volume_flow_mode
3655          CALL message( 'check_parameters', 'PA0154', 1, 2, 0, 6, 0 )
3656       ENDIF
[1425]3657       IF ( (bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic')  .AND.                &
[667]3658          TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
[1425]3659          WRITE( message_string, * )  'non-cyclic boundary conditions ',       &
[667]3660               'require  conserve_volume_flow_mode = ''initial_profiles'''
[241]3661          CALL message( 'check_parameters', 'PA0155', 1, 2, 0, 6, 0 )
3662       ENDIF
[1425]3663       IF ( bc_lr == 'cyclic'  .AND.  bc_ns == 'cyclic'  .AND.                 &
[241]3664            TRIM( conserve_volume_flow_mode ) == 'inflow_profile' )  THEN
[1425]3665          WRITE( message_string, * )  'cyclic boundary conditions ',           &
3666               'require conserve_volume_flow_mode = ''initial_profiles''',     &
[241]3667               ' or ''bulk_velocity'''
3668          CALL message( 'check_parameters', 'PA0156', 1, 2, 0, 6, 0 )
3669       ENDIF
3670    ENDIF
[1425]3671    IF ( ( u_bulk /= 0.0_wp .OR. v_bulk /= 0.0_wp ) .AND.                      &
3672         ( .NOT. conserve_volume_flow .OR.                                     &
[241]3673         TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' ) )  THEN
[1425]3674       WRITE( message_string, * )  'nonzero bulk velocity requires ',          &
3675            'conserve_volume_flow = .T. and ',                                 &
[241]3676            'conserve_volume_flow_mode = ''bulk_velocity'''
3677       CALL message( 'check_parameters', 'PA0157', 1, 2, 0, 6, 0 )
3678    ENDIF
[240]3679
3680!
[264]3681!-- Check particle attributes
3682    IF ( particle_color /= 'none' )  THEN
[1425]3683       IF ( particle_color /= 'absuv'  .AND.  particle_color /= 'pt*'  .AND.   &
[264]3684            particle_color /= 'z' )  THEN
[1425]3685          message_string = 'illegal value for parameter particle_color: ' //   &
[264]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!
[1241]3710!-- Check nudging and large scale forcing from external file
3711    IF ( nudging .AND. ( .NOT. large_scale_forcing ) )  THEN
[1425]3712       message_string = 'Nudging requires large_scale_forcing = .T.. &'//      &
3713                        'Surface fluxes and geostrophic wind should be &'//    &
[1241]3714                        'prescribed in file LSF_DATA'
3715       CALL message( 'check_parameters', 'PA0374', 1, 2, 0, 6, 0 )
3716    ENDIF
3717
[1425]3718    IF ( large_scale_forcing .AND. ( bc_lr /= 'cyclic'  .OR.                   &
[1241]3719                                    bc_ns /= 'cyclic' ) )  THEN
[1425]3720       message_string = 'Non-cyclic lateral boundaries do not allow for &' //  &
[1241]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
[1425]3726       message_string = 'The usage of large scale forcing from external &'//   & 
[1241]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
[1425]3732       message_string = 'The usage of large scale forcing from external &'//   & 
[1241]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
[1425]3738       message_string = 'The usage of large scale forcing from external &'//   & 
[1241]3739                        'file LSF_DATA is not implemented for ocean runs'
3740       CALL message( 'check_parameters', 'PA0378', 1, 2, 0, 6, 0 )
3741    ENDIF
[1384]3742
[1402]3743    CALL location_message( 'finished', .TRUE. )
[1384]3744
[1241]3745!
[217]3746!-- Check &userpar parameters
3747    CALL user_check_parameters
[1]3748
[217]3749
[1]3750 END SUBROUTINE check_parameters
Note: See TracBrowser for help on using the repository browser.