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

Last change on this file since 2258 was 2258, checked in by suehring, 7 years ago

Bugfix, add pre-preprocessor directives to enable non-parrallel mode

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