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

Last change on this file since 1826 was 1826, checked in by maronga, 8 years ago

further modularization of radiation model and plant canopy model

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