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

Last change on this file since 1850 was 1849, checked in by hoffmann, 8 years ago

lpm_droplet_condensation improved, microphysics partially modularized

  • Property svn:keywords set to Id
File size: 86.0 KB
Line 
1!> @file header.f90
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!
16! Copyright 1997-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21! Adapted for modularization of microphysics
22!
23! Former revisions:
24! -----------------
25! $Id: header.f90 1849 2016-04-08 11:33:18Z maronga $
26!
27! 1833 2016-04-07 14:23:03Z raasch
28! spectrum renamed spectra_mod, output of spectra related quantities moved to
29! spectra_mod
30!
31! 1831 2016-04-07 13:15:51Z hoffmann
32! turbulence renamed collision_turbulence,
33! drizzle renamed cloud_water_sedimentation
34!
35! 1826 2016-04-07 12:01:39Z maronga
36! Moved radiation model header output to the respective module.
37! Moved canopy model header output to the respective module.
38!
39! 1822 2016-04-07 07:49:42Z hoffmann
40! Tails removed. icloud_scheme replaced by microphysics_*
41!
42! 1817 2016-04-06 15:44:20Z maronga
43! Moved land_surface_model header output to the respective module.
44!
45! 1808 2016-04-05 19:44:00Z raasch
46! routine local_flush replaced by FORTRAN statement
47!
48! 1797 2016-03-21 16:50:28Z raasch
49! output of nesting datatransfer mode
50!
51! 1791 2016-03-11 10:41:25Z raasch
52! output of nesting informations of all domains
53!
54! 1788 2016-03-10 11:01:04Z maronga
55! Parameter dewfall removed
56!
57! 1786 2016-03-08 05:49:27Z raasch
58! cpp-direktives for spectra removed
59!
60! 1783 2016-03-06 18:36:17Z raasch
61! netcdf module and variable names changed, output of netcdf_deflate
62!
63! 1764 2016-02-28 12:45:19Z raasch
64! output of nesting informations
65!
66! 1697 2015-10-28 17:14:10Z raasch
67! small E- and F-FORMAT changes to avoid informative compiler messages about
68! insufficient field width
69!
70! 1691 2015-10-26 16:17:44Z maronga
71! Renamed prandtl_layer to constant_flux_layer, renames rif_min/rif_max to
72! zeta_min/zeta_max.
73!
74! 1682 2015-10-07 23:56:08Z knoop
75! Code annotations made doxygen readable
76!
77! 1675 2015-10-02 08:28:59Z gronemeier
78! Bugfix: Definition of topography grid levels
79!
80! 1660 2015-09-21 08:15:16Z gronemeier
81! Bugfix: Definition of building/street canyon height if vertical grid stretching
82!         starts below the maximum topography height.
83!
84! 1590 2015-05-08 13:56:27Z maronga
85! Bugfix: Added TRIM statements for character strings for LSM and radiation code
86!
87! 1585 2015-04-30 07:05:52Z maronga
88! Further output for radiation model(s).
89!
90! 1575 2015-03-27 09:56:27Z raasch
91! adjustments for psolver-queries, output of seed_follows_topography
92!
93! 1560 2015-03-06 10:48:54Z keck
94! output for recycling y shift
95!
96! 1557 2015-03-05 16:43:04Z suehring
97! output for monotonic limiter
98!
99! 1551 2015-03-03 14:18:16Z maronga
100! Added informal output for land surface model and radiation model. Removed typo.
101!
102! 1496 2014-12-02 17:25:50Z maronga
103! Renamed: "radiation -> "cloud_top_radiation"
104!
105! 1484 2014-10-21 10:53:05Z kanani
106! Changes due to new module structure of the plant canopy model:
107!   module plant_canopy_model_mod and output for new canopy model parameters
108!   (alpha_lad, beta_lad, lai_beta,...) added,
109!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
110!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
111!   learde renamed leaf_area_density.
112! Bugfix: DO-WHILE-loop for lad header information additionally restricted
113! by maximum number of gradient levels (currently 10)
114!
115! 1482 2014-10-18 12:34:45Z raasch
116! information about calculated or predefined virtual processor topology adjusted
117!
118! 1468 2014-09-24 14:06:57Z maronga
119! Adapted for use on up to 6-digit processor cores
120!
121! 1429 2014-07-15 12:53:45Z knoop
122! header exended to provide ensemble_member_nr if specified
123!
124! 1376 2014-04-26 11:21:22Z boeske
125! Correction of typos
126!
127! 1365 2014-04-22 15:03:56Z boeske
128! New section 'Large scale forcing and nudging':
129! output of large scale forcing and nudging information,
130! new section for initial profiles created
131!
132! 1359 2014-04-11 17:15:14Z hoffmann
133! dt_sort_particles removed
134!
135! 1353 2014-04-08 15:21:23Z heinze
136! REAL constants provided with KIND-attribute
137!
138! 1327 2014-03-21 11:00:16Z raasch
139! parts concerning iso2d and avs output removed,
140! -netcdf output queries
141!
142! 1324 2014-03-21 09:13:16Z suehring
143! Bugfix: module spectrum added
144!
145! 1322 2014-03-20 16:38:49Z raasch
146! REAL functions provided with KIND-attribute,
147! some REAL constants defined as wp-kind
148!
149! 1320 2014-03-20 08:40:49Z raasch
150! ONLY-attribute added to USE-statements,
151! kind-parameters added to all INTEGER and REAL declaration statements,
152! kinds are defined in new module kinds,
153! revision history before 2012 removed,
154! comment fields (!:) to be used for variable explanations added to
155! all variable declaration statements
156!
157! 1308 2014-03-13 14:58:42Z fricke
158! output of the fixed number of output time levels
159! output_format adjusted for masked data if netcdf_data_format > 5
160!
161! 1299 2014-03-06 13:15:21Z heinze
162! output for using large_scale subsidence in combination
163! with large_scale_forcing
164! reformatting, more detailed explanations
165!
166! 1241 2013-10-30 11:36:58Z heinze
167! output for nudging + large scale forcing from external file
168!
169! 1216 2013-08-26 09:31:42Z raasch
170! output for transpose_compute_overlap
171!
172! 1212 2013-08-15 08:46:27Z raasch
173! output for poisfft_hybrid removed
174!
175! 1179 2013-06-14 05:57:58Z raasch
176! output of reference_state, use_reference renamed use_single_reference_value
177!
178! 1159 2013-05-21 11:58:22Z fricke
179! +use_cmax
180!
181! 1115 2013-03-26 18:16:16Z hoffmann
182! descriptions for Seifert-Beheng-cloud-physics-scheme added
183!
184! 1111 2013-03-08 23:54:10Z raasch
185! output of accelerator board information
186! ibc_p_b = 2 removed
187!
188! 1108 2013-03-05 07:03:32Z raasch
189! bugfix for r1106
190!
191! 1106 2013-03-04 05:31:38Z raasch
192! some format changes for coupled runs
193!
194! 1092 2013-02-02 11:24:22Z raasch
195! unused variables removed
196!
197! 1036 2012-10-22 13:43:42Z raasch
198! code put under GPL (PALM 3.9)
199!
200! 1031 2012-10-19 14:35:30Z raasch
201! output of netCDF data format modified
202!
203! 1015 2012-09-27 09:23:24Z raasch
204! output of Adjustment of mixing length to the Prandtl mixing length at first
205! grid point above ground removed
206!
207! 1003 2012-09-14 14:35:53Z raasch
208! output of information about equal/unequal subdomain size removed
209!
210! 1001 2012-09-13 14:08:46Z raasch
211! all actions concerning leapfrog- and upstream-spline-scheme removed
212!
213! 978 2012-08-09 08:28:32Z fricke
214! -km_damp_max, outflow_damping_width
215! +pt_damping_factor, pt_damping_width
216! +z0h
217!
218! 964 2012-07-26 09:14:24Z raasch
219! output of profil-related quantities removed
220!
221! 940 2012-07-09 14:31:00Z raasch
222! Output in case of simulations for pure neutral stratification (no pt-equation
223! solved)
224!
225! 927 2012-06-06 19:15:04Z raasch
226! output of masking_method for mg-solver
227!
228! 868 2012-03-28 12:21:07Z raasch
229! translation velocity in Galilean transformation changed to 0.6 * ug
230!
231! 833 2012-02-22 08:55:55Z maronga
232! Adjusted format for leaf area density
233!
234! 828 2012-02-21 12:00:36Z raasch
235! output of dissipation_classes + radius_classes
236!
237! 825 2012-02-19 03:03:44Z raasch
238! Output of cloud physics parameters/quantities complemented and restructured
239!
240! Revision 1.1  1997/08/11 06:17:20  raasch
241! Initial revision
242!
243!
244! Description:
245! ------------
246!> Writing a header with all important information about the current run.
247!> This subroutine is called three times, two times at the beginning
248!> (writing information on files RUN_CONTROL and HEADER) and one time at the
249!> end of the run, then writing additional information about CPU-usage on file
250!> header.
251!-----------------------------------------------------------------------------!
252 SUBROUTINE header
253 
254
255    USE arrays_3d,                                                             &
256        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu, zw
257       
258    USE control_parameters
259       
260    USE cloud_parameters,                                                      &
261        ONLY:  cp, l_v, r_d
262
263    USE cpulog,                                                                &
264        ONLY:  log_point_s
265       
266    USE dvrp_variables,                                                        &
267        ONLY:  use_seperate_pe_for_dvrp_output
268       
269    USE grid_variables,                                                        &
270        ONLY:  dx, dy
271       
272    USE indices,                                                               &
273        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
274               nys_mg, nzt, nzt_mg
275       
276    USE kinds
277 
278    USE land_surface_model_mod,                                                &
279        ONLY: land_surface, lsm_header
280
281    USE microphysics_mod,                                                      &
282        ONLY:  cloud_water_sedimentation, collision_turbulence,                &
283               c_sedimentation, limiter_sedimentation, nc_const,               &
284               ventilation_effect
285
286    USE model_1d,                                                              &
287        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
288       
289    USE netcdf_interface,                                                      &
290        ONLY:  netcdf_data_format, netcdf_data_format_string, netcdf_deflate
291
292    USE particle_attributes,                                                   &
293        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
294               curvature_solution_effects,                                     &
295               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
296               dt_write_particle_data, end_time_prel,                          &
297               number_of_particle_groups, particle_advection,                  &
298               particle_advection_start,                                       &
299               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
300               pst, radius, radius_classes, random_start_position,             &
301               seed_follows_topography,                                        &
302               total_number_of_particles, use_sgs_for_particles,               &
303               vertical_particle_advection, write_particle_statistics
304       
305    USE pegrid
306
307    USE plant_canopy_model_mod,                                                &
308        ONLY:  pcm_header, plant_canopy
309
310    USE pmc_handle_communicator,                                               &
311        ONLY:  pmc_get_model_info
312
313    USE pmc_interface,                                                         &
314        ONLY:  nested_run, nesting_datatransfer_mode, nesting_mode
315
316    USE radiation_model_mod,                                                   &
317        ONLY:  radiation, radiation_header
318   
319    USE spectra_mod,                                                           &
320        ONLY:  calculate_spectra, spectra_header
321
322    IMPLICIT NONE
323
324    CHARACTER (LEN=1)  ::  prec                !<
325   
326    CHARACTER (LEN=2)  ::  do2d_mode           !<
327   
328    CHARACTER (LEN=5)  ::  section_chr         !<
329   
330    CHARACTER (LEN=10) ::  coor_chr            !<
331    CHARACTER (LEN=10) ::  host_chr            !<
332   
333    CHARACTER (LEN=16) ::  begin_chr           !<
334   
335    CHARACTER (LEN=26) ::  ver_rev             !<
336
337    CHARACTER (LEN=32) ::  cpl_name            !<
338   
339    CHARACTER (LEN=40) ::  output_format       !<
340   
341    CHARACTER (LEN=70) ::  char1               !<
342    CHARACTER (LEN=70) ::  char2               !<
343    CHARACTER (LEN=70) ::  dopr_chr            !<
344    CHARACTER (LEN=70) ::  do2d_xy             !<
345    CHARACTER (LEN=70) ::  do2d_xz             !<
346    CHARACTER (LEN=70) ::  do2d_yz             !<
347    CHARACTER (LEN=70) ::  do3d_chr            !<
348    CHARACTER (LEN=70) ::  domask_chr          !<
349    CHARACTER (LEN=70) ::  run_classification  !<
350   
351    CHARACTER (LEN=85) ::  r_upper             !<
352    CHARACTER (LEN=85) ::  r_lower             !<
353   
354    CHARACTER (LEN=86) ::  coordinates         !<
355    CHARACTER (LEN=86) ::  gradients           !<
356    CHARACTER (LEN=86) ::  slices              !<
357    CHARACTER (LEN=86) ::  temperatures        !<
358    CHARACTER (LEN=86) ::  ugcomponent         !<
359    CHARACTER (LEN=86) ::  vgcomponent         !<
360
361    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !<
362
363    INTEGER(iwp) ::  av             !<
364    INTEGER(iwp) ::  bh             !<
365    INTEGER(iwp) ::  blx            !<
366    INTEGER(iwp) ::  bly            !<
367    INTEGER(iwp) ::  bxl            !<
368    INTEGER(iwp) ::  bxr            !<
369    INTEGER(iwp) ::  byn            !<
370    INTEGER(iwp) ::  bys            !<
371    INTEGER(iwp) ::  ch             !<
372    INTEGER(iwp) ::  count          !<
373    INTEGER(iwp) ::  cpl_parent_id  !<
374    INTEGER(iwp) ::  cwx            !<
375    INTEGER(iwp) ::  cwy            !<
376    INTEGER(iwp) ::  cxl            !<
377    INTEGER(iwp) ::  cxr            !<
378    INTEGER(iwp) ::  cyn            !<
379    INTEGER(iwp) ::  cys            !<
380    INTEGER(iwp) ::  dim            !<
381    INTEGER(iwp) ::  i              !<
382    INTEGER(iwp) ::  io             !<
383    INTEGER(iwp) ::  j              !<
384    INTEGER(iwp) ::  k              !<
385    INTEGER(iwp) ::  l              !<
386    INTEGER(iwp) ::  ll             !<
387    INTEGER(iwp) ::  mpi_type       !<
388    INTEGER(iwp) ::  my_cpl_id      !<
389    INTEGER(iwp) ::  n              !<
390    INTEGER(iwp) ::  ncpl           !<
391    INTEGER(iwp) ::  npe_total      !<
392   
393
394    REAL(wp) ::  cpuseconds_per_simulated_second  !<
395    REAL(wp) ::  lower_left_coord_x               !< x-coordinate of nest domain
396    REAL(wp) ::  lower_left_coord_y               !< y-coordinate of nest domain
397
398!
399!-- Open the output file. At the end of the simulation, output is directed
400!-- to unit 19.
401    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
402         .NOT. simulated_time_at_begin /= simulated_time )  THEN
403       io = 15   !  header output on file RUN_CONTROL
404    ELSE
405       io = 19   !  header output on file HEADER
406    ENDIF
407    CALL check_open( io )
408
409!
410!-- At the end of the run, output file (HEADER) will be rewritten with
411!-- new information
412    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
413
414!
415!-- Determine kind of model run
416    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
417       run_classification = 'restart run'
418    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
419       run_classification = 'run with cyclic fill of 3D - prerun data'
420    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
421       run_classification = 'run without 1D - prerun'
422    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
423       run_classification = 'run with 1D - prerun'
424    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
425       run_classification = 'run initialized by user'
426    ELSE
427       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
428       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
429    ENDIF
430    IF ( nested_run )  run_classification = 'nested ' // run_classification
431    IF ( ocean )  THEN
432       run_classification = 'ocean - ' // run_classification
433    ELSE
434       run_classification = 'atmosphere - ' // run_classification
435    ENDIF
436
437!
438!-- Run-identification, date, time, host
439    host_chr = host(1:10)
440    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
441    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
442    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
443#if defined( __mpi2 )
444       mpi_type = 2
445#else
446       mpi_type = 1
447#endif
448       WRITE ( io, 101 )  mpi_type, coupling_mode
449    ENDIF
450#if defined( __parallel )
451    IF ( coupling_start_time /= 0.0_wp )  THEN
452       IF ( coupling_start_time > simulated_time_at_begin )  THEN
453          WRITE ( io, 109 )
454       ELSE
455          WRITE ( io, 114 )
456       ENDIF
457    ENDIF
458#endif
459    IF ( ensemble_member_nr /= 0 )  THEN
460       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
461                       ADJUSTR( host_chr ), ensemble_member_nr
462    ELSE
463       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
464                       ADJUSTR( host_chr )
465    ENDIF
466#if defined( __parallel )
467    IF ( npex == -1  .AND.  npey == -1 )  THEN
468       char1 = 'calculated'
469    ELSE
470       char1 = 'predefined'
471    ENDIF
472    IF ( threads_per_task == 1 )  THEN
473       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
474    ELSE
475       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
476                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
477    ENDIF
478    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
479    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
480           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
481         npex == -1  .AND.  pdims(2) == 1 )                      &
482    THEN
483       WRITE ( io, 106 )
484    ELSEIF ( pdims(2) == 1 )  THEN
485       WRITE ( io, 107 )  'x'
486    ELSEIF ( pdims(1) == 1 )  THEN
487       WRITE ( io, 107 )  'y'
488    ENDIF
489    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
490    IF ( numprocs /= maximum_parallel_io_streams )  THEN
491       WRITE ( io, 108 )  maximum_parallel_io_streams
492    ENDIF
493#else
494    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
495#endif
496
497!
498!-- Nesting informations
499    IF ( nested_run )  THEN
500
501       WRITE ( io, 600 )  TRIM( nesting_mode ),                                &
502                          TRIM( nesting_datatransfer_mode )
503       CALL pmc_get_model_info( ncpl = ncpl, cpl_id = my_cpl_id )
504
505       DO  n = 1, ncpl
506          CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,&
507                                   cpl_parent_id = cpl_parent_id,              &
508                                   lower_left_x = lower_left_coord_x,          &
509                                   lower_left_y = lower_left_coord_y,          &
510                                   npe_total = npe_total )
511          IF ( n == my_cpl_id )  THEN
512             char1 = '*'
513          ELSE
514             char1 = ' '
515          ENDIF
516          WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total,       &
517                             lower_left_coord_x, lower_left_coord_y,           &
518                             TRIM( cpl_name )
519       ENDDO
520    ENDIF
521    WRITE ( io, 99 )
522
523!
524!-- Numerical schemes
525    WRITE ( io, 110 )
526    IF ( psolver(1:7) == 'poisfft' )  THEN
527       WRITE ( io, 111 )  TRIM( fft_method )
528       IF ( transpose_compute_overlap )  WRITE( io, 115 )
529    ELSEIF ( psolver == 'sor' )  THEN
530       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
531    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
532       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
533       IF ( mg_cycles == -1 )  THEN
534          WRITE ( io, 140 )  residual_limit
535       ELSE
536          WRITE ( io, 141 )  mg_cycles
537       ENDIF
538       IF ( mg_switch_to_pe0_level == 0 )  THEN
539          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
540                             nzt_mg(1)
541       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
542          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
543                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
544                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
545                             nzt_mg(mg_switch_to_pe0_level),    &
546                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
547                             nzt_mg(1)
548       ENDIF
549       IF ( masking_method )  WRITE ( io, 144 )
550    ENDIF
551    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
552    THEN
553       WRITE ( io, 142 )
554    ENDIF
555
556    IF ( momentum_advec == 'pw-scheme' )  THEN
557       WRITE ( io, 113 )
558    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
559       WRITE ( io, 503 )
560    ENDIF
561    IF ( scalar_advec == 'pw-scheme' )  THEN
562       WRITE ( io, 116 )
563    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
564       WRITE ( io, 504 )
565    ELSEIF ( scalar_advec == 'ws-scheme-mono' )  THEN
566       WRITE ( io, 513 )
567    ELSE
568       WRITE ( io, 118 )
569    ENDIF
570
571    WRITE ( io, 139 )  TRIM( loop_optimization )
572
573    IF ( galilei_transformation )  THEN
574       IF ( use_ug_for_galilei_tr )  THEN
575          char1 = '0.6 * geostrophic wind'
576       ELSE
577          char1 = 'mean wind in model domain'
578       ENDIF
579       IF ( simulated_time_at_begin == simulated_time )  THEN
580          char2 = 'at the start of the run'
581       ELSE
582          char2 = 'at the end of the run'
583       ENDIF
584       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
585                          advected_distance_x/1000.0_wp,                       &
586                          advected_distance_y/1000.0_wp
587    ENDIF
588    WRITE ( io, 122 )  timestep_scheme
589    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
590    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
591       IF ( .NOT. ocean )  THEN
592          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
593               rayleigh_damping_factor
594       ELSE
595          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
596               rayleigh_damping_factor
597       ENDIF
598    ENDIF
599    IF ( neutral )  WRITE ( io, 131 )  pt_surface
600    IF ( humidity )  THEN
601       IF ( .NOT. cloud_physics )  THEN
602          WRITE ( io, 129 )
603       ELSE
604          WRITE ( io, 130 )
605       ENDIF
606    ENDIF
607    IF ( passive_scalar )  WRITE ( io, 134 )
608    IF ( conserve_volume_flow )  THEN
609       WRITE ( io, 150 )  conserve_volume_flow_mode
610       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
611          WRITE ( io, 151 )  u_bulk, v_bulk
612       ENDIF
613    ELSEIF ( dp_external )  THEN
614       IF ( dp_smooth )  THEN
615          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
616       ELSE
617          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
618       ENDIF
619    ENDIF
620    WRITE ( io, 99 )
621
622!
623!-- Runtime and timestep information
624    WRITE ( io, 200 )
625    IF ( .NOT. dt_fixed )  THEN
626       WRITE ( io, 201 )  dt_max, cfl_factor
627    ELSE
628       WRITE ( io, 202 )  dt
629    ENDIF
630    WRITE ( io, 203 )  simulated_time_at_begin, end_time
631
632    IF ( time_restart /= 9999999.9_wp  .AND. &
633         simulated_time_at_begin == simulated_time )  THEN
634       IF ( dt_restart == 9999999.9_wp )  THEN
635          WRITE ( io, 204 )  ' Restart at:       ',time_restart
636       ELSE
637          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
638       ENDIF
639    ENDIF
640
641    IF ( simulated_time_at_begin /= simulated_time )  THEN
642       i = MAX ( log_point_s(10)%counts, 1 )
643       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
644          cpuseconds_per_simulated_second = 0.0_wp
645       ELSE
646          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
647                                            ( simulated_time -    &
648                                              simulated_time_at_begin )
649       ENDIF
650       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
651                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
652                          cpuseconds_per_simulated_second
653       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
654          IF ( dt_restart == 9999999.9_wp )  THEN
655             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
656          ELSE
657             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
658          ENDIF
659       ENDIF
660    ENDIF
661
662
663!
664!-- Start time for coupled runs, if independent precursor runs for atmosphere
665!-- and ocean are used or have been used. In this case, coupling_start_time
666!-- defines the time when the coupling is switched on.
667    IF ( coupling_start_time /= 0.0_wp )  THEN
668       WRITE ( io, 207 )  coupling_start_time
669    ENDIF
670
671!
672!-- Computational grid
673    IF ( .NOT. ocean )  THEN
674       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
675       IF ( dz_stretch_level_index < nzt+1 )  THEN
676          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
677                             dz_stretch_factor, dz_max
678       ENDIF
679    ELSE
680       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
681       IF ( dz_stretch_level_index > 0 )  THEN
682          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
683                             dz_stretch_factor, dz_max
684       ENDIF
685    ENDIF
686    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
687                       MIN( nnz+2, nzt+2 )
688    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
689
690!
691!-- Large scale forcing and nudging
692    WRITE ( io, 160 )
693    IF ( large_scale_forcing )  THEN
694       WRITE ( io, 162 )
695       WRITE ( io, 163 )
696
697       IF ( large_scale_subsidence )  THEN
698          IF ( .NOT. use_subsidence_tendencies )  THEN
699             WRITE ( io, 164 )
700          ELSE
701             WRITE ( io, 165 )
702          ENDIF
703       ENDIF
704
705       IF ( bc_pt_b == 'dirichlet' )  THEN
706          WRITE ( io, 180 )
707       ELSEIF ( bc_pt_b == 'neumann' )  THEN
708          WRITE ( io, 181 )
709       ENDIF
710
711       IF ( bc_q_b == 'dirichlet' )  THEN
712          WRITE ( io, 182 )
713       ELSEIF ( bc_q_b == 'neumann' )  THEN
714          WRITE ( io, 183 )
715       ENDIF
716
717       WRITE ( io, 167 )
718       IF ( nudging )  THEN
719          WRITE ( io, 170 )
720       ENDIF
721    ELSE
722       WRITE ( io, 161 )
723       WRITE ( io, 171 )
724    ENDIF
725    IF ( large_scale_subsidence )  THEN
726       WRITE ( io, 168 )
727       WRITE ( io, 169 )
728    ENDIF
729
730!
731!-- Profile for the large scale vertial velocity
732!-- Building output strings, starting with surface value
733    IF ( large_scale_subsidence )  THEN
734       temperatures = '   0.0'
735       gradients = '------'
736       slices = '     0'
737       coordinates = '   0.0'
738       i = 1
739       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
740
741          WRITE (coor_chr,'(E10.2,7X)')  &
742                                w_subs(subs_vertical_gradient_level_i(i))
743          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
744
745          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
746          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
747
748          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
749          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
750
751          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
752          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
753
754          IF ( i == 10 )  THEN
755             EXIT
756          ELSE
757             i = i + 1
758          ENDIF
759
760       ENDDO
761
762 
763       IF ( .NOT. large_scale_forcing )  THEN
764          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
765                             TRIM( gradients ), TRIM( slices )
766       ENDIF
767
768
769    ENDIF
770
771!-- Profile of the geostrophic wind (component ug)
772!-- Building output strings
773    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
774    gradients = '------'
775    slices = '     0'
776    coordinates = '   0.0'
777    i = 1
778    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
779     
780       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
781       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
782
783       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
784       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
785
786       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
787       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
788
789       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
790       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
791
792       IF ( i == 10 )  THEN
793          EXIT
794       ELSE
795          i = i + 1
796       ENDIF
797
798    ENDDO
799
800    IF ( .NOT. large_scale_forcing )  THEN
801       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
802                          TRIM( gradients ), TRIM( slices )
803    ENDIF
804
805!-- Profile of the geostrophic wind (component vg)
806!-- Building output strings
807    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
808    gradients = '------'
809    slices = '     0'
810    coordinates = '   0.0'
811    i = 1
812    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
813
814       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
815       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
816
817       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
818       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
819
820       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
821       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
822
823       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
824       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
825
826       IF ( i == 10 )  THEN
827          EXIT
828       ELSE
829          i = i + 1
830       ENDIF
831 
832    ENDDO
833
834    IF ( .NOT. large_scale_forcing )  THEN
835       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
836                          TRIM( gradients ), TRIM( slices )
837    ENDIF
838
839!
840!-- Topography
841    WRITE ( io, 270 )  topography
842    SELECT CASE ( TRIM( topography ) )
843
844       CASE ( 'flat' )
845          ! no actions necessary
846
847       CASE ( 'single_building' )
848          blx = INT( building_length_x / dx )
849          bly = INT( building_length_y / dy )
850          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
851          IF ( ABS( zw(bh  ) - building_height ) == &
852               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
853
854          IF ( building_wall_left == 9999999.9_wp )  THEN
855             building_wall_left = ( nx + 1 - blx ) / 2 * dx
856          ENDIF
857          bxl = INT ( building_wall_left / dx + 0.5_wp )
858          bxr = bxl + blx
859
860          IF ( building_wall_south == 9999999.9_wp )  THEN
861             building_wall_south = ( ny + 1 - bly ) / 2 * dy
862          ENDIF
863          bys = INT ( building_wall_south / dy + 0.5_wp )
864          byn = bys + bly
865
866          WRITE ( io, 271 )  building_length_x, building_length_y, &
867                             building_height, bxl, bxr, bys, byn
868
869       CASE ( 'single_street_canyon' )
870          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
871          IF ( ABS( zw(ch  ) - canyon_height ) == &
872               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
873          IF ( canyon_width_x /= 9999999.9_wp )  THEN
874!
875!--          Street canyon in y direction
876             cwx = NINT( canyon_width_x / dx )
877             IF ( canyon_wall_left == 9999999.9_wp )  THEN
878                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
879             ENDIF
880             cxl = NINT( canyon_wall_left / dx )
881             cxr = cxl + cwx
882             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
883
884          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
885!
886!--          Street canyon in x direction
887             cwy = NINT( canyon_width_y / dy )
888             IF ( canyon_wall_south == 9999999.9_wp )  THEN
889                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
890             ENDIF
891             cys = NINT( canyon_wall_south / dy )
892             cyn = cys + cwy
893             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
894          ENDIF
895
896    END SELECT
897
898    IF ( TRIM( topography ) /= 'flat' )  THEN
899       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
900          IF ( TRIM( topography ) == 'single_building' .OR.  &
901               TRIM( topography ) == 'single_street_canyon' )  THEN
902             WRITE ( io, 278 )
903          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
904             WRITE ( io, 279 )
905          ENDIF
906       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
907          WRITE ( io, 278 )
908       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
909          WRITE ( io, 279 )
910       ENDIF
911    ENDIF
912
913    IF ( plant_canopy )  CALL pcm_header ( io )
914
915    IF ( land_surface )  CALL lsm_header ( io )
916
917    IF ( radiation )  CALL radiation_header ( io )
918
919!
920!-- Boundary conditions
921    IF ( ibc_p_b == 0 )  THEN
922       r_lower = 'p(0)     = 0      |'
923    ELSEIF ( ibc_p_b == 1 )  THEN
924       r_lower = 'p(0)     = p(1)   |'
925    ENDIF
926    IF ( ibc_p_t == 0 )  THEN
927       r_upper  = 'p(nzt+1) = 0      |'
928    ELSE
929       r_upper  = 'p(nzt+1) = p(nzt) |'
930    ENDIF
931
932    IF ( ibc_uv_b == 0 )  THEN
933       r_lower = TRIM( r_lower ) // ' uv(0)     = -uv(1)                |'
934    ELSE
935       r_lower = TRIM( r_lower ) // ' uv(0)     = uv(1)                 |'
936    ENDIF
937    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
938       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = 0                     |'
939    ELSEIF ( ibc_uv_t == 0 )  THEN
940       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
941    ELSE
942       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = uv(nzt)               |'
943    ENDIF
944
945    IF ( ibc_pt_b == 0 )  THEN
946       IF ( land_surface )  THEN
947          r_lower = TRIM( r_lower ) // ' pt(0)     = from soil model'
948       ELSE
949          r_lower = TRIM( r_lower ) // ' pt(0)     = pt_surface'
950       ENDIF
951    ELSEIF ( ibc_pt_b == 1 )  THEN
952       r_lower = TRIM( r_lower ) // ' pt(0)     = pt(1)'
953    ELSEIF ( ibc_pt_b == 2 )  THEN
954       r_lower = TRIM( r_lower ) // ' pt(0)     = from coupled model'
955    ENDIF
956    IF ( ibc_pt_t == 0 )  THEN
957       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt_top'
958    ELSEIF( ibc_pt_t == 1 )  THEN
959       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt)'
960    ELSEIF( ibc_pt_t == 2 )  THEN
961       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
962
963    ENDIF
964
965    WRITE ( io, 300 )  r_lower, r_upper
966
967    IF ( .NOT. constant_diffusion )  THEN
968       IF ( ibc_e_b == 1 )  THEN
969          r_lower = 'e(0)     = e(1)'
970       ELSE
971          r_lower = 'e(0)     = e(1) = (u*/0.1)**2'
972       ENDIF
973       r_upper = 'e(nzt+1) = e(nzt) = e(nzt-1)'
974
975       WRITE ( io, 301 )  'e', r_lower, r_upper       
976
977    ENDIF
978
979    IF ( ocean )  THEN
980       r_lower = 'sa(0)    = sa(1)'
981       IF ( ibc_sa_t == 0 )  THEN
982          r_upper =  'sa(nzt+1) = sa_surface'
983       ELSE
984          r_upper =  'sa(nzt+1) = sa(nzt)'
985       ENDIF
986       WRITE ( io, 301 ) 'sa', r_lower, r_upper
987    ENDIF
988
989    IF ( humidity )  THEN
990       IF ( ibc_q_b == 0 )  THEN
991          IF ( land_surface )  THEN
992             r_lower = 'q(0)     = from soil model'
993          ELSE
994             r_lower = 'q(0)     = q_surface'
995          ENDIF
996
997       ELSE
998          r_lower = 'q(0)     = q(1)'
999       ENDIF
1000       IF ( ibc_q_t == 0 )  THEN
1001          r_upper =  'q(nzt)   = q_top'
1002       ELSE
1003          r_upper =  'q(nzt)   = q(nzt-1) + dq/dz'
1004       ENDIF
1005       WRITE ( io, 301 ) 'q', r_lower, r_upper
1006    ENDIF
1007
1008    IF ( passive_scalar )  THEN
1009       IF ( ibc_q_b == 0 )  THEN
1010          r_lower = 's(0)     = s_surface'
1011       ELSE
1012          r_lower = 's(0)     = s(1)'
1013       ENDIF
1014       IF ( ibc_q_t == 0 )  THEN
1015          r_upper =  's(nzt)   = s_top'
1016       ELSE
1017          r_upper =  's(nzt)   = s(nzt-1) + ds/dz'
1018       ENDIF
1019       WRITE ( io, 301 ) 's', r_lower, r_upper
1020    ENDIF
1021
1022    IF ( use_surface_fluxes )  THEN
1023       WRITE ( io, 303 )
1024       IF ( constant_heatflux )  THEN
1025          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1026             WRITE ( io, 306 )  shf(0,0)
1027          ELSE
1028             WRITE ( io, 306 )  surface_heatflux
1029          ENDIF
1030          IF ( random_heatflux )  WRITE ( io, 307 )
1031       ENDIF
1032       IF ( humidity  .AND.  constant_waterflux )  THEN
1033          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1034             WRITE ( io, 311 ) qsws(0,0)
1035          ELSE
1036             WRITE ( io, 311 ) surface_waterflux
1037          ENDIF
1038       ENDIF
1039       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1040          WRITE ( io, 313 ) surface_waterflux
1041       ENDIF
1042    ENDIF
1043
1044    IF ( use_top_fluxes )  THEN
1045       WRITE ( io, 304 )
1046       IF ( coupling_mode == 'uncoupled' )  THEN
1047          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
1048          IF ( constant_top_heatflux )  THEN
1049             WRITE ( io, 306 )  top_heatflux
1050          ENDIF
1051       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1052          WRITE ( io, 316 )
1053       ENDIF
1054       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1055          WRITE ( io, 309 )  top_salinityflux
1056       ENDIF
1057       IF ( humidity  .OR.  passive_scalar )  THEN
1058          WRITE ( io, 315 )
1059       ENDIF
1060    ENDIF
1061
1062    IF ( constant_flux_layer )  THEN
1063       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
1064                          z0h_factor*roughness_length, kappa,                  &
1065                          zeta_min, zeta_max
1066       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
1067       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
1068          WRITE ( io, 312 )
1069       ENDIF
1070       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1071          WRITE ( io, 314 )
1072       ENDIF
1073    ELSE
1074       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
1075          WRITE ( io, 310 )  zeta_min, zeta_max
1076       ENDIF
1077    ENDIF
1078
1079    WRITE ( io, 317 )  bc_lr, bc_ns
1080    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1081       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
1082       IF ( turbulent_inflow )  THEN
1083          IF ( .NOT. recycling_yshift ) THEN
1084             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1085                                inflow_damping_height, inflow_damping_width
1086          ELSE
1087             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1088                                inflow_damping_height, inflow_damping_width
1089          END IF
1090       ENDIF
1091    ENDIF
1092
1093!
1094!-- Initial Profiles
1095    WRITE ( io, 321 )
1096!
1097!-- Initial wind profiles
1098    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1099
1100!
1101!-- Initial temperature profile
1102!-- Building output strings, starting with surface temperature
1103    WRITE ( temperatures, '(F6.2)' )  pt_surface
1104    gradients = '------'
1105    slices = '     0'
1106    coordinates = '   0.0'
1107    i = 1
1108    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1109
1110       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1111       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1112
1113       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1114       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1115
1116       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1117       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1118
1119       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1120       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1121
1122       IF ( i == 10 )  THEN
1123          EXIT
1124       ELSE
1125          i = i + 1
1126       ENDIF
1127
1128    ENDDO
1129
1130    IF ( .NOT. nudging )  THEN
1131       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1132                          TRIM( gradients ), TRIM( slices )
1133    ELSE
1134       WRITE ( io, 428 ) 
1135    ENDIF
1136
1137!
1138!-- Initial humidity profile
1139!-- Building output strings, starting with surface humidity
1140    IF ( humidity  .OR.  passive_scalar )  THEN
1141       WRITE ( temperatures, '(E8.1)' )  q_surface
1142       gradients = '--------'
1143       slices = '       0'
1144       coordinates = '     0.0'
1145       i = 1
1146       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1147         
1148          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1149          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1150
1151          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1152          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1153         
1154          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1155          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1156         
1157          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1158          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1159
1160          IF ( i == 10 )  THEN
1161             EXIT
1162          ELSE
1163             i = i + 1
1164          ENDIF
1165
1166       ENDDO
1167
1168       IF ( humidity )  THEN
1169          IF ( .NOT. nudging )  THEN
1170             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1171                                TRIM( gradients ), TRIM( slices )
1172          ENDIF
1173       ELSE
1174          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1175                             TRIM( gradients ), TRIM( slices )
1176       ENDIF
1177    ENDIF
1178
1179!
1180!-- Initial salinity profile
1181!-- Building output strings, starting with surface salinity
1182    IF ( ocean )  THEN
1183       WRITE ( temperatures, '(F6.2)' )  sa_surface
1184       gradients = '------'
1185       slices = '     0'
1186       coordinates = '   0.0'
1187       i = 1
1188       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1189
1190          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1191          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1192
1193          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1194          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1195
1196          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1197          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1198
1199          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1200          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1201
1202          IF ( i == 10 )  THEN
1203             EXIT
1204          ELSE
1205             i = i + 1
1206          ENDIF
1207
1208       ENDDO
1209
1210       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1211                          TRIM( gradients ), TRIM( slices )
1212    ENDIF
1213
1214
1215!
1216!-- Listing of 1D-profiles
1217    WRITE ( io, 325 )  dt_dopr_listing
1218    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1219       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1220    ENDIF
1221
1222!
1223!-- DATA output
1224    WRITE ( io, 330 )
1225    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1226       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1227    ENDIF
1228
1229!
1230!-- 1D-profiles
1231    dopr_chr = 'Profile:'
1232    IF ( dopr_n /= 0 )  THEN
1233       WRITE ( io, 331 )
1234
1235       output_format = ''
1236       output_format = netcdf_data_format_string
1237       IF ( netcdf_deflate == 0 )  THEN
1238          WRITE ( io, 344 )  output_format
1239       ELSE
1240          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1241       ENDIF
1242
1243       DO  i = 1, dopr_n
1244          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1245          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1246             WRITE ( io, 332 )  dopr_chr
1247             dopr_chr = '       :'
1248          ENDIF
1249       ENDDO
1250
1251       IF ( dopr_chr /= '' )  THEN
1252          WRITE ( io, 332 )  dopr_chr
1253       ENDIF
1254       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1255       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1256    ENDIF
1257
1258!
1259!-- 2D-arrays
1260    DO  av = 0, 1
1261
1262       i = 1
1263       do2d_xy = ''
1264       do2d_xz = ''
1265       do2d_yz = ''
1266       DO  WHILE ( do2d(av,i) /= ' ' )
1267
1268          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1269          do2d_mode = do2d(av,i)(l-1:l)
1270
1271          SELECT CASE ( do2d_mode )
1272             CASE ( 'xy' )
1273                ll = LEN_TRIM( do2d_xy )
1274                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1275             CASE ( 'xz' )
1276                ll = LEN_TRIM( do2d_xz )
1277                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1278             CASE ( 'yz' )
1279                ll = LEN_TRIM( do2d_yz )
1280                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1281          END SELECT
1282
1283          i = i + 1
1284
1285       ENDDO
1286
1287       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1288              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1289              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1290
1291          IF (  av == 0 )  THEN
1292             WRITE ( io, 334 )  ''
1293          ELSE
1294             WRITE ( io, 334 )  '(time-averaged)'
1295          ENDIF
1296
1297          IF ( do2d_at_begin )  THEN
1298             begin_chr = 'and at the start'
1299          ELSE
1300             begin_chr = ''
1301          ENDIF
1302
1303          output_format = ''
1304          output_format = netcdf_data_format_string
1305          IF ( netcdf_deflate == 0 )  THEN
1306             WRITE ( io, 344 )  output_format
1307          ELSE
1308             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1309          ENDIF
1310
1311          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1312             i = 1
1313             slices = '/'
1314             coordinates = '/'
1315!
1316!--          Building strings with index and coordinate information of the
1317!--          slices
1318             DO  WHILE ( section(i,1) /= -9999 )
1319
1320                WRITE (section_chr,'(I5)')  section(i,1)
1321                section_chr = ADJUSTL( section_chr )
1322                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1323
1324                IF ( section(i,1) == -1 )  THEN
1325                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1326                ELSE
1327                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1328                ENDIF
1329                coor_chr = ADJUSTL( coor_chr )
1330                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1331
1332                i = i + 1
1333             ENDDO
1334             IF ( av == 0 )  THEN
1335                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1336                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1337                                   TRIM( coordinates )
1338                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1339                   WRITE ( io, 339 )  skip_time_do2d_xy
1340                ENDIF
1341             ELSE
1342                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1343                                   TRIM( begin_chr ), averaging_interval, &
1344                                   dt_averaging_input, 'k', TRIM( slices ), &
1345                                   TRIM( coordinates )
1346                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1347                   WRITE ( io, 339 )  skip_time_data_output_av
1348                ENDIF
1349             ENDIF
1350             IF ( netcdf_data_format > 4 )  THEN
1351                WRITE ( io, 352 )  ntdim_2d_xy(av)
1352             ELSE
1353                WRITE ( io, 353 )
1354             ENDIF
1355          ENDIF
1356
1357          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1358             i = 1
1359             slices = '/'
1360             coordinates = '/'
1361!
1362!--          Building strings with index and coordinate information of the
1363!--          slices
1364             DO  WHILE ( section(i,2) /= -9999 )
1365
1366                WRITE (section_chr,'(I5)')  section(i,2)
1367                section_chr = ADJUSTL( section_chr )
1368                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1369
1370                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1371                coor_chr = ADJUSTL( coor_chr )
1372                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1373
1374                i = i + 1
1375             ENDDO
1376             IF ( av == 0 )  THEN
1377                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1378                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1379                                   TRIM( coordinates )
1380                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1381                   WRITE ( io, 339 )  skip_time_do2d_xz
1382                ENDIF
1383             ELSE
1384                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1385                                   TRIM( begin_chr ), averaging_interval, &
1386                                   dt_averaging_input, 'j', TRIM( slices ), &
1387                                   TRIM( coordinates )
1388                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1389                   WRITE ( io, 339 )  skip_time_data_output_av
1390                ENDIF
1391             ENDIF
1392             IF ( netcdf_data_format > 4 )  THEN
1393                WRITE ( io, 352 )  ntdim_2d_xz(av)
1394             ELSE
1395                WRITE ( io, 353 )
1396             ENDIF
1397          ENDIF
1398
1399          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1400             i = 1
1401             slices = '/'
1402             coordinates = '/'
1403!
1404!--          Building strings with index and coordinate information of the
1405!--          slices
1406             DO  WHILE ( section(i,3) /= -9999 )
1407
1408                WRITE (section_chr,'(I5)')  section(i,3)
1409                section_chr = ADJUSTL( section_chr )
1410                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1411
1412                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1413                coor_chr = ADJUSTL( coor_chr )
1414                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1415
1416                i = i + 1
1417             ENDDO
1418             IF ( av == 0 )  THEN
1419                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1420                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1421                                   TRIM( coordinates )
1422                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1423                   WRITE ( io, 339 )  skip_time_do2d_yz
1424                ENDIF
1425             ELSE
1426                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1427                                   TRIM( begin_chr ), averaging_interval, &
1428                                   dt_averaging_input, 'i', TRIM( slices ), &
1429                                   TRIM( coordinates )
1430                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1431                   WRITE ( io, 339 )  skip_time_data_output_av
1432                ENDIF
1433             ENDIF
1434             IF ( netcdf_data_format > 4 )  THEN
1435                WRITE ( io, 352 )  ntdim_2d_yz(av)
1436             ELSE
1437                WRITE ( io, 353 )
1438             ENDIF
1439          ENDIF
1440
1441       ENDIF
1442
1443    ENDDO
1444
1445!
1446!-- 3d-arrays
1447    DO  av = 0, 1
1448
1449       i = 1
1450       do3d_chr = ''
1451       DO  WHILE ( do3d(av,i) /= ' ' )
1452
1453          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1454          i = i + 1
1455
1456       ENDDO
1457
1458       IF ( do3d_chr /= '' )  THEN
1459          IF ( av == 0 )  THEN
1460             WRITE ( io, 336 )  ''
1461          ELSE
1462             WRITE ( io, 336 )  '(time-averaged)'
1463          ENDIF
1464
1465          output_format = netcdf_data_format_string
1466          IF ( netcdf_deflate == 0 )  THEN
1467             WRITE ( io, 344 )  output_format
1468          ELSE
1469             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1470          ENDIF
1471
1472          IF ( do3d_at_begin )  THEN
1473             begin_chr = 'and at the start'
1474          ELSE
1475             begin_chr = ''
1476          ENDIF
1477          IF ( av == 0 )  THEN
1478             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1479                                zu(nz_do3d), nz_do3d
1480          ELSE
1481             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1482                                TRIM( begin_chr ), averaging_interval, &
1483                                dt_averaging_input, zu(nz_do3d), nz_do3d
1484          ENDIF
1485
1486          IF ( netcdf_data_format > 4 )  THEN
1487             WRITE ( io, 352 )  ntdim_3d(av)
1488          ELSE
1489             WRITE ( io, 353 )
1490          ENDIF
1491
1492          IF ( av == 0 )  THEN
1493             IF ( skip_time_do3d /= 0.0_wp )  THEN
1494                WRITE ( io, 339 )  skip_time_do3d
1495             ENDIF
1496          ELSE
1497             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1498                WRITE ( io, 339 )  skip_time_data_output_av
1499             ENDIF
1500          ENDIF
1501
1502       ENDIF
1503
1504    ENDDO
1505
1506!
1507!-- masked arrays
1508    IF ( masks > 0 )  WRITE ( io, 345 )  &
1509         mask_scale_x, mask_scale_y, mask_scale_z
1510    DO  mid = 1, masks
1511       DO  av = 0, 1
1512
1513          i = 1
1514          domask_chr = ''
1515          DO  WHILE ( domask(mid,av,i) /= ' ' )
1516             domask_chr = TRIM( domask_chr ) // ' ' //  &
1517                          TRIM( domask(mid,av,i) ) // ','
1518             i = i + 1
1519          ENDDO
1520
1521          IF ( domask_chr /= '' )  THEN
1522             IF ( av == 0 )  THEN
1523                WRITE ( io, 346 )  '', mid
1524             ELSE
1525                WRITE ( io, 346 )  ' (time-averaged)', mid
1526             ENDIF
1527
1528             output_format = netcdf_data_format_string
1529!--          Parallel output not implemented for mask data, hence
1530!--          output_format must be adjusted.
1531             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1532             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1533             IF ( netcdf_deflate == 0 )  THEN
1534                WRITE ( io, 344 )  output_format
1535             ELSE
1536                WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1537             ENDIF
1538
1539             IF ( av == 0 )  THEN
1540                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1541             ELSE
1542                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1543                                   averaging_interval, dt_averaging_input
1544             ENDIF
1545
1546             IF ( av == 0 )  THEN
1547                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1548                   WRITE ( io, 339 )  skip_time_domask(mid)
1549                ENDIF
1550             ELSE
1551                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1552                   WRITE ( io, 339 )  skip_time_data_output_av
1553                ENDIF
1554             ENDIF
1555!
1556!--          output locations
1557             DO  dim = 1, 3
1558                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1559                   count = 0
1560                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1561                      count = count + 1
1562                   ENDDO
1563                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1564                                      mask(mid,dim,:count)
1565                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1566                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1567                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1568                   WRITE ( io, 350 )  dir(dim), dir(dim)
1569                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1570                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1571                                      mask_loop(mid,dim,1:2)
1572                ELSE
1573                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1574                                      mask_loop(mid,dim,1:3)
1575                ENDIF
1576             ENDDO
1577          ENDIF
1578
1579       ENDDO
1580    ENDDO
1581
1582!
1583!-- Timeseries
1584    IF ( dt_dots /= 9999999.9_wp )  THEN
1585       WRITE ( io, 340 )
1586
1587       output_format = netcdf_data_format_string
1588       IF ( netcdf_deflate == 0 )  THEN
1589          WRITE ( io, 344 )  output_format
1590       ELSE
1591          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1592       ENDIF
1593       WRITE ( io, 341 )  dt_dots
1594    ENDIF
1595
1596#if defined( __dvrp_graphics )
1597!
1598!-- Dvrp-output
1599    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1600       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1601                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1602       i = 1
1603       l = 0
1604       m = 0
1605       DO WHILE ( mode_dvrp(i) /= ' ' )
1606          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1607             READ ( mode_dvrp(i), '(10X,I2)' )  j
1608             l = l + 1
1609             IF ( do3d(0,j) /= ' ' )  THEN
1610                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1611                                   isosurface_color(:,l)
1612             ENDIF
1613          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1614             READ ( mode_dvrp(i), '(6X,I2)' )  j
1615             m = m + 1
1616             IF ( do2d(0,j) /= ' ' )  THEN
1617                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1618                                   slicer_range_limits_dvrp(:,m)
1619             ENDIF
1620          ENDIF
1621          i = i + 1
1622       ENDDO
1623
1624       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1625                          superelevation_y, superelevation, clip_dvrp_l, &
1626                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1627
1628       IF ( TRIM( topography ) /= 'flat' )  THEN
1629          WRITE ( io, 366 )  topography_color
1630          IF ( cluster_size > 1 )  THEN
1631             WRITE ( io, 367 )  cluster_size
1632          ENDIF
1633       ENDIF
1634
1635    ENDIF
1636#endif
1637
1638!
1639!-- Output of spectra related quantities
1640    IF ( calculate_spectra )  CALL spectra_header( io )
1641
1642    WRITE ( io, 99 )
1643
1644!
1645!-- Physical quantities
1646    WRITE ( io, 400 )
1647
1648!
1649!-- Geostrophic parameters
1650    WRITE ( io, 410 )  phi, omega, f, fs
1651
1652!
1653!-- Other quantities
1654    WRITE ( io, 411 )  g
1655
1656    WRITE ( io, 412 )  TRIM( reference_state )
1657    IF ( use_single_reference_value )  THEN
1658       IF ( ocean )  THEN
1659          WRITE ( io, 413 )  prho_reference
1660       ELSE
1661          WRITE ( io, 414 )  pt_reference
1662       ENDIF
1663    ENDIF
1664
1665!
1666!-- Cloud physics parameters
1667    IF ( cloud_physics )  THEN
1668       WRITE ( io, 415 )
1669       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1670       IF ( microphysics_seifert )  THEN
1671          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1672          WRITE ( io, 511 ) c_sedimentation
1673       ENDIF
1674    ENDIF
1675
1676!
1677!-- Cloud physcis parameters / quantities / numerical methods
1678    WRITE ( io, 430 )
1679    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1680       WRITE ( io, 431 )
1681    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1682       WRITE ( io, 432 )
1683       IF ( cloud_top_radiation )  WRITE ( io, 132 )
1684       IF ( microphysics_kessler )  THEN
1685          WRITE ( io, 133 )
1686       ELSEIF ( microphysics_seifert )  THEN
1687          IF ( cloud_water_sedimentation )  WRITE ( io, 506 )
1688          WRITE ( io, 505 )
1689          IF ( collision_turbulence )  WRITE ( io, 507 )
1690          IF ( ventilation_effect )  WRITE ( io, 508 )
1691          IF ( limiter_sedimentation )  WRITE ( io, 509 )
1692       ENDIF
1693    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1694       WRITE ( io, 433 )
1695       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1696       IF ( collision_kernel /= 'none' )  THEN
1697          WRITE ( io, 435 )  TRIM( collision_kernel )
1698          IF ( collision_kernel(6:9) == 'fast' )  THEN
1699             WRITE ( io, 436 )  radius_classes, dissipation_classes
1700          ENDIF
1701       ELSE
1702          WRITE ( io, 437 )
1703       ENDIF
1704    ENDIF
1705
1706!
1707!-- LES / turbulence parameters
1708    WRITE ( io, 450 )
1709
1710!--
1711! ... LES-constants used must still be added here
1712!--
1713    IF ( constant_diffusion )  THEN
1714       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1715                          prandtl_number
1716    ENDIF
1717    IF ( .NOT. constant_diffusion)  THEN
1718       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1719       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1720       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1721    ENDIF
1722
1723!
1724!-- Special actions during the run
1725    WRITE ( io, 470 )
1726    IF ( create_disturbances )  THEN
1727       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1728                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1729                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1730       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1731          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1732       ELSE
1733          WRITE ( io, 473 )  disturbance_energy_limit
1734       ENDIF
1735       WRITE ( io, 474 )  TRIM( random_generator )
1736    ENDIF
1737    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1738       WRITE ( io, 475 )  pt_surface_initial_change
1739    ENDIF
1740    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1741       WRITE ( io, 476 )  q_surface_initial_change       
1742    ENDIF
1743    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1744       WRITE ( io, 477 )  q_surface_initial_change       
1745    ENDIF
1746
1747    IF ( particle_advection )  THEN
1748!
1749!--    Particle attributes
1750       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1751                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1752                          end_time_prel
1753       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1754       IF ( random_start_position )  WRITE ( io, 481 )
1755       IF ( seed_follows_topography )  WRITE ( io, 496 )
1756       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1757       WRITE ( io, 495 )  total_number_of_particles
1758       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1759          WRITE ( io, 485 )  dt_write_particle_data
1760          IF ( netcdf_data_format > 1 )  THEN
1761             output_format = 'netcdf (64 bit offset) and binary'
1762          ELSE
1763             output_format = 'netcdf and binary'
1764          ENDIF
1765          IF ( netcdf_deflate == 0 )  THEN
1766             WRITE ( io, 344 )  output_format
1767          ELSE
1768             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1769          ENDIF
1770       ENDIF
1771       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1772       IF ( write_particle_statistics )  WRITE ( io, 486 )
1773
1774       WRITE ( io, 487 )  number_of_particle_groups
1775
1776       DO  i = 1, number_of_particle_groups
1777          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1778             WRITE ( io, 490 )  i, 0.0_wp
1779             WRITE ( io, 492 )
1780          ELSE
1781             WRITE ( io, 490 )  i, radius(i)
1782             IF ( density_ratio(i) /= 0.0_wp )  THEN
1783                WRITE ( io, 491 )  density_ratio(i)
1784             ELSE
1785                WRITE ( io, 492 )
1786             ENDIF
1787          ENDIF
1788          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1789                             pdx(i), pdy(i), pdz(i)
1790          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1791       ENDDO
1792
1793    ENDIF
1794
1795
1796!
1797!-- Parameters of 1D-model
1798    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1799       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1800                          mixing_length_1d, dissipation_1d
1801       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1802          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1803       ENDIF
1804    ENDIF
1805
1806!
1807!-- User-defined information
1808    CALL user_header( io )
1809
1810    WRITE ( io, 99 )
1811
1812!
1813!-- Write buffer contents to disc immediately
1814    FLUSH( io )
1815
1816!
1817!-- Here the FORMATs start
1818
1819 99 FORMAT (1X,78('-'))
1820100 FORMAT (/1X,'******************************',4X,44('-')/        &
1821            1X,'* ',A,' *',4X,A/                               &
1822            1X,'******************************',4X,44('-'))
1823101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1824            35X,42('-'))
1825102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1826            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1827            ' Run on host:        ',A10)
1828#if defined( __parallel )
1829103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1830              ')',1X,A)
1831104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1832              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1833105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1834106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1835            35X,'because the job is running on an SMP-cluster')
1836107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1837108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1838109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1839            35X,42('-'))
1840114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1841            35X,'independent precursor runs'/             &
1842            35X,42('-'))
1843117 FORMAT (' Accelerator boards / node:  ',I2)
1844#endif
1845110 FORMAT (/' Numerical Schemes:'/ &
1846             ' -----------------'/)
1847111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1848112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1849            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
1850113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1851                  ' or Upstream')
1852115 FORMAT ('     FFT and transpositions are overlapping')
1853116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1854                  ' or Upstream')
1855118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1856119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1857            '     translation velocity = ',A/ &
1858            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1859120 FORMAT (' Accelerator boards: ',8X,I2)
1860122 FORMAT (' --> Time differencing scheme: ',A)
1861123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1862            '     maximum damping coefficient:',F6.3, ' 1/s')
1863129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1864130 FORMAT (' --> Additional prognostic equation for the total water content')
1865131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1866                  F6.2, ' K assumed')
1867132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1868            '     effective emissivity scheme')
1869133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1870134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1871135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1872                  A,'-cycle)'/ &
1873            '     number of grid levels:                   ',I2/ &
1874            '     Gauss-Seidel red/black iterations:       ',I2)
1875136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1876                  I3,')')
1877137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1878            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1879                  I3,')'/ &
1880            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1881                  I3,')')
1882139 FORMAT (' --> Loop optimization method: ',A)
1883140 FORMAT ('     maximum residual allowed:                ',E10.3)
1884141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1885142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1886                  'step')
1887143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1888                  'kinetic energy')
1889144 FORMAT ('     masking method is used')
1890150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1891                  'conserved'/ &
1892            '     using the ',A,' mode')
1893151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1894152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1895           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1896           /'     starting from dp_level_b =', F8.3, 'm', A /)
1897160 FORMAT (//' Large scale forcing and nudging:'/ &
1898              ' -------------------------------'/)
1899161 FORMAT (' --> No large scale forcing from external is used (default) ')
1900162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1901163 FORMAT ('     - large scale advection tendencies ')
1902164 FORMAT ('     - large scale subsidence velocity w_subs ')
1903165 FORMAT ('     - large scale subsidence tendencies ')
1904167 FORMAT ('     - and geostrophic wind components ug and vg')
1905168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1906                  'prognostic equation(s) for')
1907169 FORMAT ('     the scalar(s) only')
1908170 FORMAT (' --> Nudging is used')
1909171 FORMAT (' --> No nudging is used (default) ')
1910180 FORMAT ('     - prescribed surface values for temperature')
1911181 FORMAT ('     - prescribed surface fluxes for temperature')
1912182 FORMAT ('     - prescribed surface values for humidity')
1913183 FORMAT ('     - prescribed surface fluxes for humidity')
1914200 FORMAT (//' Run time and time step information:'/ &
1915             ' ----------------------------------'/)
1916201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1917             '    CFL-factor:',F5.2)
1918202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1919203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1920             ' End time:            ',F9.3,' s')
1921204 FORMAT ( A,F9.3,' s')
1922205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1923206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1924             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1925               '  ',F9.3,' s'/                                                    &
1926             '                                      per second of simulated tim', &
1927               'e: ',F9.3,' s')
1928207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1929250 FORMAT (//' Computational grid and domain size:'/ &
1930              ' ----------------------------------'// &
1931              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1932              ' m    dz =    ',F7.3,' m'/ &
1933              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1934              ' m  z(u) = ',F10.3,' m'/)
1935252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1936              ' factor:',F6.3/ &
1937            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1938254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1939            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1940260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1941             ' degrees')
1942270 FORMAT (//' Topography information:'/ &
1943              ' ----------------------'// &
1944              1X,'Topography: ',A)
1945271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1946              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1947                ' / ',I4)
1948272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1949              ' direction' / &
1950              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1951              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1952278 FORMAT (' Topography grid definition convention:'/ &
1953            ' cell edge (staggered grid points'/  &
1954            ' (u in x-direction, v in y-direction))' /)
1955279 FORMAT (' Topography grid definition convention:'/ &
1956            ' cell center (scalar grid points)' /)
1957300 FORMAT (//' Boundary conditions:'/ &
1958             ' -------------------'// &
1959             '                     p                    uv             ', &
1960             '                     pt'// &
1961             ' B. bound.: ',A/ &
1962             ' T. bound.: ',A)
1963301 FORMAT (/'                     ',A// &
1964             ' B. bound.: ',A/ &
1965             ' T. bound.: ',A)
1966303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1967304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1968305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1969               'computational u,v-level:'// &
1970             '       zp = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
1971             ' m   kappa =',F5.2/ &
1972             '       Rif value range:   ',F8.2,' <= rif <=',F6.2)
1973306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1974307 FORMAT ('       Heatflux has a random normal distribution')
1975308 FORMAT ('       Predefined surface temperature')
1976309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1977310 FORMAT (//'    1D-Model:'// &
1978             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1979311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1980312 FORMAT ('       Predefined surface humidity')
1981313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1982314 FORMAT ('       Predefined scalar value at the surface')
1983315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1984316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1985                    'atmosphere model')
1986317 FORMAT (//' Lateral boundaries:'/ &
1987            '       left/right:  ',A/    &
1988            '       north/south: ',A)
1989318 FORMAT (/'       use_cmax: ',L1 / &
1990            '       pt damping layer width = ',F8.2,' m, pt ', &
1991                    'damping factor =',F7.4)
1992319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1993            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1994            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1995320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1996            '                                          v: ',F9.6,' m**2/s**2')
1997321 FORMAT (//' Initial profiles:'/ &
1998              ' ----------------')
1999322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2000            '       y shift of the recycled inflow turbulence switched on'/ &
2001            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2002            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
2003325 FORMAT (//' List output:'/ &
2004             ' -----------'//  &
2005            '    1D-Profiles:'/    &
2006            '       Output every             ',F8.2,' s')
2007326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
2008            '       Averaging input every    ',F8.2,' s')
2009330 FORMAT (//' Data output:'/ &
2010             ' -----------'/)
2011331 FORMAT (/'    1D-Profiles:')
2012332 FORMAT (/'       ',A)
2013333 FORMAT ('       Output every             ',F8.2,' s',/ &
2014            '       Time averaged over       ',F8.2,' s'/ &
2015            '       Averaging input every    ',F8.2,' s')
2016334 FORMAT (/'    2D-Arrays',A,':')
2017335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2018            '       Output every             ',F8.2,' s  ',A/ &
2019            '       Cross sections at ',A1,' = ',A/ &
2020            '       scalar-coordinates:   ',A,' m'/)
2021336 FORMAT (/'    3D-Arrays',A,':')
2022337 FORMAT (/'       Arrays: ',A/ &
2023            '       Output every             ',F8.2,' s  ',A/ &
2024            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2025339 FORMAT ('       No output during initial ',F8.2,' s')
2026340 FORMAT (/'    Time series:')
2027341 FORMAT ('       Output every             ',F8.2,' s'/)
2028342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2029            '       Output every             ',F8.2,' s  ',A/ &
2030            '       Time averaged over       ',F8.2,' s'/ &
2031            '       Averaging input every    ',F8.2,' s'/ &
2032            '       Cross sections at ',A1,' = ',A/ &
2033            '       scalar-coordinates:   ',A,' m'/)
2034343 FORMAT (/'       Arrays: ',A/ &
2035            '       Output every             ',F8.2,' s  ',A/ &
2036            '       Time averaged over       ',F8.2,' s'/ &
2037            '       Averaging input every    ',F8.2,' s'/ &
2038            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2039344 FORMAT ('       Output format: ',A/)
2040345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2041            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2042            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2043            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2044346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2045347 FORMAT ('       Variables: ',A/ &
2046            '       Output every             ',F8.2,' s')
2047348 FORMAT ('       Variables: ',A/ &
2048            '       Output every             ',F8.2,' s'/ &
2049            '       Time averaged over       ',F8.2,' s'/ &
2050            '       Averaging input every    ',F8.2,' s')
2051349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2052            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2053            13('       ',8(F8.2,',')/) )
2054350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2055            'all gridpoints along ',A,'-direction (default).' )
2056351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2057            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2058            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
2059352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2060353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
2061354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
2062#if defined( __dvrp_graphics )
2063360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2064            '       Output every      ',F7.1,' s'/ &
2065            '       Output mode:      ',A/ &
2066            '       Host / User:      ',A,' / ',A/ &
2067            '       Directory:        ',A// &
2068            '       The sequence contains:')
2069361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2070            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2071362 FORMAT (/'       Slicer plane ',A/ &
2072            '       Slicer limits: [',F6.2,',',F6.2,']')
2073365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
2074            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2075                     ')'/ &
2076            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2077            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
2078366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2079367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
2080#endif
2081400 FORMAT (//' Physical quantities:'/ &
2082              ' -------------------'/)
2083410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
2084            '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
2085            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2086            '                            f*     = ',F9.6,' 1/s')
2087411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
2088412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2089413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2090414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2091415 FORMAT (/' Cloud physics parameters:'/ &
2092             ' ------------------------'/)
2093416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2094            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2095            '    Density of air     :   rho_0 =',F6.3,' kg/m**3'/  &
2096            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2097            '    Vapourization heat :   L_v   =',E9.2,' J/kg')
2098417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2099418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2100            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2101420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2102            '       Height:        ',A,'  m'/ &
2103            '       Temperature:   ',A,'  K'/ &
2104            '       Gradient:      ',A,'  K/100m'/ &
2105            '       Gridpoint:     ',A)
2106421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2107            '       Height:      ',A,'  m'/ &
2108            '       Humidity:    ',A,'  kg/kg'/ &
2109            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2110            '       Gridpoint:   ',A)
2111422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2112            '       Height:                  ',A,'  m'/ &
2113            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2114            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2115            '       Gridpoint:               ',A)
2116423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2117            '       Height:      ',A,'  m'/ &
2118            '       ug:          ',A,'  m/s'/ &
2119            '       Gradient:    ',A,'  1/100s'/ &
2120            '       Gridpoint:   ',A)
2121424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2122            '       Height:      ',A,'  m'/ &
2123            '       vg:          ',A,'  m/s'/ &
2124            '       Gradient:    ',A,'  1/100s'/ &
2125            '       Gridpoint:   ',A)
2126425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2127            '       Height:     ',A,'  m'/ &
2128            '       Salinity:   ',A,'  psu'/ &
2129            '       Gradient:   ',A,'  psu/100m'/ &
2130            '       Gridpoint:  ',A)
2131426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2132            '       Height:      ',A,'  m'/ &
2133            '       w_subs:      ',A,'  m/s'/ &
2134            '       Gradient:    ',A,'  (m/s)/100m'/ &
2135            '       Gridpoint:   ',A)
2136427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2137                  ' profiles')
2138428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2139             '    NUDGING_DATA')
2140430 FORMAT (//' Cloud physics quantities / methods:'/ &
2141              ' ----------------------------------'/)
2142431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2143                 'on)')
2144432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2145            '    total water content is used.'/ &
2146            '    Condensation is parameterized via 0% - or 100% scheme.')
2147433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2148                 'icle model')
2149434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2150                 ' droplets < 1.0E-6 m')
2151435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2152436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2153                    'are used'/ &
2154            '          number of radius classes:       ',I3,'    interval ', &
2155                       '[1.0E-6,2.0E-4] m'/ &
2156            '          number of dissipation classes:   ',I2,'    interval ', &
2157                       '[0,1000] cm**2/s**3')
2158437 FORMAT ('    Droplet collision is switched off')
2159450 FORMAT (//' LES / Turbulence quantities:'/ &
2160              ' ---------------------------'/)
2161451 FORMAT ('    Diffusion coefficients are constant:'/ &
2162            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2163453 FORMAT ('    Mixing length is limited to',F5.2,' * z')
2164454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2165455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2166470 FORMAT (//' Actions during the simulation:'/ &
2167              ' -----------------------------'/)
2168471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2169            '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
2170            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2171            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2172472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2173                 ' to i/j =',I4)
2174473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2175                 F6.3, ' m**2/s**2')
2176474 FORMAT ('    Random number generator used    : ',A/)
2177475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2178                 'respectively, if'/ &
2179            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2180                 ' 3D-simulation'/)
2181476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2182                 'respectively, if the'/ &
2183            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2184                 ' the 3D-simulation'/)
2185477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2186                 'respectively, if the'/ &
2187            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2188                 ' the 3D-simulation'/)
2189480 FORMAT ('    Particles:'/ &
2190            '    ---------'// &
2191            '       Particle advection is active (switched on at t = ', F7.1, &
2192                    ' s)'/ &
2193            '       Start of new particle generations every  ',F6.1,' s'/ &
2194            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2195            '                            bottom:     ', A, ' top:         ', A/&
2196            '       Maximum particle age:                 ',F9.1,' s'/ &
2197            '       Advection stopped at t = ',F9.1,' s'/)
2198481 FORMAT ('       Particles have random start positions'/)
2199482 FORMAT ('          Particles are advected only horizontally'/)
2200485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2201486 FORMAT ('       Particle statistics are written on file'/)
2202487 FORMAT ('       Number of particle groups: ',I2/)
2203488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2204            '          minimum timestep for advection:', F8.5/)
2205489 FORMAT ('       Number of particles simultaneously released at each ', &
2206                    'point: ', I5/)
2207490 FORMAT ('       Particle group ',I2,':'/ &
2208            '          Particle radius: ',E10.3, 'm')
2209491 FORMAT ('          Particle inertia is activated'/ &
2210            '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
2211492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2212493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2213            '                                         y:',F8.1,' - ',F8.1,' m'/&
2214            '                                         z:',F8.1,' - ',F8.1,' m'/&
2215            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2216                       ' m  dz = ',F8.1,' m'/)
2217494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2218                    F8.2,' s'/)
2219495 FORMAT ('       Number of particles in total domain: ',I10/)
2220496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2221                    'as relative to the given topography')
2222500 FORMAT (//' 1D-Model parameters:'/                           &
2223              ' -------------------'//                           &
2224            '    Simulation time:                   ',F8.1,' s'/ &
2225            '    Run-controll output every:         ',F8.1,' s'/ &
2226            '    Vertical profile output every:     ',F8.1,' s'/ &
2227            '    Mixing length calculation:         ',A/         &
2228            '    Dissipation calculation:           ',A/)
2229502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2230503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2231504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2232505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2233506 FORMAT ('    Cloud water sedimentation parameterization via Stokes law')
2234507 FORMAT ('    Turbulence effects on precipitation process')
2235508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2236509 FORMAT ('    Slope limiter used for sedimentation process')
2237510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2238511 FORMAT ('    Sedimentation Courant number:                  '/&
2239            '                               C_s   =',F4.1,'        ')
2240512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2241            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2242            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2243513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2244            '+ monotonic adjustment')
2245600 FORMAT (/' Nesting informations:'/ &
2246            ' --------------------'/ &
2247            ' Nesting mode:                     ',A/ &
2248            ' Nesting-datatransfer mode:        ',A// &
2249            ' Nest id  parent  number   lower left coordinates   name'/ &
2250            ' (*=me)     id    of PEs      x (m)     y (m)' )
2251601 FORMAT (2X,A1,1X,I2.2,6X,I2.2,5X,I5,5X,F8.2,2X,F8.2,5X,A)
2252
2253 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.