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

Last change on this file since 2768 was 2746, checked in by suehring, 6 years ago

Read information from statitic driver for resolved vegetation independently from land- or urban-surface model

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