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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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