source: palm/trunk/SOURCE/header.f90 @ 1792

Last change on this file since 1792 was 1792, checked in by raasch, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 95.9 KB
RevLine 
[1682]1!> @file header.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1691]16! Copyright 1997-2015 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[254]19! Current revisions:
[1]20! -----------------
[1791]21!
[1792]22!
[1485]23! Former revisions:
24! -----------------
25! $Id: header.f90 1792 2016-03-11 10:48:08Z raasch $
26!
[1792]27! 1791 2016-03-11 10:41:25Z raasch
28! output of nesting informations of all domains
29!
[1789]30! 1788 2016-03-10 11:01:04Z maronga
31! Parameter dewfall removed
32!
[1787]33! 1786 2016-03-08 05:49:27Z raasch
34! cpp-direktives for spectra removed
35!
[1784]36! 1783 2016-03-06 18:36:17Z raasch
37! netcdf module and variable names changed, output of netcdf_deflate
38!
[1765]39! 1764 2016-02-28 12:45:19Z raasch
40! output of nesting informations
41!
[1698]42! 1697 2015-10-28 17:14:10Z raasch
43! small E- and F-FORMAT changes to avoid informative compiler messages about
44! insufficient field width
45!
[1692]46! 1691 2015-10-26 16:17:44Z maronga
47! Renamed prandtl_layer to constant_flux_layer, renames rif_min/rif_max to
48! zeta_min/zeta_max.
49!
[1683]50! 1682 2015-10-07 23:56:08Z knoop
51! Code annotations made doxygen readable
52!
[1676]53! 1675 2015-10-02 08:28:59Z gronemeier
54! Bugfix: Definition of topography grid levels
55!
[1662]56! 1660 2015-09-21 08:15:16Z gronemeier
57! Bugfix: Definition of building/street canyon height if vertical grid stretching
58!         starts below the maximum topography height.
59!
[1591]60! 1590 2015-05-08 13:56:27Z maronga
61! Bugfix: Added TRIM statements for character strings for LSM and radiation code
62!
[1586]63! 1585 2015-04-30 07:05:52Z maronga
64! Further output for radiation model(s).
65!
[1576]66! 1575 2015-03-27 09:56:27Z raasch
67! adjustments for psolver-queries, output of seed_follows_topography
68!
[1561]69! 1560 2015-03-06 10:48:54Z keck
70! output for recycling y shift
71!
[1558]72! 1557 2015-03-05 16:43:04Z suehring
73! output for monotonic limiter
74!
[1552]75! 1551 2015-03-03 14:18:16Z maronga
76! Added informal output for land surface model and radiation model. Removed typo.
77!
[1497]78! 1496 2014-12-02 17:25:50Z maronga
79! Renamed: "radiation -> "cloud_top_radiation"
80!
[1485]81! 1484 2014-10-21 10:53:05Z kanani
[1484]82! Changes due to new module structure of the plant canopy model:
83!   module plant_canopy_model_mod and output for new canopy model parameters
84!   (alpha_lad, beta_lad, lai_beta,...) added,
85!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
86!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
87!   learde renamed leaf_area_density.
88! Bugfix: DO-WHILE-loop for lad header information additionally restricted
89! by maximum number of gradient levels (currently 10)
[1483]90!
91! 1482 2014-10-18 12:34:45Z raasch
92! information about calculated or predefined virtual processor topology adjusted
93!
[1469]94! 1468 2014-09-24 14:06:57Z maronga
95! Adapted for use on up to 6-digit processor cores
96!
[1430]97! 1429 2014-07-15 12:53:45Z knoop
98! header exended to provide ensemble_member_nr if specified
99!
[1377]100! 1376 2014-04-26 11:21:22Z boeske
101! Correction of typos
102!
[1366]103! 1365 2014-04-22 15:03:56Z boeske
104! New section 'Large scale forcing and nudging':
105! output of large scale forcing and nudging information,
106! new section for initial profiles created
107!
[1360]108! 1359 2014-04-11 17:15:14Z hoffmann
109! dt_sort_particles removed
110!
[1354]111! 1353 2014-04-08 15:21:23Z heinze
112! REAL constants provided with KIND-attribute
113!
[1329]114! 1327 2014-03-21 11:00:16Z raasch
115! parts concerning iso2d and avs output removed,
116! -netcdf output queries
117!
[1325]118! 1324 2014-03-21 09:13:16Z suehring
119! Bugfix: module spectrum added
120!
[1323]121! 1322 2014-03-20 16:38:49Z raasch
122! REAL functions provided with KIND-attribute,
123! some REAL constants defined as wp-kind
124!
[1321]125! 1320 2014-03-20 08:40:49Z raasch
[1320]126! ONLY-attribute added to USE-statements,
127! kind-parameters added to all INTEGER and REAL declaration statements,
128! kinds are defined in new module kinds,
129! revision history before 2012 removed,
130! comment fields (!:) to be used for variable explanations added to
131! all variable declaration statements
[1321]132!
[1309]133! 1308 2014-03-13 14:58:42Z fricke
134! output of the fixed number of output time levels
135! output_format adjusted for masked data if netcdf_data_format > 5
136!
[1300]137! 1299 2014-03-06 13:15:21Z heinze
138! output for using large_scale subsidence in combination
139! with large_scale_forcing
140! reformatting, more detailed explanations
141!
[1242]142! 1241 2013-10-30 11:36:58Z heinze
143! output for nudging + large scale forcing from external file
144!
[1217]145! 1216 2013-08-26 09:31:42Z raasch
146! output for transpose_compute_overlap
147!
[1213]148! 1212 2013-08-15 08:46:27Z raasch
149! output for poisfft_hybrid removed
150!
[1182]151! 1179 2013-06-14 05:57:58Z raasch
152! output of reference_state, use_reference renamed use_single_reference_value
153!
[1160]154! 1159 2013-05-21 11:58:22Z fricke
155! +use_cmax
156!
[1116]157! 1115 2013-03-26 18:16:16Z hoffmann
158! descriptions for Seifert-Beheng-cloud-physics-scheme added
159!
[1112]160! 1111 2013-03-08 23:54:10Z raasch
161! output of accelerator board information
162! ibc_p_b = 2 removed
163!
[1109]164! 1108 2013-03-05 07:03:32Z raasch
165! bugfix for r1106
166!
[1107]167! 1106 2013-03-04 05:31:38Z raasch
168! some format changes for coupled runs
169!
[1093]170! 1092 2013-02-02 11:24:22Z raasch
171! unused variables removed
172!
[1037]173! 1036 2012-10-22 13:43:42Z raasch
174! code put under GPL (PALM 3.9)
175!
[1035]176! 1031 2012-10-19 14:35:30Z raasch
177! output of netCDF data format modified
178!
[1017]179! 1015 2012-09-27 09:23:24Z raasch
[1365]180! output of Adjustment of mixing length to the Prandtl mixing length at first
[1017]181! grid point above ground removed
182!
[1004]183! 1003 2012-09-14 14:35:53Z raasch
184! output of information about equal/unequal subdomain size removed
185!
[1002]186! 1001 2012-09-13 14:08:46Z raasch
187! all actions concerning leapfrog- and upstream-spline-scheme removed
188!
[979]189! 978 2012-08-09 08:28:32Z fricke
190! -km_damp_max, outflow_damping_width
191! +pt_damping_factor, pt_damping_width
192! +z0h
193!
[965]194! 964 2012-07-26 09:14:24Z raasch
195! output of profil-related quantities removed
196!
[941]197! 940 2012-07-09 14:31:00Z raasch
198! Output in case of simulations for pure neutral stratification (no pt-equation
199! solved)
200!
[928]201! 927 2012-06-06 19:15:04Z raasch
202! output of masking_method for mg-solver
203!
[869]204! 868 2012-03-28 12:21:07Z raasch
205! translation velocity in Galilean transformation changed to 0.6 * ug
206!
[834]207! 833 2012-02-22 08:55:55Z maronga
208! Adjusted format for leaf area density
209!
[829]210! 828 2012-02-21 12:00:36Z raasch
211! output of dissipation_classes + radius_classes
212!
[826]213! 825 2012-02-19 03:03:44Z raasch
214! Output of cloud physics parameters/quantities complemented and restructured
215!
[1]216! Revision 1.1  1997/08/11 06:17:20  raasch
217! Initial revision
218!
219!
220! Description:
221! ------------
[1764]222!> Writing a header with all important information about the current run.
[1682]223!> This subroutine is called three times, two times at the beginning
224!> (writing information on files RUN_CONTROL and HEADER) and one time at the
225!> end of the run, then writing additional information about CPU-usage on file
226!> header.
[411]227!-----------------------------------------------------------------------------!
[1682]228 SUBROUTINE header
229 
[1]230
[1320]231    USE arrays_3d,                                                             &
[1660]232        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu, zw
[1320]233       
[1]234    USE control_parameters
[1320]235       
236    USE cloud_parameters,                                                      &
237        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
238               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
239       
240    USE cpulog,                                                                &
241        ONLY:  log_point_s
242       
243    USE dvrp_variables,                                                        &
244        ONLY:  use_seperate_pe_for_dvrp_output
245       
246    USE grid_variables,                                                        &
247        ONLY:  dx, dy
248       
249    USE indices,                                                               &
250        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
251               nys_mg, nzt, nzt_mg
252       
253    USE kinds
[1551]254   
255    USE land_surface_model_mod,                                                &
[1788]256        ONLY:  conserve_water_content, land_surface, nzb_soil,                 &
[1551]257               nzt_soil, root_fraction, soil_moisture, soil_temperature,       &
258               soil_type, soil_type_name, veg_type, veg_type_name, zs
259 
[1320]260    USE model_1d,                                                              &
261        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
262       
[1783]263    USE netcdf_interface,                                                      &
264        ONLY:  netcdf_data_format, netcdf_data_format_string, netcdf_deflate
265
[1320]266    USE particle_attributes,                                                   &
267        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
268               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
[1359]269               dt_write_particle_data, end_time_prel,                          &
[1320]270               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
271               minimum_tailpoint_distance, number_of_particle_groups,          &
272               particle_advection, particle_advection_start,                   &
273               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
274               pst, radius, radius_classes, random_start_position,             &
[1575]275               seed_follows_topography,                                        &
[1320]276               total_number_of_particles, use_particle_tails,                  &
277               use_sgs_for_particles, total_number_of_tails,                   &
278               vertical_particle_advection, write_particle_statistics
279       
[1]280    USE pegrid
[1484]281
282    USE plant_canopy_model_mod,                                                &
283        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
284               canopy_mode, cthf, lad, lad_surface, lad_vertical_gradient,     &
285               lad_vertical_gradient_level, lad_vertical_gradient_level_ind,   &
286               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
287               plant_canopy
[1551]288
[1791]289    USE pmc_handle_communicator,                                               &
290        ONLY:  pmc_get_model_info
291
[1764]292    USE pmc_interface,                                                         &
[1791]293        ONLY:  nested_run, nesting_mode
[1764]294
[1551]295    USE radiation_model_mod,                                                   &
[1585]296        ONLY:  albedo, albedo_type, albedo_type_name, constant_albedo,         &
297               day_init, dt_radiation, lambda, lw_radiation, net_radiation,    &
298               radiation, radiation_scheme, sw_radiation, time_utc_init
[1324]299   
300    USE spectrum,                                                              &
301        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
302               spectra_direction
[1]303
304    IMPLICIT NONE
305
[1682]306    CHARACTER (LEN=1)  ::  prec                !<
[1320]307   
[1682]308    CHARACTER (LEN=2)  ::  do2d_mode           !<
[1320]309   
[1682]310    CHARACTER (LEN=5)  ::  section_chr         !<
[1320]311   
[1682]312    CHARACTER (LEN=10) ::  coor_chr            !<
313    CHARACTER (LEN=10) ::  host_chr            !<
[1320]314   
[1682]315    CHARACTER (LEN=16) ::  begin_chr           !<
[1320]316   
[1682]317    CHARACTER (LEN=26) ::  ver_rev             !<
[1791]318
319    CHARACTER (LEN=32) ::  cpl_name            !<
[1320]320   
[1682]321    CHARACTER (LEN=40) ::  output_format       !<
[1320]322   
[1682]323    CHARACTER (LEN=70) ::  char1               !<
324    CHARACTER (LEN=70) ::  char2               !<
325    CHARACTER (LEN=70) ::  dopr_chr            !<
326    CHARACTER (LEN=70) ::  do2d_xy             !<
327    CHARACTER (LEN=70) ::  do2d_xz             !<
328    CHARACTER (LEN=70) ::  do2d_yz             !<
329    CHARACTER (LEN=70) ::  do3d_chr            !<
330    CHARACTER (LEN=70) ::  domask_chr          !<
331    CHARACTER (LEN=70) ::  run_classification  !<
[1320]332   
[1682]333    CHARACTER (LEN=85) ::  roben               !<
334    CHARACTER (LEN=85) ::  runten              !<
[1320]335   
[1682]336    CHARACTER (LEN=86) ::  coordinates         !<
337    CHARACTER (LEN=86) ::  gradients           !<
338    CHARACTER (LEN=86) ::  leaf_area_density   !<
339    CHARACTER (LEN=86) ::  roots               !<
340    CHARACTER (LEN=86) ::  slices              !<
341    CHARACTER (LEN=86) ::  temperatures        !<
342    CHARACTER (LEN=86) ::  ugcomponent         !<
343    CHARACTER (LEN=86) ::  vgcomponent         !<
[1]344
[1682]345    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !<
[410]346
[1791]347    INTEGER(iwp) ::  av             !<
348    INTEGER(iwp) ::  bh             !<
349    INTEGER(iwp) ::  blx            !<
350    INTEGER(iwp) ::  bly            !<
351    INTEGER(iwp) ::  bxl            !<
352    INTEGER(iwp) ::  bxr            !<
353    INTEGER(iwp) ::  byn            !<
354    INTEGER(iwp) ::  bys            !<
355    INTEGER(iwp) ::  ch             !<
356    INTEGER(iwp) ::  count          !<
357    INTEGER(iwp) ::  cpl_parent_id  !<
358    INTEGER(iwp) ::  cwx            !<
359    INTEGER(iwp) ::  cwy            !<
360    INTEGER(iwp) ::  cxl            !<
361    INTEGER(iwp) ::  cxr            !<
362    INTEGER(iwp) ::  cyn            !<
363    INTEGER(iwp) ::  cys            !<
364    INTEGER(iwp) ::  dim            !<
365    INTEGER(iwp) ::  i              !<
366    INTEGER(iwp) ::  io             !<
367    INTEGER(iwp) ::  j              !<
368    INTEGER(iwp) ::  k              !<
369    INTEGER(iwp) ::  l              !<
370    INTEGER(iwp) ::  ll             !<
371    INTEGER(iwp) ::  mpi_type       !<
372    INTEGER(iwp) ::  my_cpl_id      !<
373    INTEGER(iwp) ::  n              !<
374    INTEGER(iwp) ::  ncpl           !<
375    INTEGER(iwp) ::  npe_total      !<
[1320]376   
[1682]377    REAL(wp) ::  canopy_height                    !< canopy height (in m)
378    REAL(wp) ::  cpuseconds_per_simulated_second  !<
[1791]379    REAL(wp) ::  lower_left_coord_x               !< x-coordinate of nest domain
380    REAL(wp) ::  lower_left_coord_y               !< y-coordinate of nest domain
[1]381
382!
383!-- Open the output file. At the end of the simulation, output is directed
384!-- to unit 19.
385    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
386         .NOT. simulated_time_at_begin /= simulated_time )  THEN
387       io = 15   !  header output on file RUN_CONTROL
388    ELSE
389       io = 19   !  header output on file HEADER
390    ENDIF
391    CALL check_open( io )
392
393!
394!-- At the end of the run, output file (HEADER) will be rewritten with
[1551]395!-- new information
[1]396    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
397
398!
399!-- Determine kind of model run
400    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
[1764]401       run_classification = 'restart run'
[328]402    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
[1764]403       run_classification = 'run with cyclic fill of 3D - prerun data'
[147]404    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
[1764]405       run_classification = 'run without 1D - prerun'
[197]406    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[1764]407       run_classification = 'run with 1D - prerun'
[197]408    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
[1764]409       run_classification = 'run initialized by user'
[1]410    ELSE
[254]411       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
412       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
[1]413    ENDIF
[1764]414    IF ( nested_run )  run_classification = 'nested ' // run_classification
[97]415    IF ( ocean )  THEN
416       run_classification = 'ocean - ' // run_classification
417    ELSE
418       run_classification = 'atmosphere - ' // run_classification
419    ENDIF
[1]420
421!
422!-- Run-identification, date, time, host
423    host_chr = host(1:10)
[75]424    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
[102]425    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
[291]426    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
427#if defined( __mpi2 )
428       mpi_type = 2
429#else
430       mpi_type = 1
431#endif
432       WRITE ( io, 101 )  mpi_type, coupling_mode
433    ENDIF
[1108]434#if defined( __parallel )
[1353]435    IF ( coupling_start_time /= 0.0_wp )  THEN
[1106]436       IF ( coupling_start_time > simulated_time_at_begin )  THEN
437          WRITE ( io, 109 )
438       ELSE
439          WRITE ( io, 114 )
440       ENDIF
441    ENDIF
[1108]442#endif
[1429]443    IF ( ensemble_member_nr /= 0 )  THEN
444       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
445                       ADJUSTR( host_chr ), ensemble_member_nr
446    ELSE
447       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
[102]448                       ADJUSTR( host_chr )
[1429]449    ENDIF
[1]450#if defined( __parallel )
[1482]451    IF ( npex == -1  .AND.  npey == -1 )  THEN
[1]452       char1 = 'calculated'
453    ELSE
454       char1 = 'predefined'
455    ENDIF
456    IF ( threads_per_task == 1 )  THEN
[102]457       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
[1]458    ELSE
[102]459       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
[1]460                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
461    ENDIF
[1111]462    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
[1]463    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
464           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
465         npex == -1  .AND.  pdims(2) == 1 )                      &
466    THEN
[102]467       WRITE ( io, 106 )
[1]468    ELSEIF ( pdims(2) == 1 )  THEN
[102]469       WRITE ( io, 107 )  'x'
[1]470    ELSEIF ( pdims(1) == 1 )  THEN
[102]471       WRITE ( io, 107 )  'y'
[1]472    ENDIF
[102]473    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
[759]474    IF ( numprocs /= maximum_parallel_io_streams )  THEN
475       WRITE ( io, 108 )  maximum_parallel_io_streams
476    ENDIF
[1111]477#else
478    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
[1]479#endif
[1764]480
481!
482!-- Nesting informations
483    IF ( nested_run )  THEN
[1791]484
485       WRITE ( io, 600 )  TRIM( nesting_mode )
486       CALL pmc_get_model_info( ncpl = ncpl, cpl_id = my_cpl_id )
487
488       DO  n = 1, ncpl
489          CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,&
490                                   cpl_parent_id = cpl_parent_id,              &
491                                   lower_left_x = lower_left_coord_x,          &
492                                   lower_left_y = lower_left_coord_y,          &
493                                   npe_total = npe_total )
494          IF ( n == my_cpl_id )  THEN
495             char1 = '*'
496          ELSE
497             char1 = ' '
498          ENDIF
499          WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total,       &
500                             lower_left_coord_x, lower_left_coord_y,           &
501                             TRIM( cpl_name )
502       ENDDO
[1764]503    ENDIF
[1]504    WRITE ( io, 99 )
505
506!
507!-- Numerical schemes
508    WRITE ( io, 110 )
509    IF ( psolver(1:7) == 'poisfft' )  THEN
510       WRITE ( io, 111 )  TRIM( fft_method )
[1216]511       IF ( transpose_compute_overlap )  WRITE( io, 115 )
[1]512    ELSEIF ( psolver == 'sor' )  THEN
513       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
[1575]514    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
515       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
[1]516       IF ( mg_cycles == -1 )  THEN
517          WRITE ( io, 140 )  residual_limit
518       ELSE
519          WRITE ( io, 141 )  mg_cycles
520       ENDIF
521       IF ( mg_switch_to_pe0_level == 0 )  THEN
522          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
523                             nzt_mg(1)
[197]524       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
[1]525          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
526                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
527                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
528                             nzt_mg(mg_switch_to_pe0_level),    &
529                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
530                             nzt_mg(1)
531       ENDIF
[927]532       IF ( masking_method )  WRITE ( io, 144 )
[1]533    ENDIF
534    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
535    THEN
536       WRITE ( io, 142 )
537    ENDIF
538
539    IF ( momentum_advec == 'pw-scheme' )  THEN
540       WRITE ( io, 113 )
[1299]541    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
[667]542       WRITE ( io, 503 )
[1]543    ENDIF
544    IF ( scalar_advec == 'pw-scheme' )  THEN
545       WRITE ( io, 116 )
[667]546    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
547       WRITE ( io, 504 )
[1557]548    ELSEIF ( scalar_advec == 'ws-scheme-mono' )  THEN
549       WRITE ( io, 513 )
[1]550    ELSE
551       WRITE ( io, 118 )
552    ENDIF
[63]553
554    WRITE ( io, 139 )  TRIM( loop_optimization )
555
[1]556    IF ( galilei_transformation )  THEN
557       IF ( use_ug_for_galilei_tr )  THEN
[868]558          char1 = '0.6 * geostrophic wind'
[1]559       ELSE
560          char1 = 'mean wind in model domain'
561       ENDIF
562       IF ( simulated_time_at_begin == simulated_time )  THEN
563          char2 = 'at the start of the run'
564       ELSE
565          char2 = 'at the end of the run'
566       ENDIF
[1353]567       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
568                          advected_distance_x/1000.0_wp,                       &
569                          advected_distance_y/1000.0_wp
[1]570    ENDIF
[1001]571    WRITE ( io, 122 )  timestep_scheme
[87]572    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
[1353]573    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
[108]574       IF ( .NOT. ocean )  THEN
575          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
576               rayleigh_damping_factor
577       ELSE
578          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
579               rayleigh_damping_factor
580       ENDIF
[1]581    ENDIF
[940]582    IF ( neutral )  WRITE ( io, 131 )  pt_surface
[75]583    IF ( humidity )  THEN
[1]584       IF ( .NOT. cloud_physics )  THEN
585          WRITE ( io, 129 )
586       ELSE
587          WRITE ( io, 130 )
588       ENDIF
589    ENDIF
590    IF ( passive_scalar )  WRITE ( io, 134 )
[240]591    IF ( conserve_volume_flow )  THEN
[241]592       WRITE ( io, 150 )  conserve_volume_flow_mode
593       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
594          WRITE ( io, 151 )  u_bulk, v_bulk
595       ENDIF
[240]596    ELSEIF ( dp_external )  THEN
597       IF ( dp_smooth )  THEN
[241]598          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
[240]599       ELSE
[241]600          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
[240]601       ENDIF
602    ENDIF
[1]603    WRITE ( io, 99 )
604
605!
[1551]606!-- Runtime and timestep information
[1]607    WRITE ( io, 200 )
608    IF ( .NOT. dt_fixed )  THEN
609       WRITE ( io, 201 )  dt_max, cfl_factor
610    ELSE
611       WRITE ( io, 202 )  dt
612    ENDIF
613    WRITE ( io, 203 )  simulated_time_at_begin, end_time
614
[1322]615    IF ( time_restart /= 9999999.9_wp  .AND. &
[1]616         simulated_time_at_begin == simulated_time )  THEN
[1322]617       IF ( dt_restart == 9999999.9_wp )  THEN
[1]618          WRITE ( io, 204 )  ' Restart at:       ',time_restart
619       ELSE
620          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
621       ENDIF
622    ENDIF
623
624    IF ( simulated_time_at_begin /= simulated_time )  THEN
625       i = MAX ( log_point_s(10)%counts, 1 )
[1353]626       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
627          cpuseconds_per_simulated_second = 0.0_wp
[1]628       ELSE
629          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
630                                            ( simulated_time -    &
631                                              simulated_time_at_begin )
632       ENDIF
[1322]633       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
634                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
[1]635                          cpuseconds_per_simulated_second
[1322]636       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
637          IF ( dt_restart == 9999999.9_wp )  THEN
[1106]638             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
[1]639          ELSE
[1106]640             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
[1]641          ENDIF
642       ENDIF
643    ENDIF
644
[1324]645
[1]646!
[291]647!-- Start time for coupled runs, if independent precursor runs for atmosphere
[1106]648!-- and ocean are used or have been used. In this case, coupling_start_time
649!-- defines the time when the coupling is switched on.
[1353]650    IF ( coupling_start_time /= 0.0_wp )  THEN
[1106]651       WRITE ( io, 207 )  coupling_start_time
[291]652    ENDIF
653
654!
[1]655!-- Computational grid
[94]656    IF ( .NOT. ocean )  THEN
657       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
658       IF ( dz_stretch_level_index < nzt+1 )  THEN
659          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
660                             dz_stretch_factor, dz_max
661       ENDIF
662    ELSE
663       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
664       IF ( dz_stretch_level_index > 0 )  THEN
665          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
666                             dz_stretch_factor, dz_max
667       ENDIF
[1]668    ENDIF
669    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
670                       MIN( nnz+2, nzt+2 )
671    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
672
673!
[1365]674!-- Large scale forcing and nudging
675    WRITE ( io, 160 )
676    IF ( large_scale_forcing )  THEN
677       WRITE ( io, 162 )
678       WRITE ( io, 163 )
679
680       IF ( large_scale_subsidence )  THEN
681          IF ( .NOT. use_subsidence_tendencies )  THEN
682             WRITE ( io, 164 )
683          ELSE
684             WRITE ( io, 165 )
685          ENDIF
686       ENDIF
687
688       IF ( bc_pt_b == 'dirichlet' )  THEN
689          WRITE ( io, 180 )
690       ELSEIF ( bc_pt_b == 'neumann' )  THEN
691          WRITE ( io, 181 )
692       ENDIF
693
694       IF ( bc_q_b == 'dirichlet' )  THEN
695          WRITE ( io, 182 )
696       ELSEIF ( bc_q_b == 'neumann' )  THEN
697          WRITE ( io, 183 )
698       ENDIF
699
700       WRITE ( io, 167 )
701       IF ( nudging )  THEN
702          WRITE ( io, 170 )
703       ENDIF
704    ELSE
705       WRITE ( io, 161 )
706       WRITE ( io, 171 )
707    ENDIF
708    IF ( large_scale_subsidence )  THEN
709       WRITE ( io, 168 )
710       WRITE ( io, 169 )
711    ENDIF
712
713!
714!-- Profile for the large scale vertial velocity
715!-- Building output strings, starting with surface value
716    IF ( large_scale_subsidence )  THEN
717       temperatures = '   0.0'
718       gradients = '------'
719       slices = '     0'
720       coordinates = '   0.0'
721       i = 1
722       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
723
724          WRITE (coor_chr,'(E10.2,7X)')  &
725                                w_subs(subs_vertical_gradient_level_i(i))
726          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
727
728          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
729          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
730
731          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
732          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
733
734          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
735          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
736
737          IF ( i == 10 )  THEN
738             EXIT
739          ELSE
740             i = i + 1
741          ENDIF
742
743       ENDDO
744
745 
746       IF ( .NOT. large_scale_forcing )  THEN
747          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
748                             TRIM( gradients ), TRIM( slices )
749       ENDIF
750
751
752    ENDIF
753
754!-- Profile of the geostrophic wind (component ug)
755!-- Building output strings
756    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
757    gradients = '------'
758    slices = '     0'
759    coordinates = '   0.0'
760    i = 1
761    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
762     
763       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
764       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
765
766       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
767       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
768
769       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
770       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
771
772       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
773       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
774
775       IF ( i == 10 )  THEN
776          EXIT
777       ELSE
778          i = i + 1
779       ENDIF
780
781    ENDDO
782
783    IF ( .NOT. large_scale_forcing )  THEN
784       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
785                          TRIM( gradients ), TRIM( slices )
786    ENDIF
787
788!-- Profile of the geostrophic wind (component vg)
789!-- Building output strings
790    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
791    gradients = '------'
792    slices = '     0'
793    coordinates = '   0.0'
794    i = 1
795    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
796
797       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
798       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
799
800       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
801       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
802
803       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
804       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
805
806       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
807       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
808
809       IF ( i == 10 )  THEN
810          EXIT
811       ELSE
812          i = i + 1
813       ENDIF
814 
815    ENDDO
816
817    IF ( .NOT. large_scale_forcing )  THEN
818       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
819                          TRIM( gradients ), TRIM( slices )
820    ENDIF
821
822!
[1]823!-- Topography
824    WRITE ( io, 270 )  topography
825    SELECT CASE ( TRIM( topography ) )
826
827       CASE ( 'flat' )
828          ! no actions necessary
829
830       CASE ( 'single_building' )
831          blx = INT( building_length_x / dx )
832          bly = INT( building_length_y / dy )
[1675]833          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
834          IF ( ABS( zw(bh  ) - building_height ) == &
835               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
[1]836
[1322]837          IF ( building_wall_left == 9999999.9_wp )  THEN
[1]838             building_wall_left = ( nx + 1 - blx ) / 2 * dx
839          ENDIF
[1353]840          bxl = INT ( building_wall_left / dx + 0.5_wp )
[1]841          bxr = bxl + blx
842
[1322]843          IF ( building_wall_south == 9999999.9_wp )  THEN
[1]844             building_wall_south = ( ny + 1 - bly ) / 2 * dy
845          ENDIF
[1353]846          bys = INT ( building_wall_south / dy + 0.5_wp )
[1]847          byn = bys + bly
848
849          WRITE ( io, 271 )  building_length_x, building_length_y, &
850                             building_height, bxl, bxr, bys, byn
851
[240]852       CASE ( 'single_street_canyon' )
[1675]853          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
854          IF ( ABS( zw(ch  ) - canyon_height ) == &
855               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
[1322]856          IF ( canyon_width_x /= 9999999.9_wp )  THEN
[240]857!
858!--          Street canyon in y direction
859             cwx = NINT( canyon_width_x / dx )
[1322]860             IF ( canyon_wall_left == 9999999.9_wp )  THEN
[240]861                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
862             ENDIF
863             cxl = NINT( canyon_wall_left / dx )
864             cxr = cxl + cwx
865             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
866
[1322]867          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
[240]868!
869!--          Street canyon in x direction
870             cwy = NINT( canyon_width_y / dy )
[1322]871             IF ( canyon_wall_south == 9999999.9_wp )  THEN
[240]872                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
873             ENDIF
874             cys = NINT( canyon_wall_south / dy )
875             cyn = cys + cwy
876             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
877          ENDIF
878
[1]879    END SELECT
880
[256]881    IF ( TRIM( topography ) /= 'flat' )  THEN
882       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
883          IF ( TRIM( topography ) == 'single_building' .OR.  &
884               TRIM( topography ) == 'single_street_canyon' )  THEN
885             WRITE ( io, 278 )
886          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
887             WRITE ( io, 279 )
888          ENDIF
889       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
890          WRITE ( io, 278 )
891       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
892          WRITE ( io, 279 )
893       ENDIF
894    ENDIF
895
[1299]896    IF ( plant_canopy )  THEN
[1484]897   
898       canopy_height = pch_index * dz
[138]899
[1484]900       WRITE ( io, 280 )  canopy_mode, canopy_height, pch_index,               &
901                          canopy_drag_coeff
[1299]902       IF ( passive_scalar )  THEN
[1484]903          WRITE ( io, 281 )  leaf_scalar_exch_coeff,                           &
904                             leaf_surface_conc
[153]905       ENDIF
[138]906
[1]907!
[153]908!--    Heat flux at the top of vegetation
[1484]909       WRITE ( io, 282 )  cthf
[153]910
911!
[1484]912!--    Leaf area density profile, calculated either from given vertical
913!--    gradients or from beta probability density function.
914       IF (  .NOT.  calc_beta_lad_profile )  THEN
[138]915
[1484]916!--       Building output strings, starting with surface value
[1697]917          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
[1484]918          gradients = '------'
919          slices = '     0'
920          coordinates = '   0.0'
921          i = 1
922          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i) /= -9999 )
[138]923
[1484]924             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
925             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
926 
927             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
928             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
[138]929
[1484]930             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
931             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
[138]932
[1484]933             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
934             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
[138]935
[1484]936             i = i + 1
937          ENDDO
[138]938
[1484]939          WRITE ( io, 283 )  TRIM( coordinates ), TRIM( leaf_area_density ),              &
940                             TRIM( gradients ), TRIM( slices )
[138]941
[1484]942       ELSE
943       
[1697]944          WRITE ( leaf_area_density, '(F7.4)' )  lad_surface
[1484]945          coordinates = '   0.0'
946         
947          DO  k = 1, pch_index
948
949             WRITE (coor_chr,'(F7.2)')  lad(k)
950             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
951 
952             WRITE (coor_chr,'(F7.1)')  zu(k)
953             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
954
955          ENDDO       
956
957          WRITE ( io, 284 ) TRIM( coordinates ), TRIM( leaf_area_density ), alpha_lad,    &
958                            beta_lad, lai_beta
959
960       ENDIF 
961
[138]962    ENDIF
963
[1484]964
[1551]965    IF ( land_surface )  THEN
966
967       temperatures = ''
968       gradients    = '' ! use for humidity here
969       coordinates  = '' ! use for height
970       roots        = '' ! use for root fraction
971       slices       = '' ! use for index
972
973       i = 1
974       DO i = nzb_soil, nzt_soil
975          WRITE (coor_chr,'(F10.2,7X)') soil_temperature(i)
976          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
977
978          WRITE (coor_chr,'(F10.2,7X)') soil_moisture(i)
979          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
980
981          WRITE (coor_chr,'(F10.2,7X)')  - zs(i)
982          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
983
984          WRITE (coor_chr,'(F10.2,7X)')  root_fraction(i)
985          roots = TRIM( roots ) // ' '  // TRIM( coor_chr )
986
987          WRITE (coor_chr,'(I10,7X)')  i
988          slices = TRIM( slices ) // ' '  // TRIM( coor_chr )
989
990
991       ENDDO
992
[138]993!
[1551]994!--    Write land surface model header
995       WRITE( io, 419 )
996       IF ( conserve_water_content )  THEN
997          WRITE( io, 440 )
998       ELSE
999          WRITE( io, 441 )
1000       ENDIF
1001
[1590]1002       WRITE( io, 438 ) TRIM( veg_type_name(veg_type) ),                       &
1003                        TRIM (soil_type_name(soil_type) )
[1551]1004       WRITE( io, 439 ) TRIM( coordinates ), TRIM( temperatures ),             &
1005                        TRIM( gradients ), TRIM( roots ), TRIM( slices )
1006
1007
1008    ENDIF
1009
1010    IF ( radiation )  THEN
1011!
[1585]1012!--    Write radiation model header
[1551]1013       WRITE( io, 444 )
1014
1015       IF ( radiation_scheme == "constant" )  THEN
1016          WRITE( io, 445 ) net_radiation
1017       ELSEIF ( radiation_scheme == "clear-sky" )  THEN
1018          WRITE( io, 446 )
[1585]1019       ELSEIF ( radiation_scheme == "rrtmg" )  THEN
1020          WRITE( io, 447 )
1021          IF ( .NOT. lw_radiation )  WRITE( io, 458 )
1022          IF ( .NOT. sw_radiation )  WRITE( io, 459 )
1023       ENDIF
1024
1025       IF ( albedo_type == 0 )  THEN
1026          WRITE( io, 448 ) albedo
[1551]1027       ELSE
[1590]1028          WRITE( io, 456 ) TRIM( albedo_type_name(albedo_type) )
[1551]1029       ENDIF
[1585]1030       IF ( constant_albedo )  THEN
1031          WRITE( io, 457 )
1032       ENDIF
[1551]1033       WRITE( io, 449 ) dt_radiation
1034    ENDIF
1035
1036
1037!
[1]1038!-- Boundary conditions
1039    IF ( ibc_p_b == 0 )  THEN
1040       runten = 'p(0)     = 0      |'
1041    ELSEIF ( ibc_p_b == 1 )  THEN
1042       runten = 'p(0)     = p(1)   |'
1043    ENDIF
1044    IF ( ibc_p_t == 0 )  THEN
1045       roben  = 'p(nzt+1) = 0      |'
1046    ELSE
1047       roben  = 'p(nzt+1) = p(nzt) |'
1048    ENDIF
1049
1050    IF ( ibc_uv_b == 0 )  THEN
1051       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
1052    ELSE
1053       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
1054    ENDIF
[132]1055    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
1056       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
1057    ELSEIF ( ibc_uv_t == 0 )  THEN
[1]1058       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
1059    ELSE
1060       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
1061    ENDIF
1062
1063    IF ( ibc_pt_b == 0 )  THEN
[1551]1064       IF ( land_surface )  THEN
1065          runten = TRIM( runten ) // ' pt(0)     = from soil model'
1066       ELSE
1067          runten = TRIM( runten ) // ' pt(0)     = pt_surface'
1068       ENDIF
[102]1069    ELSEIF ( ibc_pt_b == 1 )  THEN
[1551]1070       runten = TRIM( runten ) // ' pt(0)     = pt(1)'
[102]1071    ELSEIF ( ibc_pt_b == 2 )  THEN
[1551]1072       runten = TRIM( runten ) // ' pt(0)     = from coupled model'
[1]1073    ENDIF
1074    IF ( ibc_pt_t == 0 )  THEN
[19]1075       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
1076    ELSEIF( ibc_pt_t == 1 )  THEN
1077       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
1078    ELSEIF( ibc_pt_t == 2 )  THEN
1079       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
[667]1080
[1]1081    ENDIF
1082
1083    WRITE ( io, 300 )  runten, roben
1084
1085    IF ( .NOT. constant_diffusion )  THEN
1086       IF ( ibc_e_b == 1 )  THEN
1087          runten = 'e(0)     = e(1)'
1088       ELSE
1089          runten = 'e(0)     = e(1) = (u*/0.1)**2'
1090       ENDIF
1091       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
1092
[97]1093       WRITE ( io, 301 )  'e', runten, roben       
[1]1094
1095    ENDIF
1096
[97]1097    IF ( ocean )  THEN
1098       runten = 'sa(0)    = sa(1)'
1099       IF ( ibc_sa_t == 0 )  THEN
1100          roben =  'sa(nzt+1) = sa_surface'
[1]1101       ELSE
[97]1102          roben =  'sa(nzt+1) = sa(nzt)'
[1]1103       ENDIF
[97]1104       WRITE ( io, 301 ) 'sa', runten, roben
1105    ENDIF
[1]1106
[97]1107    IF ( humidity )  THEN
1108       IF ( ibc_q_b == 0 )  THEN
[1551]1109          IF ( land_surface )  THEN
1110             runten = 'q(0)     = from soil model'
1111          ELSE
1112             runten = 'q(0)     = q_surface'
1113          ENDIF
1114
[97]1115       ELSE
1116          runten = 'q(0)     = q(1)'
1117       ENDIF
1118       IF ( ibc_q_t == 0 )  THEN
1119          roben =  'q(nzt)   = q_top'
1120       ELSE
1121          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
1122       ENDIF
1123       WRITE ( io, 301 ) 'q', runten, roben
1124    ENDIF
[1]1125
[97]1126    IF ( passive_scalar )  THEN
1127       IF ( ibc_q_b == 0 )  THEN
1128          runten = 's(0)     = s_surface'
1129       ELSE
1130          runten = 's(0)     = s(1)'
1131       ENDIF
1132       IF ( ibc_q_t == 0 )  THEN
1133          roben =  's(nzt)   = s_top'
1134       ELSE
1135          roben =  's(nzt)   = s(nzt-1) + ds/dz'
1136       ENDIF
1137       WRITE ( io, 301 ) 's', runten, roben
[1]1138    ENDIF
1139
1140    IF ( use_surface_fluxes )  THEN
1141       WRITE ( io, 303 )
1142       IF ( constant_heatflux )  THEN
[1299]1143          IF ( large_scale_forcing .AND. lsf_surf )  THEN
[1241]1144             WRITE ( io, 306 )  shf(0,0)
1145          ELSE
1146             WRITE ( io, 306 )  surface_heatflux
1147          ENDIF
[1]1148          IF ( random_heatflux )  WRITE ( io, 307 )
1149       ENDIF
[75]1150       IF ( humidity  .AND.  constant_waterflux )  THEN
[1299]1151          IF ( large_scale_forcing .AND. lsf_surf )  THEN
[1241]1152             WRITE ( io, 311 ) qsws(0,0)
1153          ELSE
1154             WRITE ( io, 311 ) surface_waterflux
1155          ENDIF
[1]1156       ENDIF
1157       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1158          WRITE ( io, 313 ) surface_waterflux
1159       ENDIF
1160    ENDIF
1161
[19]1162    IF ( use_top_fluxes )  THEN
1163       WRITE ( io, 304 )
[102]1164       IF ( coupling_mode == 'uncoupled' )  THEN
[151]1165          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
[102]1166          IF ( constant_top_heatflux )  THEN
1167             WRITE ( io, 306 )  top_heatflux
1168          ENDIF
1169       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1170          WRITE ( io, 316 )
[19]1171       ENDIF
[97]1172       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1173          WRITE ( io, 309 )  top_salinityflux
1174       ENDIF
[75]1175       IF ( humidity  .OR.  passive_scalar )  THEN
[19]1176          WRITE ( io, 315 )
1177       ENDIF
1178    ENDIF
1179
[1691]1180    IF ( constant_flux_layer )  THEN
1181       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
1182                          z0h_factor*roughness_length, kappa,                  &
1183                          zeta_min, zeta_max
[1]1184       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
[75]1185       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
[1]1186          WRITE ( io, 312 )
1187       ENDIF
1188       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1189          WRITE ( io, 314 )
1190       ENDIF
1191    ELSE
1192       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
[1691]1193          WRITE ( io, 310 )  zeta_min, zeta_max
[1]1194       ENDIF
1195    ENDIF
1196
1197    WRITE ( io, 317 )  bc_lr, bc_ns
[707]1198    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1159]1199       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
[151]1200       IF ( turbulent_inflow )  THEN
[1560]1201          IF ( .NOT. recycling_yshift ) THEN
1202             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1203                                inflow_damping_height, inflow_damping_width
1204          ELSE
1205             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1206                                inflow_damping_height, inflow_damping_width
1207          END IF
[151]1208       ENDIF
[1]1209    ENDIF
1210
1211!
[1365]1212!-- Initial Profiles
1213    WRITE ( io, 321 )
1214!
1215!-- Initial wind profiles
1216    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1217
1218!
1219!-- Initial temperature profile
1220!-- Building output strings, starting with surface temperature
1221    WRITE ( temperatures, '(F6.2)' )  pt_surface
1222    gradients = '------'
1223    slices = '     0'
1224    coordinates = '   0.0'
1225    i = 1
1226    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1227
1228       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1229       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1230
1231       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1232       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1233
1234       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1235       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1236
1237       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1238       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1239
1240       IF ( i == 10 )  THEN
1241          EXIT
1242       ELSE
1243          i = i + 1
1244       ENDIF
1245
1246    ENDDO
1247
1248    IF ( .NOT. nudging )  THEN
1249       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1250                          TRIM( gradients ), TRIM( slices )
1251    ELSE
1252       WRITE ( io, 428 ) 
1253    ENDIF
1254
1255!
1256!-- Initial humidity profile
1257!-- Building output strings, starting with surface humidity
1258    IF ( humidity  .OR.  passive_scalar )  THEN
1259       WRITE ( temperatures, '(E8.1)' )  q_surface
1260       gradients = '--------'
1261       slices = '       0'
1262       coordinates = '     0.0'
1263       i = 1
1264       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1265         
1266          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1267          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1268
1269          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1270          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1271         
1272          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1273          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1274         
1275          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1276          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1277
1278          IF ( i == 10 )  THEN
1279             EXIT
1280          ELSE
1281             i = i + 1
1282          ENDIF
1283
1284       ENDDO
1285
1286       IF ( humidity )  THEN
1287          IF ( .NOT. nudging )  THEN
1288             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1289                                TRIM( gradients ), TRIM( slices )
1290          ENDIF
1291       ELSE
1292          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1293                             TRIM( gradients ), TRIM( slices )
1294       ENDIF
1295    ENDIF
1296
1297!
1298!-- Initial salinity profile
1299!-- Building output strings, starting with surface salinity
1300    IF ( ocean )  THEN
1301       WRITE ( temperatures, '(F6.2)' )  sa_surface
1302       gradients = '------'
1303       slices = '     0'
1304       coordinates = '   0.0'
1305       i = 1
1306       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1307
1308          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1309          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1310
1311          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1312          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1313
1314          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1315          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1316
1317          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1318          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1319
1320          IF ( i == 10 )  THEN
1321             EXIT
1322          ELSE
1323             i = i + 1
1324          ENDIF
1325
1326       ENDDO
1327
1328       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1329                          TRIM( gradients ), TRIM( slices )
1330    ENDIF
1331
1332
1333!
[1]1334!-- Listing of 1D-profiles
[151]1335    WRITE ( io, 325 )  dt_dopr_listing
[1353]1336    IF ( averaging_interval_pr /= 0.0_wp )  THEN
[151]1337       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]1338    ENDIF
1339
1340!
1341!-- DATA output
1342    WRITE ( io, 330 )
[1353]1343    IF ( averaging_interval_pr /= 0.0_wp )  THEN
[151]1344       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]1345    ENDIF
1346
1347!
1348!-- 1D-profiles
[346]1349    dopr_chr = 'Profile:'
[1]1350    IF ( dopr_n /= 0 )  THEN
1351       WRITE ( io, 331 )
1352
1353       output_format = ''
[1783]1354       output_format = netcdf_data_format_string
1355       IF ( netcdf_deflate == 0 )  THEN
1356          WRITE ( io, 344 )  output_format
1357       ELSE
1358          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1359       ENDIF
[1]1360
1361       DO  i = 1, dopr_n
1362          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1363          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1364             WRITE ( io, 332 )  dopr_chr
1365             dopr_chr = '       :'
1366          ENDIF
1367       ENDDO
1368
1369       IF ( dopr_chr /= '' )  THEN
1370          WRITE ( io, 332 )  dopr_chr
1371       ENDIF
1372       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
[1353]1373       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
[1]1374    ENDIF
1375
1376!
1377!-- 2D-arrays
1378    DO  av = 0, 1
1379
1380       i = 1
1381       do2d_xy = ''
1382       do2d_xz = ''
1383       do2d_yz = ''
1384       DO  WHILE ( do2d(av,i) /= ' ' )
1385
1386          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1387          do2d_mode = do2d(av,i)(l-1:l)
1388
1389          SELECT CASE ( do2d_mode )
1390             CASE ( 'xy' )
1391                ll = LEN_TRIM( do2d_xy )
1392                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1393             CASE ( 'xz' )
1394                ll = LEN_TRIM( do2d_xz )
1395                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1396             CASE ( 'yz' )
1397                ll = LEN_TRIM( do2d_yz )
1398                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1399          END SELECT
1400
1401          i = i + 1
1402
1403       ENDDO
1404
1405       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1406              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
[1327]1407              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
[1]1408
1409          IF (  av == 0 )  THEN
1410             WRITE ( io, 334 )  ''
1411          ELSE
1412             WRITE ( io, 334 )  '(time-averaged)'
1413          ENDIF
1414
1415          IF ( do2d_at_begin )  THEN
1416             begin_chr = 'and at the start'
1417          ELSE
1418             begin_chr = ''
1419          ENDIF
1420
1421          output_format = ''
[1783]1422          output_format = netcdf_data_format_string
1423          IF ( netcdf_deflate == 0 )  THEN
1424             WRITE ( io, 344 )  output_format
1425          ELSE
1426             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1427          ENDIF
[1]1428
1429          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1430             i = 1
1431             slices = '/'
1432             coordinates = '/'
1433!
[1551]1434!--          Building strings with index and coordinate information of the
[1]1435!--          slices
1436             DO  WHILE ( section(i,1) /= -9999 )
1437
1438                WRITE (section_chr,'(I5)')  section(i,1)
1439                section_chr = ADJUSTL( section_chr )
1440                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1441
[206]1442                IF ( section(i,1) == -1 )  THEN
[1353]1443                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
[206]1444                ELSE
1445                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1446                ENDIF
[1]1447                coor_chr = ADJUSTL( coor_chr )
1448                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1449
1450                i = i + 1
1451             ENDDO
1452             IF ( av == 0 )  THEN
1453                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1454                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1455                                   TRIM( coordinates )
[1353]1456                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
[1]1457                   WRITE ( io, 339 )  skip_time_do2d_xy
1458                ENDIF
1459             ELSE
1460                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1461                                   TRIM( begin_chr ), averaging_interval, &
1462                                   dt_averaging_input, 'k', TRIM( slices ), &
1463                                   TRIM( coordinates )
[1353]1464                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1465                   WRITE ( io, 339 )  skip_time_data_output_av
1466                ENDIF
1467             ENDIF
[1308]1468             IF ( netcdf_data_format > 4 )  THEN
1469                WRITE ( io, 352 )  ntdim_2d_xy(av)
1470             ELSE
1471                WRITE ( io, 353 )
1472             ENDIF
[1]1473          ENDIF
1474
1475          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1476             i = 1
1477             slices = '/'
1478             coordinates = '/'
1479!
[1551]1480!--          Building strings with index and coordinate information of the
[1]1481!--          slices
1482             DO  WHILE ( section(i,2) /= -9999 )
1483
1484                WRITE (section_chr,'(I5)')  section(i,2)
1485                section_chr = ADJUSTL( section_chr )
1486                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1487
1488                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1489                coor_chr = ADJUSTL( coor_chr )
1490                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1491
1492                i = i + 1
1493             ENDDO
1494             IF ( av == 0 )  THEN
1495                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1496                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1497                                   TRIM( coordinates )
[1353]1498                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
[1]1499                   WRITE ( io, 339 )  skip_time_do2d_xz
1500                ENDIF
1501             ELSE
1502                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1503                                   TRIM( begin_chr ), averaging_interval, &
1504                                   dt_averaging_input, 'j', TRIM( slices ), &
1505                                   TRIM( coordinates )
[1353]1506                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1507                   WRITE ( io, 339 )  skip_time_data_output_av
1508                ENDIF
1509             ENDIF
[1308]1510             IF ( netcdf_data_format > 4 )  THEN
1511                WRITE ( io, 352 )  ntdim_2d_xz(av)
1512             ELSE
1513                WRITE ( io, 353 )
1514             ENDIF
[1]1515          ENDIF
1516
1517          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1518             i = 1
1519             slices = '/'
1520             coordinates = '/'
1521!
[1551]1522!--          Building strings with index and coordinate information of the
[1]1523!--          slices
1524             DO  WHILE ( section(i,3) /= -9999 )
1525
1526                WRITE (section_chr,'(I5)')  section(i,3)
1527                section_chr = ADJUSTL( section_chr )
1528                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1529
1530                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1531                coor_chr = ADJUSTL( coor_chr )
1532                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1533
1534                i = i + 1
1535             ENDDO
1536             IF ( av == 0 )  THEN
1537                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1538                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1539                                   TRIM( coordinates )
[1353]1540                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
[1]1541                   WRITE ( io, 339 )  skip_time_do2d_yz
1542                ENDIF
1543             ELSE
1544                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1545                                   TRIM( begin_chr ), averaging_interval, &
1546                                   dt_averaging_input, 'i', TRIM( slices ), &
1547                                   TRIM( coordinates )
[1353]1548                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1549                   WRITE ( io, 339 )  skip_time_data_output_av
1550                ENDIF
1551             ENDIF
[1308]1552             IF ( netcdf_data_format > 4 )  THEN
1553                WRITE ( io, 352 )  ntdim_2d_yz(av)
1554             ELSE
1555                WRITE ( io, 353 )
1556             ENDIF
[1]1557          ENDIF
1558
1559       ENDIF
1560
1561    ENDDO
1562
1563!
1564!-- 3d-arrays
1565    DO  av = 0, 1
1566
1567       i = 1
1568       do3d_chr = ''
1569       DO  WHILE ( do3d(av,i) /= ' ' )
1570
1571          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1572          i = i + 1
1573
1574       ENDDO
1575
1576       IF ( do3d_chr /= '' )  THEN
1577          IF ( av == 0 )  THEN
1578             WRITE ( io, 336 )  ''
1579          ELSE
1580             WRITE ( io, 336 )  '(time-averaged)'
1581          ENDIF
1582
[1783]1583          output_format = netcdf_data_format_string
1584          IF ( netcdf_deflate == 0 )  THEN
1585             WRITE ( io, 344 )  output_format
1586          ELSE
1587             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1588          ENDIF
[1]1589
1590          IF ( do3d_at_begin )  THEN
1591             begin_chr = 'and at the start'
1592          ELSE
1593             begin_chr = ''
1594          ENDIF
1595          IF ( av == 0 )  THEN
1596             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1597                                zu(nz_do3d), nz_do3d
1598          ELSE
1599             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1600                                TRIM( begin_chr ), averaging_interval, &
1601                                dt_averaging_input, zu(nz_do3d), nz_do3d
1602          ENDIF
1603
[1308]1604          IF ( netcdf_data_format > 4 )  THEN
1605             WRITE ( io, 352 )  ntdim_3d(av)
1606          ELSE
1607             WRITE ( io, 353 )
1608          ENDIF
1609
[1]1610          IF ( av == 0 )  THEN
[1353]1611             IF ( skip_time_do3d /= 0.0_wp )  THEN
[1]1612                WRITE ( io, 339 )  skip_time_do3d
1613             ENDIF
1614          ELSE
[1353]1615             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1616                WRITE ( io, 339 )  skip_time_data_output_av
1617             ENDIF
1618          ENDIF
1619
1620       ENDIF
1621
1622    ENDDO
1623
1624!
[410]1625!-- masked arrays
1626    IF ( masks > 0 )  WRITE ( io, 345 )  &
1627         mask_scale_x, mask_scale_y, mask_scale_z
1628    DO  mid = 1, masks
1629       DO  av = 0, 1
1630
1631          i = 1
1632          domask_chr = ''
1633          DO  WHILE ( domask(mid,av,i) /= ' ' )
1634             domask_chr = TRIM( domask_chr ) // ' ' //  &
1635                          TRIM( domask(mid,av,i) ) // ','
1636             i = i + 1
1637          ENDDO
1638
1639          IF ( domask_chr /= '' )  THEN
1640             IF ( av == 0 )  THEN
1641                WRITE ( io, 346 )  '', mid
1642             ELSE
1643                WRITE ( io, 346 )  ' (time-averaged)', mid
1644             ENDIF
1645
[1783]1646             output_format = netcdf_data_format_string
[1308]1647!--          Parallel output not implemented for mask data, hence
1648!--          output_format must be adjusted.
1649             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1650             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
[1783]1651             IF ( netcdf_deflate == 0 )  THEN
1652                WRITE ( io, 344 )  output_format
1653             ELSE
1654                WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1655             ENDIF
[410]1656
1657             IF ( av == 0 )  THEN
1658                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1659             ELSE
1660                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1661                                   averaging_interval, dt_averaging_input
1662             ENDIF
1663
1664             IF ( av == 0 )  THEN
[1353]1665                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
[410]1666                   WRITE ( io, 339 )  skip_time_domask(mid)
1667                ENDIF
1668             ELSE
[1353]1669                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[410]1670                   WRITE ( io, 339 )  skip_time_data_output_av
1671                ENDIF
1672             ENDIF
1673!
1674!--          output locations
1675             DO  dim = 1, 3
[1353]1676                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
[410]1677                   count = 0
[1353]1678                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
[410]1679                      count = count + 1
1680                   ENDDO
1681                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1682                                      mask(mid,dim,:count)
[1353]1683                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1684                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1685                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
[410]1686                   WRITE ( io, 350 )  dir(dim), dir(dim)
[1353]1687                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
[410]1688                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1689                                      mask_loop(mid,dim,1:2)
1690                ELSE
1691                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1692                                      mask_loop(mid,dim,1:3)
1693                ENDIF
1694             ENDDO
1695          ENDIF
1696
1697       ENDDO
1698    ENDDO
1699
1700!
[1]1701!-- Timeseries
[1322]1702    IF ( dt_dots /= 9999999.9_wp )  THEN
[1]1703       WRITE ( io, 340 )
1704
[1783]1705       output_format = netcdf_data_format_string
1706       IF ( netcdf_deflate == 0 )  THEN
1707          WRITE ( io, 344 )  output_format
1708       ELSE
1709          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1710       ENDIF
[1]1711       WRITE ( io, 341 )  dt_dots
1712    ENDIF
1713
1714#if defined( __dvrp_graphics )
1715!
1716!-- Dvrp-output
[1322]1717    IF ( dt_dvrp /= 9999999.9_wp )  THEN
[1]1718       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1719                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1720       i = 1
1721       l = 0
[336]1722       m = 0
[1]1723       DO WHILE ( mode_dvrp(i) /= ' ' )
1724          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
[130]1725             READ ( mode_dvrp(i), '(10X,I2)' )  j
[1]1726             l = l + 1
1727             IF ( do3d(0,j) /= ' ' )  THEN
[336]1728                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1729                                   isosurface_color(:,l)
[1]1730             ENDIF
1731          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
[130]1732             READ ( mode_dvrp(i), '(6X,I2)' )  j
[336]1733             m = m + 1
1734             IF ( do2d(0,j) /= ' ' )  THEN
1735                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1736                                   slicer_range_limits_dvrp(:,m)
1737             ENDIF
[1]1738          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
[336]1739             WRITE ( io, 363 )  dvrp_psize
1740             IF ( particle_dvrpsize /= 'none' )  THEN
1741                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1742                                   dvrpsize_interval
1743             ENDIF
1744             IF ( particle_color /= 'none' )  THEN
1745                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1746                                   color_interval
1747             ENDIF
[1]1748          ENDIF
1749          i = i + 1
1750       ENDDO
[237]1751
[336]1752       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1753                          superelevation_y, superelevation, clip_dvrp_l, &
1754                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1755
1756       IF ( TRIM( topography ) /= 'flat' )  THEN
1757          WRITE ( io, 366 )  topography_color
1758          IF ( cluster_size > 1 )  THEN
1759             WRITE ( io, 367 )  cluster_size
1760          ENDIF
[237]1761       ENDIF
1762
[1]1763    ENDIF
1764#endif
1765
1766!
1767!-- Spectra output
[1322]1768    IF ( dt_dosp /= 9999999.9_wp )  THEN
[1]1769       WRITE ( io, 370 )
1770
[1783]1771       output_format = netcdf_data_format_string
1772       IF ( netcdf_deflate == 0 )  THEN
1773          WRITE ( io, 344 )  output_format
1774       ELSE
1775          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1776       ENDIF
[1]1777       WRITE ( io, 371 )  dt_dosp
[1353]1778       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
[1]1779       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1780                          ( spectra_direction(i), i = 1,10 ),  &
[189]1781                          ( comp_spectra_level(i), i = 1,100 ), &
1782                          ( plot_spectra_level(i), i = 1,100 ), &
[1]1783                          averaging_interval_sp, dt_averaging_input_pr
1784    ENDIF
1785
1786    WRITE ( io, 99 )
1787
1788!
1789!-- Physical quantities
1790    WRITE ( io, 400 )
1791
1792!
1793!-- Geostrophic parameters
[1551]1794    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1795       WRITE ( io, 417 )  lambda
1796    ENDIF
1797    WRITE ( io, 410 )  phi, omega, f, fs
[1]1798
1799!
1800!-- Other quantities
1801    WRITE ( io, 411 )  g
[1551]1802    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1803       WRITE ( io, 418 )  day_init, time_utc_init
1804    ENDIF
1805
[1179]1806    WRITE ( io, 412 )  TRIM( reference_state )
1807    IF ( use_single_reference_value )  THEN
[97]1808       IF ( ocean )  THEN
[1179]1809          WRITE ( io, 413 )  prho_reference
[97]1810       ELSE
[1179]1811          WRITE ( io, 414 )  pt_reference
[97]1812       ENDIF
1813    ENDIF
[1]1814
1815!
1816!-- Cloud physics parameters
[1299]1817    IF ( cloud_physics )  THEN
[57]1818       WRITE ( io, 415 )
1819       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
[1115]1820       IF ( icloud_scheme == 0 )  THEN
[1353]1821          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
[1115]1822          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1823       ENDIF
[1]1824    ENDIF
1825
1826!
[824]1827!-- Cloud physcis parameters / quantities / numerical methods
1828    WRITE ( io, 430 )
1829    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1830       WRITE ( io, 431 )
1831    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1832       WRITE ( io, 432 )
[1496]1833       IF ( cloud_top_radiation )  WRITE ( io, 132 )
[1115]1834       IF ( icloud_scheme == 1 )  THEN
1835          IF ( precipitation )  WRITE ( io, 133 )
1836       ELSEIF ( icloud_scheme == 0 )  THEN
1837          IF ( drizzle )  WRITE ( io, 506 )
1838          IF ( precipitation )  THEN
1839             WRITE ( io, 505 )
1840             IF ( turbulence )  WRITE ( io, 507 )
1841             IF ( ventilation_effect )  WRITE ( io, 508 )
1842             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1843          ENDIF
1844       ENDIF
[824]1845    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1846       WRITE ( io, 433 )
1847       IF ( curvature_solution_effects )  WRITE ( io, 434 )
[825]1848       IF ( collision_kernel /= 'none' )  THEN
1849          WRITE ( io, 435 )  TRIM( collision_kernel )
[828]1850          IF ( collision_kernel(6:9) == 'fast' )  THEN
1851             WRITE ( io, 436 )  radius_classes, dissipation_classes
1852          ENDIF
[825]1853       ELSE
[828]1854          WRITE ( io, 437 )
[825]1855       ENDIF
[824]1856    ENDIF
1857
1858!
[1]1859!-- LES / turbulence parameters
1860    WRITE ( io, 450 )
1861
1862!--
1863! ... LES-constants used must still be added here
1864!--
1865    IF ( constant_diffusion )  THEN
1866       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1867                          prandtl_number
1868    ENDIF
1869    IF ( .NOT. constant_diffusion)  THEN
[1353]1870       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1871       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
[1]1872       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1873    ENDIF
1874
1875!
1876!-- Special actions during the run
1877    WRITE ( io, 470 )
1878    IF ( create_disturbances )  THEN
1879       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1880                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1881                          zu(disturbance_level_ind_t), disturbance_level_ind_t
[707]1882       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1]1883          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1884       ELSE
1885          WRITE ( io, 473 )  disturbance_energy_limit
1886       ENDIF
1887       WRITE ( io, 474 )  TRIM( random_generator )
1888    ENDIF
[1353]1889    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
[1]1890       WRITE ( io, 475 )  pt_surface_initial_change
1891    ENDIF
[1353]1892    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
[1]1893       WRITE ( io, 476 )  q_surface_initial_change       
1894    ENDIF
[1353]1895    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
[1]1896       WRITE ( io, 477 )  q_surface_initial_change       
1897    ENDIF
1898
[60]1899    IF ( particle_advection )  THEN
[1]1900!
[60]1901!--    Particle attributes
1902       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1903                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
[1359]1904                          end_time_prel
[60]1905       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1906       IF ( random_start_position )  WRITE ( io, 481 )
[1575]1907       IF ( seed_follows_topography )  WRITE ( io, 496 )
[60]1908       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1909       WRITE ( io, 495 )  total_number_of_particles
[824]1910       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
[60]1911          WRITE ( io, 483 )  maximum_number_of_tailpoints
1912          IF ( minimum_tailpoint_distance /= 0 )  THEN
1913             WRITE ( io, 484 )  total_number_of_tails,      &
1914                                minimum_tailpoint_distance, &
1915                                maximum_tailpoint_age
1916          ENDIF
[1]1917       ENDIF
[1322]1918       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
[60]1919          WRITE ( io, 485 )  dt_write_particle_data
[1327]1920          IF ( netcdf_data_format > 1 )  THEN
1921             output_format = 'netcdf (64 bit offset) and binary'
[1]1922          ELSE
[1327]1923             output_format = 'netcdf and binary'
[1]1924          ENDIF
[1783]1925          IF ( netcdf_deflate == 0 )  THEN
1926             WRITE ( io, 344 )  output_format
1927          ELSE
1928             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1929          ENDIF
[1]1930       ENDIF
[1322]1931       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
[60]1932       IF ( write_particle_statistics )  WRITE ( io, 486 )
[1]1933
[60]1934       WRITE ( io, 487 )  number_of_particle_groups
[1]1935
[60]1936       DO  i = 1, number_of_particle_groups
[1322]1937          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
[1353]1938             WRITE ( io, 490 )  i, 0.0_wp
[60]1939             WRITE ( io, 492 )
[1]1940          ELSE
[60]1941             WRITE ( io, 490 )  i, radius(i)
[1353]1942             IF ( density_ratio(i) /= 0.0_wp )  THEN
[60]1943                WRITE ( io, 491 )  density_ratio(i)
1944             ELSE
1945                WRITE ( io, 492 )
1946             ENDIF
[1]1947          ENDIF
[60]1948          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1949                             pdx(i), pdy(i), pdz(i)
[336]1950          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
[60]1951       ENDDO
[1]1952
[60]1953    ENDIF
[1]1954
[60]1955
[1]1956!
1957!-- Parameters of 1D-model
1958    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1959       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1960                          mixing_length_1d, dissipation_1d
1961       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1962          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1963       ENDIF
1964    ENDIF
1965
1966!
[1551]1967!-- User-defined information
[1]1968    CALL user_header( io )
1969
1970    WRITE ( io, 99 )
1971
1972!
1973!-- Write buffer contents to disc immediately
[82]1974    CALL local_flush( io )
[1]1975
1976!
1977!-- Here the FORMATs start
1978
1979 99 FORMAT (1X,78('-'))
[1468]1980100 FORMAT (/1X,'******************************',4X,44('-')/        &
1981            1X,'* ',A,' *',4X,A/                               &
1982            1X,'******************************',4X,44('-'))
1983101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1984            35X,42('-'))
1985102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1986            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
[1106]1987            ' Run on host:        ',A10)
[1]1988#if defined( __parallel )
[1468]1989103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
[1]1990              ')',1X,A)
[1468]1991104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1992              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1993105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1994106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1995            35X,'because the job is running on an SMP-cluster')
1996107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1997108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1998109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1999            35X,42('-'))
2000114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
2001            35X,'independent precursor runs'/             &
2002            35X,42('-'))
[1111]2003117 FORMAT (' Accelerator boards / node:  ',I2)
[1]2004#endif
2005110 FORMAT (/' Numerical Schemes:'/ &
2006             ' -----------------'/)
2007111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
2008112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
[1697]2009            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
[1]2010113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
2011                  ' or Upstream')
[1216]2012115 FORMAT ('     FFT and transpositions are overlapping')
[1]2013116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
2014                  ' or Upstream')
2015118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
[1106]2016119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
2017            '     translation velocity = ',A/ &
[1]2018            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
[1111]2019120 FORMAT (' Accelerator boards: ',8X,I2)
[1]2020122 FORMAT (' --> Time differencing scheme: ',A)
[108]2021123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
[1697]2022            '     maximum damping coefficient:',F6.3, ' 1/s')
[1]2023129 FORMAT (' --> Additional prognostic equation for the specific humidity')
2024130 FORMAT (' --> Additional prognostic equation for the total water content')
[940]2025131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
2026                  F6.2, ' K assumed')
[824]2027132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
[1]2028            '     effective emissivity scheme')
[824]2029133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
[1]2030134 FORMAT (' --> Additional prognostic equation for a passive scalar')
[1575]2031135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
[1]2032                  A,'-cycle)'/ &
2033            '     number of grid levels:                   ',I2/ &
2034            '     Gauss-Seidel red/black iterations:       ',I2)
2035136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
2036                  I3,')')
2037137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
2038            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
2039                  I3,')'/ &
2040            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
2041                  I3,')')
[63]2042139 FORMAT (' --> Loop optimization method: ',A)
[1]2043140 FORMAT ('     maximum residual allowed:                ',E10.3)
2044141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
2045142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
2046                  'step')
[87]2047143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
2048                  'kinetic energy')
[927]2049144 FORMAT ('     masking method is used')
[1]2050150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
[241]2051                  'conserved'/ &
2052            '     using the ',A,' mode')
2053151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
[306]2054152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
2055           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
2056           /'     starting from dp_level_b =', F8.3, 'm', A /)
[1365]2057160 FORMAT (//' Large scale forcing and nudging:'/ &
2058              ' -------------------------------'/)
2059161 FORMAT (' --> No large scale forcing from external is used (default) ')
2060162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
2061163 FORMAT ('     - large scale advection tendencies ')
2062164 FORMAT ('     - large scale subsidence velocity w_subs ')
2063165 FORMAT ('     - large scale subsidence tendencies ')
2064167 FORMAT ('     - and geostrophic wind components ug and vg')
2065168 FORMAT (' --> Large-scale vertical motion is used in the ', &
[1299]2066                  'prognostic equation(s) for')
[1365]2067169 FORMAT ('     the scalar(s) only')
2068170 FORMAT (' --> Nudging is used')
2069171 FORMAT (' --> No nudging is used (default) ')
2070180 FORMAT ('     - prescribed surface values for temperature')
[1376]2071181 FORMAT ('     - prescribed surface fluxes for temperature')
2072182 FORMAT ('     - prescribed surface values for humidity')
[1365]2073183 FORMAT ('     - prescribed surface fluxes for humidity')
[1]2074200 FORMAT (//' Run time and time step information:'/ &
2075             ' ----------------------------------'/)
[1106]2076201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
[1697]2077             '    CFL-factor:',F5.2)
[1106]2078202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
2079203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
2080             ' End time:            ',F9.3,' s')
[1]2081204 FORMAT ( A,F9.3,' s')
2082205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
[1106]2083206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
2084             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
2085               '  ',F9.3,' s'/                                                    &
[1111]2086             '                                      per second of simulated tim', &
[1]2087               'e: ',F9.3,' s')
[1106]2088207 FORMAT ( ' Coupling start time: ',F9.3,' s')
[1]2089250 FORMAT (//' Computational grid and domain size:'/ &
2090              ' ----------------------------------'// &
2091              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
2092              ' m    dz =    ',F7.3,' m'/ &
2093              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
2094              ' m  z(u) = ',F10.3,' m'/)
2095252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
[1697]2096              ' factor:',F6.3/ &
[1]2097            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
2098254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
2099            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
2100260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
2101             ' degrees')
[1551]2102270 FORMAT (//' Topography information:'/ &
2103              ' ----------------------'// &
[1]2104              1X,'Topography: ',A)
2105271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
2106              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
2107                ' / ',I4)
[240]2108272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
2109              ' direction' / &
2110              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
2111              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
[256]2112278 FORMAT (' Topography grid definition convention:'/ &
2113            ' cell edge (staggered grid points'/  &
2114            ' (u in x-direction, v in y-direction))' /)
2115279 FORMAT (' Topography grid definition convention:'/ &
2116            ' cell center (scalar grid points)' /)
[138]2117280 FORMAT (//' Vegetation canopy (drag) model:'/ &
2118              ' ------------------------------'// &
2119              ' Canopy mode: ', A / &
[1484]2120              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
[138]2121              ' Leaf drag coefficient: ',F6.2 /)
[1484]2122281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
[153]2123              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
2124282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
2125283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
[138]2126              ' Height:              ',A,'  m'/ &
2127              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2128              ' Gradient:            ',A,'  m**2/m**4'/ &
2129              ' Gridpoint:           ',A)
[1484]2130284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
2131              ' Height:              ',A,'  m'/ &
2132              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2133              ' Coefficient alpha: ',F6.2 / &
2134              ' Coefficient beta: ',F6.2 / &
2135              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
[138]2136               
[1]2137300 FORMAT (//' Boundary conditions:'/ &
2138             ' -------------------'// &
2139             '                     p                    uv             ', &
[1551]2140             '                     pt'// &
[1]2141             ' B. bound.: ',A/ &
2142             ' T. bound.: ',A)
[97]2143301 FORMAT (/'                     ',A// &
[1]2144             ' B. bound.: ',A/ &
2145             ' T. bound.: ',A)
[19]2146303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
2147304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
2148305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
2149               'computational u,v-level:'// &
[1697]2150             '       zp = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
2151             ' m   kappa =',F5.2/ &
2152             '       Rif value range:   ',F8.2,' <= rif <=',F6.2)
[97]2153306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
[1]2154307 FORMAT ('       Heatflux has a random normal distribution')
2155308 FORMAT ('       Predefined surface temperature')
[97]2156309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
[1]2157310 FORMAT (//'    1D-Model:'// &
2158             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2159311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
2160312 FORMAT ('       Predefined surface humidity')
2161313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
2162314 FORMAT ('       Predefined scalar value at the surface')
[19]2163315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
[102]2164316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
2165                    'atmosphere model')
[1]2166317 FORMAT (//' Lateral boundaries:'/ &
2167            '       left/right:  ',A/    &
2168            '       north/south: ',A)
[1159]2169318 FORMAT (/'       use_cmax: ',L1 / &
2170            '       pt damping layer width = ',F8.2,' m, pt ', &
[1697]2171                    'damping factor =',F7.4)
[151]2172319 FORMAT ('       turbulence recycling at inflow switched on'/ &
2173            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2174            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
2175320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
[103]2176            '                                          v: ',F9.6,' m**2/s**2')
[1365]2177321 FORMAT (//' Initial profiles:'/ &
2178              ' ----------------')
[1560]2179322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2180            '       y shift of the recycled inflow turbulence switched on'/ &
2181            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
[1592]2182            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
[151]2183325 FORMAT (//' List output:'/ &
[1]2184             ' -----------'//  &
2185            '    1D-Profiles:'/    &
2186            '       Output every             ',F8.2,' s')
[151]2187326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
[1]2188            '       Averaging input every    ',F8.2,' s')
2189330 FORMAT (//' Data output:'/ &
2190             ' -----------'/)
2191331 FORMAT (/'    1D-Profiles:')
2192332 FORMAT (/'       ',A)
2193333 FORMAT ('       Output every             ',F8.2,' s',/ &
2194            '       Time averaged over       ',F8.2,' s'/ &
2195            '       Averaging input every    ',F8.2,' s')
2196334 FORMAT (/'    2D-Arrays',A,':')
2197335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2198            '       Output every             ',F8.2,' s  ',A/ &
2199            '       Cross sections at ',A1,' = ',A/ &
2200            '       scalar-coordinates:   ',A,' m'/)
2201336 FORMAT (/'    3D-Arrays',A,':')
2202337 FORMAT (/'       Arrays: ',A/ &
2203            '       Output every             ',F8.2,' s  ',A/ &
2204            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2205339 FORMAT ('       No output during initial ',F8.2,' s')
2206340 FORMAT (/'    Time series:')
2207341 FORMAT ('       Output every             ',F8.2,' s'/)
2208342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2209            '       Output every             ',F8.2,' s  ',A/ &
2210            '       Time averaged over       ',F8.2,' s'/ &
2211            '       Averaging input every    ',F8.2,' s'/ &
2212            '       Cross sections at ',A1,' = ',A/ &
2213            '       scalar-coordinates:   ',A,' m'/)
2214343 FORMAT (/'       Arrays: ',A/ &
2215            '       Output every             ',F8.2,' s  ',A/ &
2216            '       Time averaged over       ',F8.2,' s'/ &
2217            '       Averaging input every    ',F8.2,' s'/ &
2218            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
[292]2219344 FORMAT ('       Output format: ',A/)
[410]2220345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2221            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2222            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2223            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2224346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2225347 FORMAT ('       Variables: ',A/ &
2226            '       Output every             ',F8.2,' s')
2227348 FORMAT ('       Variables: ',A/ &
2228            '       Output every             ',F8.2,' s'/ &
2229            '       Time averaged over       ',F8.2,' s'/ &
2230            '       Averaging input every    ',F8.2,' s')
2231349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2232            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2233            13('       ',8(F8.2,',')/) )
2234350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2235            'all gridpoints along ',A,'-direction (default).' )
2236351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2237            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2238            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
[1313]2239352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2240353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
[1783]2241354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
[1]2242#if defined( __dvrp_graphics )
2243360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2244            '       Output every      ',F7.1,' s'/ &
2245            '       Output mode:      ',A/ &
2246            '       Host / User:      ',A,' / ',A/ &
2247            '       Directory:        ',A// &
2248            '       The sequence contains:')
[337]2249361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2250            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2251362 FORMAT (/'       Slicer plane ',A/ &
[336]2252            '       Slicer limits: [',F6.2,',',F6.2,']')
[337]2253363 FORMAT (/'       Particles'/ &
[336]2254            '          particle size:  ',F7.2,' m')
2255364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
2256                       F6.2,',',F6.2,']')
[337]2257365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
[336]2258            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2259                     ')'/ &
2260            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2261            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
[337]2262366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
[336]2263367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
[1]2264#endif
2265370 FORMAT ('    Spectra:')
2266371 FORMAT ('       Output every ',F7.1,' s'/)
2267372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
2268            '       Directions: ', 10(A5,',')/                         &
[189]2269            '       height levels  k = ', 20(I3,',')/                  &
2270            '                          ', 20(I3,',')/                  &
2271            '                          ', 20(I3,',')/                  &
2272            '                          ', 20(I3,',')/                  &
2273            '                          ', 19(I3,','),I3,'.'/           &
[1]2274            '       height levels selected for standard plot:'/        &
[189]2275            '                      k = ', 20(I3,',')/                  &
2276            '                          ', 20(I3,',')/                  &
2277            '                          ', 20(I3,',')/                  &
2278            '                          ', 20(I3,',')/                  &
2279            '                          ', 19(I3,','),I3,'.'/           &
[1]2280            '       Time averaged over ', F7.1, ' s,' /                &
2281            '       Profiles for the time averaging are taken every ', &
2282                    F6.1,' s')
2283400 FORMAT (//' Physical quantities:'/ &
2284              ' -------------------'/)
[1551]2285410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
[1697]2286            '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
[1551]2287            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2288            '                            f*     = ',F9.6,' 1/s')
2289411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
[1179]2290412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2291413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2292414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
[1551]2293415 FORMAT (/' Cloud physics parameters:'/ &
2294             ' ------------------------'/)
2295416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2296            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
[1697]2297            '    Density of air     :   rho_0 =',F6.3,' kg/m**3'/  &
[1551]2298            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
[1697]2299            '    Vapourization heat :   L_v   =',E9.2,' J/kg')
[1551]2300417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2301418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2302            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2303419 FORMAT (//' Land surface model information:'/ &
2304              ' ------------------------------'/)
[1]2305420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2306            '       Height:        ',A,'  m'/ &
2307            '       Temperature:   ',A,'  K'/ &
2308            '       Gradient:      ',A,'  K/100m'/ &
2309            '       Gridpoint:     ',A)
2310421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2311            '       Height:      ',A,'  m'/ &
2312            '       Humidity:    ',A,'  kg/kg'/ &
2313            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2314            '       Gridpoint:   ',A)
2315422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2316            '       Height:                  ',A,'  m'/ &
2317            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2318            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2319            '       Gridpoint:               ',A)
2320423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2321            '       Height:      ',A,'  m'/ &
2322            '       ug:          ',A,'  m/s'/ &
2323            '       Gradient:    ',A,'  1/100s'/ &
2324            '       Gridpoint:   ',A)
2325424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2326            '       Height:      ',A,'  m'/ &
[97]2327            '       vg:          ',A,'  m/s'/ &
[1]2328            '       Gradient:    ',A,'  1/100s'/ &
2329            '       Gridpoint:   ',A)
[97]2330425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2331            '       Height:     ',A,'  m'/ &
2332            '       Salinity:   ',A,'  psu'/ &
2333            '       Gradient:   ',A,'  psu/100m'/ &
2334            '       Gridpoint:  ',A)
[411]2335426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2336            '       Height:      ',A,'  m'/ &
2337            '       w_subs:      ',A,'  m/s'/ &
2338            '       Gradient:    ',A,'  (m/s)/100m'/ &
2339            '       Gridpoint:   ',A)
[767]2340427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2341                  ' profiles')
[1241]2342428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2343             '    NUDGING_DATA')
[824]2344430 FORMAT (//' Cloud physics quantities / methods:'/ &
2345              ' ----------------------------------'/)
2346431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2347                 'on)')
2348432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2349            '    total water content is used.'/ &
2350            '    Condensation is parameterized via 0% - or 100% scheme.')
2351433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2352                 'icle model')
2353434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2354                 ' droplets < 1.0E-6 m')
[825]2355435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
[828]2356436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2357                    'are used'/ &
2358            '          number of radius classes:       ',I3,'    interval ', &
2359                       '[1.0E-6,2.0E-4] m'/ &
2360            '          number of dissipation classes:   ',I2,'    interval ', &
2361                       '[0,1000] cm**2/s**3')
2362437 FORMAT ('    Droplet collision is switched off')
[1551]2363438 FORMAT (' --> Land surface type  : ',A,/ &
2364            ' --> Soil porosity type : ',A)
2365439 FORMAT (/'    Initial soil temperature and moisture profile:'// &
2366            '       Height:        ',A,'  m'/ &
2367            '       Temperature:   ',A,'  K'/ &
2368            '       Moisture:      ',A,'  m**3/m**3'/ &
2369            '       Root fraction: ',A,'  '/ &
2370            '       Gridpoint:     ',A)
[1788]2371440 FORMAT (' --> Soil bottom is closed (water content is conserved, default)')
2372441 FORMAT (' --> Soil bottom is open (water content is not conserved)')
[1551]2373444 FORMAT (//' Radiation model information:'/                                 &
2374              ' ----------------------------'/)
2375445 FORMAT (' --> Using constant net radiation: net_radiation = ', F6.2, '  W/m**2')
2376446 FORMAT (' --> Simple radiation scheme for clear sky is used (no clouds,',  &
2377                   ' default)')
[1585]2378447 FORMAT (' --> RRTMG scheme is used')
[1697]2379448 FORMAT (/'     User-specific surface albedo: albedo =', F6.3)
[1585]2380449 FORMAT  ('     Timestep: dt_radiation = ', F5.2, '  s')
[1551]2381
[1]2382450 FORMAT (//' LES / Turbulence quantities:'/ &
2383              ' ---------------------------'/)
[824]2384451 FORMAT ('    Diffusion coefficients are constant:'/ &
2385            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
[1697]2386453 FORMAT ('    Mixing length is limited to',F5.2,' * z')
[824]2387454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2388455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
[1585]2389456 FORMAT (/'    Albedo is set for land surface type: ', A)
2390457 FORMAT (/'    --> Albedo is fixed during the run')
2391458 FORMAT (/'    --> Longwave radiation is disabled')
2392459 FORMAT (/'    --> Shortwave radiation is disabled.')
[1]2393470 FORMAT (//' Actions during the simulation:'/ &
2394              ' -----------------------------'/)
[94]2395471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
[1697]2396            '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
[94]2397            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2398            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
[1]2399472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2400                 ' to i/j =',I4)
2401473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
[1697]2402                 F6.3, ' m**2/s**2')
[1]2403474 FORMAT ('    Random number generator used    : ',A/)
2404475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2405                 'respectively, if'/ &
2406            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2407                 ' 3D-simulation'/)
2408476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2409                 'respectively, if the'/ &
2410            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2411                 ' the 3D-simulation'/)
2412477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2413                 'respectively, if the'/ &
2414            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2415                 ' the 3D-simulation'/)
2416480 FORMAT ('    Particles:'/ &
2417            '    ---------'// &
2418            '       Particle advection is active (switched on at t = ', F7.1, &
2419                    ' s)'/ &
2420            '       Start of new particle generations every  ',F6.1,' s'/ &
2421            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2422            '                            bottom:     ', A, ' top:         ', A/&
2423            '       Maximum particle age:                 ',F9.1,' s'/ &
[1359]2424            '       Advection stopped at t = ',F9.1,' s'/)
[1]2425481 FORMAT ('       Particles have random start positions'/)
[336]2426482 FORMAT ('          Particles are advected only horizontally'/)
[1]2427483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2428484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2429            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2430            '            Maximum age of the end of the tail:  ',F8.2,' s')
2431485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2432486 FORMAT ('       Particle statistics are written on file'/)
2433487 FORMAT ('       Number of particle groups: ',I2/)
2434488 FORMAT ('       SGS velocity components are used for particle advection'/ &
[1697]2435            '          minimum timestep for advection:', F8.5/)
[1]2436489 FORMAT ('       Number of particles simultaneously released at each ', &
2437                    'point: ', I5/)
2438490 FORMAT ('       Particle group ',I2,':'/ &
2439            '          Particle radius: ',E10.3, 'm')
2440491 FORMAT ('          Particle inertia is activated'/ &
[1697]2441            '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
[1]2442492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2443493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2444            '                                         y:',F8.1,' - ',F8.1,' m'/&
2445            '                                         z:',F8.1,' - ',F8.1,' m'/&
2446            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2447                       ' m  dz = ',F8.1,' m'/)
2448494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2449                    F8.2,' s'/)
2450495 FORMAT ('       Number of particles in total domain: ',I10/)
[1575]2451496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2452                    'as relative to the given topography')
[1]2453500 FORMAT (//' 1D-Model parameters:'/                           &
2454              ' -------------------'//                           &
2455            '    Simulation time:                   ',F8.1,' s'/ &
2456            '    Run-controll output every:         ',F8.1,' s'/ &
2457            '    Vertical profile output every:     ',F8.1,' s'/ &
2458            '    Mixing length calculation:         ',A/         &
2459            '    Dissipation calculation:           ',A/)
2460502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
[667]2461503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2462504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
[1115]2463505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2464506 FORMAT ('    Drizzle parameterization via Stokes law')
2465507 FORMAT ('    Turbulence effects on precipitation process')
2466508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2467509 FORMAT ('    Slope limiter used for sedimentation process')
[1551]2468510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2469511 FORMAT ('    Sedimentation Courant number:                  '/&
[1697]2470            '                               C_s   =',F4.1,'        ')
[1429]2471512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2472            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2473            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
[1557]2474513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2475            '+ monotonic adjustment')
[1791]2476600 FORMAT (/' Nesting informations:'/ &
2477            ' --------------------'/ &
2478            ' Nesting mode:                     ',A// &
2479            ' Nest id  parent  number   lower left coordinates   name'/ &
2480            ' (*=me)     id    of PEs      x (m)     y (m)' )
2481601 FORMAT (2X,A1,1X,I2.2,6X,I2.2,5X,I5,5X,F8.2,2X,F8.2,5X,A)
[1]2482
2483 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.