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

Last change on this file since 1914 was 1903, checked in by suehring, 8 years ago

last commit documented

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