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

Last change on this file since 2544 was 2544, checked in by maronga, 7 years ago

introduced new module date_and_time_mod

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