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

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

last commit documented

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