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

Last change on this file since 2851 was 2817, checked in by knoop, 6 years ago

Preliminary gust module interface implemented

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