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

Last change on this file since 3049 was 3045, checked in by Giersch, 6 years ago

Code adjusted according to coding standards, renamed namelists, error messages revised until PA0347, output CASE 108 disabled

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