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

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

last commit documented

  • Property svn:keywords set to Id
File size: 92.4 KB
Line 
1!> @file header.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the 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-2015 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: header.f90 1692 2015-10-26 16:29:17Z maronga $
26!
27! 1691 2015-10-26 16:17:44Z maronga
28! Renamed prandtl_layer to constant_flux_layer, renames rif_min/rif_max to
29! zeta_min/zeta_max.
30!
31! 1682 2015-10-07 23:56:08Z knoop
32! Code annotations made doxygen readable
33!
34! 1675 2015-10-02 08:28:59Z gronemeier
35! Bugfix: Definition of topography grid levels
36!
37! 1660 2015-09-21 08:15:16Z gronemeier
38! Bugfix: Definition of building/street canyon height if vertical grid stretching
39!         starts below the maximum topography height.
40!
41! 1590 2015-05-08 13:56:27Z maronga
42! Bugfix: Added TRIM statements for character strings for LSM and radiation code
43!
44! 1585 2015-04-30 07:05:52Z maronga
45! Further output for radiation model(s).
46!
47! 1575 2015-03-27 09:56:27Z raasch
48! adjustments for psolver-queries, output of seed_follows_topography
49!
50! 1560 2015-03-06 10:48:54Z keck
51! output for recycling y shift
52!
53! 1557 2015-03-05 16:43:04Z suehring
54! output for monotonic limiter
55!
56! 1551 2015-03-03 14:18:16Z maronga
57! Added informal output for land surface model and radiation model. Removed typo.
58!
59! 1496 2014-12-02 17:25:50Z maronga
60! Renamed: "radiation -> "cloud_top_radiation"
61!
62! 1484 2014-10-21 10:53:05Z kanani
63! Changes due to new module structure of the plant canopy model:
64!   module plant_canopy_model_mod and output for new canopy model parameters
65!   (alpha_lad, beta_lad, lai_beta,...) added,
66!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
67!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
68!   learde renamed leaf_area_density.
69! Bugfix: DO-WHILE-loop for lad header information additionally restricted
70! by maximum number of gradient levels (currently 10)
71!
72! 1482 2014-10-18 12:34:45Z raasch
73! information about calculated or predefined virtual processor topology adjusted
74!
75! 1468 2014-09-24 14:06:57Z maronga
76! Adapted for use on up to 6-digit processor cores
77!
78! 1429 2014-07-15 12:53:45Z knoop
79! header exended to provide ensemble_member_nr if specified
80!
81! 1376 2014-04-26 11:21:22Z boeske
82! Correction of typos
83!
84! 1365 2014-04-22 15:03:56Z boeske
85! New section 'Large scale forcing and nudging':
86! output of large scale forcing and nudging information,
87! new section for initial profiles created
88!
89! 1359 2014-04-11 17:15:14Z hoffmann
90! dt_sort_particles removed
91!
92! 1353 2014-04-08 15:21:23Z heinze
93! REAL constants provided with KIND-attribute
94!
95! 1327 2014-03-21 11:00:16Z raasch
96! parts concerning iso2d and avs output removed,
97! -netcdf output queries
98!
99! 1324 2014-03-21 09:13:16Z suehring
100! Bugfix: module spectrum added
101!
102! 1322 2014-03-20 16:38:49Z raasch
103! REAL functions provided with KIND-attribute,
104! some REAL constants defined as wp-kind
105!
106! 1320 2014-03-20 08:40:49Z raasch
107! ONLY-attribute added to USE-statements,
108! kind-parameters added to all INTEGER and REAL declaration statements,
109! kinds are defined in new module kinds,
110! revision history before 2012 removed,
111! comment fields (!:) to be used for variable explanations added to
112! all variable declaration statements
113!
114! 1308 2014-03-13 14:58:42Z fricke
115! output of the fixed number of output time levels
116! output_format adjusted for masked data if netcdf_data_format > 5
117!
118! 1299 2014-03-06 13:15:21Z heinze
119! output for using large_scale subsidence in combination
120! with large_scale_forcing
121! reformatting, more detailed explanations
122!
123! 1241 2013-10-30 11:36:58Z heinze
124! output for nudging + large scale forcing from external file
125!
126! 1216 2013-08-26 09:31:42Z raasch
127! output for transpose_compute_overlap
128!
129! 1212 2013-08-15 08:46:27Z raasch
130! output for poisfft_hybrid removed
131!
132! 1179 2013-06-14 05:57:58Z raasch
133! output of reference_state, use_reference renamed use_single_reference_value
134!
135! 1159 2013-05-21 11:58:22Z fricke
136! +use_cmax
137!
138! 1115 2013-03-26 18:16:16Z hoffmann
139! descriptions for Seifert-Beheng-cloud-physics-scheme added
140!
141! 1111 2013-03-08 23:54:10Z raasch
142! output of accelerator board information
143! ibc_p_b = 2 removed
144!
145! 1108 2013-03-05 07:03:32Z raasch
146! bugfix for r1106
147!
148! 1106 2013-03-04 05:31:38Z raasch
149! some format changes for coupled runs
150!
151! 1092 2013-02-02 11:24:22Z raasch
152! unused variables removed
153!
154! 1036 2012-10-22 13:43:42Z raasch
155! code put under GPL (PALM 3.9)
156!
157! 1031 2012-10-19 14:35:30Z raasch
158! output of netCDF data format modified
159!
160! 1015 2012-09-27 09:23:24Z raasch
161! output of Adjustment of mixing length to the Prandtl mixing length at first
162! grid point above ground removed
163!
164! 1003 2012-09-14 14:35:53Z raasch
165! output of information about equal/unequal subdomain size removed
166!
167! 1001 2012-09-13 14:08:46Z raasch
168! all actions concerning leapfrog- and upstream-spline-scheme removed
169!
170! 978 2012-08-09 08:28:32Z fricke
171! -km_damp_max, outflow_damping_width
172! +pt_damping_factor, pt_damping_width
173! +z0h
174!
175! 964 2012-07-26 09:14:24Z raasch
176! output of profil-related quantities removed
177!
178! 940 2012-07-09 14:31:00Z raasch
179! Output in case of simulations for pure neutral stratification (no pt-equation
180! solved)
181!
182! 927 2012-06-06 19:15:04Z raasch
183! output of masking_method for mg-solver
184!
185! 868 2012-03-28 12:21:07Z raasch
186! translation velocity in Galilean transformation changed to 0.6 * ug
187!
188! 833 2012-02-22 08:55:55Z maronga
189! Adjusted format for leaf area density
190!
191! 828 2012-02-21 12:00:36Z raasch
192! output of dissipation_classes + radius_classes
193!
194! 825 2012-02-19 03:03:44Z raasch
195! Output of cloud physics parameters/quantities complemented and restructured
196!
197! Revision 1.1  1997/08/11 06:17:20  raasch
198! Initial revision
199!
200!
201! Description:
202! ------------
203!> Writing a header with all important information about the actual run.
204!> This subroutine is called three times, two times at the beginning
205!> (writing information on files RUN_CONTROL and HEADER) and one time at the
206!> end of the run, then writing additional information about CPU-usage on file
207!> header.
208!-----------------------------------------------------------------------------!
209 SUBROUTINE header
210 
211
212    USE arrays_3d,                                                             &
213        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu, zw
214       
215    USE control_parameters
216       
217    USE cloud_parameters,                                                      &
218        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
219               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
220       
221    USE cpulog,                                                                &
222        ONLY:  log_point_s
223       
224    USE dvrp_variables,                                                        &
225        ONLY:  use_seperate_pe_for_dvrp_output
226       
227    USE grid_variables,                                                        &
228        ONLY:  dx, dy
229       
230    USE indices,                                                               &
231        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
232               nys_mg, nzt, nzt_mg
233       
234    USE kinds
235   
236    USE land_surface_model_mod,                                                &
237        ONLY:  conserve_water_content, dewfall, land_surface, nzb_soil,        &
238               nzt_soil, root_fraction, soil_moisture, soil_temperature,       &
239               soil_type, soil_type_name, veg_type, veg_type_name, zs
240 
241    USE model_1d,                                                              &
242        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
243       
244    USE particle_attributes,                                                   &
245        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
246               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
247               dt_write_particle_data, end_time_prel,                          &
248               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
249               minimum_tailpoint_distance, number_of_particle_groups,          &
250               particle_advection, particle_advection_start,                   &
251               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
252               pst, radius, radius_classes, random_start_position,             &
253               seed_follows_topography,                                        &
254               total_number_of_particles, use_particle_tails,                  &
255               use_sgs_for_particles, total_number_of_tails,                   &
256               vertical_particle_advection, write_particle_statistics
257       
258    USE pegrid
259
260    USE plant_canopy_model_mod,                                                &
261        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
262               canopy_mode, cthf, lad, lad_surface, lad_vertical_gradient,     &
263               lad_vertical_gradient_level, lad_vertical_gradient_level_ind,   &
264               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
265               plant_canopy
266
267    USE radiation_model_mod,                                                   &
268        ONLY:  albedo, albedo_type, albedo_type_name, constant_albedo,         &
269               day_init, dt_radiation, lambda, lw_radiation, net_radiation,    &
270               radiation, radiation_scheme, sw_radiation, time_utc_init
271   
272    USE spectrum,                                                              &
273        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
274               spectra_direction
275
276    IMPLICIT NONE
277
278    CHARACTER (LEN=1)  ::  prec                !<
279   
280    CHARACTER (LEN=2)  ::  do2d_mode           !<
281   
282    CHARACTER (LEN=5)  ::  section_chr         !<
283   
284    CHARACTER (LEN=10) ::  coor_chr            !<
285    CHARACTER (LEN=10) ::  host_chr            !<
286   
287    CHARACTER (LEN=16) ::  begin_chr           !<
288   
289    CHARACTER (LEN=26) ::  ver_rev             !<
290   
291    CHARACTER (LEN=40) ::  output_format       !<
292   
293    CHARACTER (LEN=70) ::  char1               !<
294    CHARACTER (LEN=70) ::  char2               !<
295    CHARACTER (LEN=70) ::  dopr_chr            !<
296    CHARACTER (LEN=70) ::  do2d_xy             !<
297    CHARACTER (LEN=70) ::  do2d_xz             !<
298    CHARACTER (LEN=70) ::  do2d_yz             !<
299    CHARACTER (LEN=70) ::  do3d_chr            !<
300    CHARACTER (LEN=70) ::  domask_chr          !<
301    CHARACTER (LEN=70) ::  run_classification  !<
302   
303    CHARACTER (LEN=85) ::  roben               !<
304    CHARACTER (LEN=85) ::  runten              !<
305   
306    CHARACTER (LEN=86) ::  coordinates         !<
307    CHARACTER (LEN=86) ::  gradients           !<
308    CHARACTER (LEN=86) ::  leaf_area_density   !<
309    CHARACTER (LEN=86) ::  roots               !<
310    CHARACTER (LEN=86) ::  slices              !<
311    CHARACTER (LEN=86) ::  temperatures        !<
312    CHARACTER (LEN=86) ::  ugcomponent         !<
313    CHARACTER (LEN=86) ::  vgcomponent         !<
314
315    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !<
316
317    INTEGER(iwp) ::  av        !<
318    INTEGER(iwp) ::  bh        !<
319    INTEGER(iwp) ::  blx       !<
320    INTEGER(iwp) ::  bly       !<
321    INTEGER(iwp) ::  bxl       !<
322    INTEGER(iwp) ::  bxr       !<
323    INTEGER(iwp) ::  byn       !<
324    INTEGER(iwp) ::  bys       !<
325    INTEGER(iwp) ::  ch        !<
326    INTEGER(iwp) ::  count     !<
327    INTEGER(iwp) ::  cwx       !<
328    INTEGER(iwp) ::  cwy       !<
329    INTEGER(iwp) ::  cxl       !<
330    INTEGER(iwp) ::  cxr       !<
331    INTEGER(iwp) ::  cyn       !<
332    INTEGER(iwp) ::  cys       !<
333    INTEGER(iwp) ::  dim       !<
334    INTEGER(iwp) ::  i         !<
335    INTEGER(iwp) ::  io        !<
336    INTEGER(iwp) ::  j         !<
337    INTEGER(iwp) ::  k         !<
338    INTEGER(iwp) ::  l         !<
339    INTEGER(iwp) ::  ll        !<
340    INTEGER(iwp) ::  mpi_type  !<
341   
342    REAL(wp) ::  canopy_height                    !< canopy height (in m)
343    REAL(wp) ::  cpuseconds_per_simulated_second  !<
344
345!
346!-- Open the output file. At the end of the simulation, output is directed
347!-- to unit 19.
348    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
349         .NOT. simulated_time_at_begin /= simulated_time )  THEN
350       io = 15   !  header output on file RUN_CONTROL
351    ELSE
352       io = 19   !  header output on file HEADER
353    ENDIF
354    CALL check_open( io )
355
356!
357!-- At the end of the run, output file (HEADER) will be rewritten with
358!-- new information
359    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
360
361!
362!-- Determine kind of model run
363    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
364       run_classification = '3D - restart run'
365    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
366       run_classification = '3D - run with cyclic fill of 3D - prerun data'
367    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
368       run_classification = '3D - run without 1D - prerun'
369    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
370       run_classification = '3D - run with 1D - prerun'
371    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
372       run_classification = '3D - run initialized by user'
373    ELSE
374       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
375       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
376    ENDIF
377    IF ( ocean )  THEN
378       run_classification = 'ocean - ' // run_classification
379    ELSE
380       run_classification = 'atmosphere - ' // run_classification
381    ENDIF
382
383!
384!-- Run-identification, date, time, host
385    host_chr = host(1:10)
386    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
387    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
388    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
389#if defined( __mpi2 )
390       mpi_type = 2
391#else
392       mpi_type = 1
393#endif
394       WRITE ( io, 101 )  mpi_type, coupling_mode
395    ENDIF
396#if defined( __parallel )
397    IF ( coupling_start_time /= 0.0_wp )  THEN
398       IF ( coupling_start_time > simulated_time_at_begin )  THEN
399          WRITE ( io, 109 )
400       ELSE
401          WRITE ( io, 114 )
402       ENDIF
403    ENDIF
404#endif
405    IF ( ensemble_member_nr /= 0 )  THEN
406       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
407                       ADJUSTR( host_chr ), ensemble_member_nr
408    ELSE
409       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
410                       ADJUSTR( host_chr )
411    ENDIF
412#if defined( __parallel )
413    IF ( npex == -1  .AND.  npey == -1 )  THEN
414       char1 = 'calculated'
415    ELSE
416       char1 = 'predefined'
417    ENDIF
418    IF ( threads_per_task == 1 )  THEN
419       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
420    ELSE
421       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
422                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
423    ENDIF
424    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
425    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
426           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
427         npex == -1  .AND.  pdims(2) == 1 )                      &
428    THEN
429       WRITE ( io, 106 )
430    ELSEIF ( pdims(2) == 1 )  THEN
431       WRITE ( io, 107 )  'x'
432    ELSEIF ( pdims(1) == 1 )  THEN
433       WRITE ( io, 107 )  'y'
434    ENDIF
435    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
436    IF ( numprocs /= maximum_parallel_io_streams )  THEN
437       WRITE ( io, 108 )  maximum_parallel_io_streams
438    ENDIF
439#else
440    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
441#endif
442    WRITE ( io, 99 )
443
444!
445!-- Numerical schemes
446    WRITE ( io, 110 )
447    IF ( psolver(1:7) == 'poisfft' )  THEN
448       WRITE ( io, 111 )  TRIM( fft_method )
449       IF ( transpose_compute_overlap )  WRITE( io, 115 )
450    ELSEIF ( psolver == 'sor' )  THEN
451       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
452    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
453       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
454       IF ( mg_cycles == -1 )  THEN
455          WRITE ( io, 140 )  residual_limit
456       ELSE
457          WRITE ( io, 141 )  mg_cycles
458       ENDIF
459       IF ( mg_switch_to_pe0_level == 0 )  THEN
460          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
461                             nzt_mg(1)
462       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
463          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
464                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
465                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
466                             nzt_mg(mg_switch_to_pe0_level),    &
467                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
468                             nzt_mg(1)
469       ENDIF
470       IF ( masking_method )  WRITE ( io, 144 )
471    ENDIF
472    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
473    THEN
474       WRITE ( io, 142 )
475    ENDIF
476
477    IF ( momentum_advec == 'pw-scheme' )  THEN
478       WRITE ( io, 113 )
479    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
480       WRITE ( io, 503 )
481    ENDIF
482    IF ( scalar_advec == 'pw-scheme' )  THEN
483       WRITE ( io, 116 )
484    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
485       WRITE ( io, 504 )
486    ELSEIF ( scalar_advec == 'ws-scheme-mono' )  THEN
487       WRITE ( io, 513 )
488    ELSE
489       WRITE ( io, 118 )
490    ENDIF
491
492    WRITE ( io, 139 )  TRIM( loop_optimization )
493
494    IF ( galilei_transformation )  THEN
495       IF ( use_ug_for_galilei_tr )  THEN
496          char1 = '0.6 * geostrophic wind'
497       ELSE
498          char1 = 'mean wind in model domain'
499       ENDIF
500       IF ( simulated_time_at_begin == simulated_time )  THEN
501          char2 = 'at the start of the run'
502       ELSE
503          char2 = 'at the end of the run'
504       ENDIF
505       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
506                          advected_distance_x/1000.0_wp,                       &
507                          advected_distance_y/1000.0_wp
508    ENDIF
509    WRITE ( io, 122 )  timestep_scheme
510    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
511    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
512       IF ( .NOT. ocean )  THEN
513          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
514               rayleigh_damping_factor
515       ELSE
516          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
517               rayleigh_damping_factor
518       ENDIF
519    ENDIF
520    IF ( neutral )  WRITE ( io, 131 )  pt_surface
521    IF ( humidity )  THEN
522       IF ( .NOT. cloud_physics )  THEN
523          WRITE ( io, 129 )
524       ELSE
525          WRITE ( io, 130 )
526       ENDIF
527    ENDIF
528    IF ( passive_scalar )  WRITE ( io, 134 )
529    IF ( conserve_volume_flow )  THEN
530       WRITE ( io, 150 )  conserve_volume_flow_mode
531       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
532          WRITE ( io, 151 )  u_bulk, v_bulk
533       ENDIF
534    ELSEIF ( dp_external )  THEN
535       IF ( dp_smooth )  THEN
536          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
537       ELSE
538          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
539       ENDIF
540    ENDIF
541    WRITE ( io, 99 )
542
543!
544!-- Runtime and timestep information
545    WRITE ( io, 200 )
546    IF ( .NOT. dt_fixed )  THEN
547       WRITE ( io, 201 )  dt_max, cfl_factor
548    ELSE
549       WRITE ( io, 202 )  dt
550    ENDIF
551    WRITE ( io, 203 )  simulated_time_at_begin, end_time
552
553    IF ( time_restart /= 9999999.9_wp  .AND. &
554         simulated_time_at_begin == simulated_time )  THEN
555       IF ( dt_restart == 9999999.9_wp )  THEN
556          WRITE ( io, 204 )  ' Restart at:       ',time_restart
557       ELSE
558          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
559       ENDIF
560    ENDIF
561
562    IF ( simulated_time_at_begin /= simulated_time )  THEN
563       i = MAX ( log_point_s(10)%counts, 1 )
564       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
565          cpuseconds_per_simulated_second = 0.0_wp
566       ELSE
567          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
568                                            ( simulated_time -    &
569                                              simulated_time_at_begin )
570       ENDIF
571       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
572                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
573                          cpuseconds_per_simulated_second
574       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
575          IF ( dt_restart == 9999999.9_wp )  THEN
576             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
577          ELSE
578             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
579          ENDIF
580       ENDIF
581    ENDIF
582
583
584!
585!-- Start time for coupled runs, if independent precursor runs for atmosphere
586!-- and ocean are used or have been used. In this case, coupling_start_time
587!-- defines the time when the coupling is switched on.
588    IF ( coupling_start_time /= 0.0_wp )  THEN
589       WRITE ( io, 207 )  coupling_start_time
590    ENDIF
591
592!
593!-- Computational grid
594    IF ( .NOT. ocean )  THEN
595       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
596       IF ( dz_stretch_level_index < nzt+1 )  THEN
597          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
598                             dz_stretch_factor, dz_max
599       ENDIF
600    ELSE
601       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
602       IF ( dz_stretch_level_index > 0 )  THEN
603          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
604                             dz_stretch_factor, dz_max
605       ENDIF
606    ENDIF
607    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
608                       MIN( nnz+2, nzt+2 )
609    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
610
611!
612!-- Large scale forcing and nudging
613    WRITE ( io, 160 )
614    IF ( large_scale_forcing )  THEN
615       WRITE ( io, 162 )
616       WRITE ( io, 163 )
617
618       IF ( large_scale_subsidence )  THEN
619          IF ( .NOT. use_subsidence_tendencies )  THEN
620             WRITE ( io, 164 )
621          ELSE
622             WRITE ( io, 165 )
623          ENDIF
624       ENDIF
625
626       IF ( bc_pt_b == 'dirichlet' )  THEN
627          WRITE ( io, 180 )
628       ELSEIF ( bc_pt_b == 'neumann' )  THEN
629          WRITE ( io, 181 )
630       ENDIF
631
632       IF ( bc_q_b == 'dirichlet' )  THEN
633          WRITE ( io, 182 )
634       ELSEIF ( bc_q_b == 'neumann' )  THEN
635          WRITE ( io, 183 )
636       ENDIF
637
638       WRITE ( io, 167 )
639       IF ( nudging )  THEN
640          WRITE ( io, 170 )
641       ENDIF
642    ELSE
643       WRITE ( io, 161 )
644       WRITE ( io, 171 )
645    ENDIF
646    IF ( large_scale_subsidence )  THEN
647       WRITE ( io, 168 )
648       WRITE ( io, 169 )
649    ENDIF
650
651!
652!-- Profile for the large scale vertial velocity
653!-- Building output strings, starting with surface value
654    IF ( large_scale_subsidence )  THEN
655       temperatures = '   0.0'
656       gradients = '------'
657       slices = '     0'
658       coordinates = '   0.0'
659       i = 1
660       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
661
662          WRITE (coor_chr,'(E10.2,7X)')  &
663                                w_subs(subs_vertical_gradient_level_i(i))
664          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
665
666          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
667          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
668
669          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
670          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
671
672          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
673          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
674
675          IF ( i == 10 )  THEN
676             EXIT
677          ELSE
678             i = i + 1
679          ENDIF
680
681       ENDDO
682
683 
684       IF ( .NOT. large_scale_forcing )  THEN
685          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
686                             TRIM( gradients ), TRIM( slices )
687       ENDIF
688
689
690    ENDIF
691
692!-- Profile of the geostrophic wind (component ug)
693!-- Building output strings
694    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
695    gradients = '------'
696    slices = '     0'
697    coordinates = '   0.0'
698    i = 1
699    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
700     
701       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
702       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
703
704       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
705       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
706
707       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
708       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
709
710       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
711       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
712
713       IF ( i == 10 )  THEN
714          EXIT
715       ELSE
716          i = i + 1
717       ENDIF
718
719    ENDDO
720
721    IF ( .NOT. large_scale_forcing )  THEN
722       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
723                          TRIM( gradients ), TRIM( slices )
724    ENDIF
725
726!-- Profile of the geostrophic wind (component vg)
727!-- Building output strings
728    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
729    gradients = '------'
730    slices = '     0'
731    coordinates = '   0.0'
732    i = 1
733    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
734
735       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
736       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
737
738       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
739       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
740
741       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
742       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
743
744       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
745       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
746
747       IF ( i == 10 )  THEN
748          EXIT
749       ELSE
750          i = i + 1
751       ENDIF
752 
753    ENDDO
754
755    IF ( .NOT. large_scale_forcing )  THEN
756       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
757                          TRIM( gradients ), TRIM( slices )
758    ENDIF
759
760!
761!-- Topography
762    WRITE ( io, 270 )  topography
763    SELECT CASE ( TRIM( topography ) )
764
765       CASE ( 'flat' )
766          ! no actions necessary
767
768       CASE ( 'single_building' )
769          blx = INT( building_length_x / dx )
770          bly = INT( building_length_y / dy )
771          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
772          IF ( ABS( zw(bh  ) - building_height ) == &
773               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
774
775          IF ( building_wall_left == 9999999.9_wp )  THEN
776             building_wall_left = ( nx + 1 - blx ) / 2 * dx
777          ENDIF
778          bxl = INT ( building_wall_left / dx + 0.5_wp )
779          bxr = bxl + blx
780
781          IF ( building_wall_south == 9999999.9_wp )  THEN
782             building_wall_south = ( ny + 1 - bly ) / 2 * dy
783          ENDIF
784          bys = INT ( building_wall_south / dy + 0.5_wp )
785          byn = bys + bly
786
787          WRITE ( io, 271 )  building_length_x, building_length_y, &
788                             building_height, bxl, bxr, bys, byn
789
790       CASE ( 'single_street_canyon' )
791          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
792          IF ( ABS( zw(ch  ) - canyon_height ) == &
793               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
794          IF ( canyon_width_x /= 9999999.9_wp )  THEN
795!
796!--          Street canyon in y direction
797             cwx = NINT( canyon_width_x / dx )
798             IF ( canyon_wall_left == 9999999.9_wp )  THEN
799                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
800             ENDIF
801             cxl = NINT( canyon_wall_left / dx )
802             cxr = cxl + cwx
803             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
804
805          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
806!
807!--          Street canyon in x direction
808             cwy = NINT( canyon_width_y / dy )
809             IF ( canyon_wall_south == 9999999.9_wp )  THEN
810                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
811             ENDIF
812             cys = NINT( canyon_wall_south / dy )
813             cyn = cys + cwy
814             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
815          ENDIF
816
817    END SELECT
818
819    IF ( TRIM( topography ) /= 'flat' )  THEN
820       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
821          IF ( TRIM( topography ) == 'single_building' .OR.  &
822               TRIM( topography ) == 'single_street_canyon' )  THEN
823             WRITE ( io, 278 )
824          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
825             WRITE ( io, 279 )
826          ENDIF
827       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
828          WRITE ( io, 278 )
829       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
830          WRITE ( io, 279 )
831       ENDIF
832    ENDIF
833
834    IF ( plant_canopy )  THEN
835   
836       canopy_height = pch_index * dz
837
838       WRITE ( io, 280 )  canopy_mode, canopy_height, pch_index,               &
839                          canopy_drag_coeff
840       IF ( passive_scalar )  THEN
841          WRITE ( io, 281 )  leaf_scalar_exch_coeff,                           &
842                             leaf_surface_conc
843       ENDIF
844
845!
846!--    Heat flux at the top of vegetation
847       WRITE ( io, 282 )  cthf
848
849!
850!--    Leaf area density profile, calculated either from given vertical
851!--    gradients or from beta probability density function.
852       IF (  .NOT.  calc_beta_lad_profile )  THEN
853
854!--       Building output strings, starting with surface value
855          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
856          gradients = '------'
857          slices = '     0'
858          coordinates = '   0.0'
859          i = 1
860          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i) /= -9999 )
861
862             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
863             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
864 
865             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
866             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
867
868             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
869             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
870
871             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
872             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
873
874             i = i + 1
875          ENDDO
876
877          WRITE ( io, 283 )  TRIM( coordinates ), TRIM( leaf_area_density ),              &
878                             TRIM( gradients ), TRIM( slices )
879
880       ELSE
881       
882          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
883          coordinates = '   0.0'
884         
885          DO  k = 1, pch_index
886
887             WRITE (coor_chr,'(F7.2)')  lad(k)
888             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
889 
890             WRITE (coor_chr,'(F7.1)')  zu(k)
891             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
892
893          ENDDO       
894
895          WRITE ( io, 284 ) TRIM( coordinates ), TRIM( leaf_area_density ), alpha_lad,    &
896                            beta_lad, lai_beta
897
898       ENDIF 
899
900    ENDIF
901
902
903    IF ( land_surface )  THEN
904
905       temperatures = ''
906       gradients    = '' ! use for humidity here
907       coordinates  = '' ! use for height
908       roots        = '' ! use for root fraction
909       slices       = '' ! use for index
910
911       i = 1
912       DO i = nzb_soil, nzt_soil
913          WRITE (coor_chr,'(F10.2,7X)') soil_temperature(i)
914          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
915
916          WRITE (coor_chr,'(F10.2,7X)') soil_moisture(i)
917          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
918
919          WRITE (coor_chr,'(F10.2,7X)')  - zs(i)
920          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
921
922          WRITE (coor_chr,'(F10.2,7X)')  root_fraction(i)
923          roots = TRIM( roots ) // ' '  // TRIM( coor_chr )
924
925          WRITE (coor_chr,'(I10,7X)')  i
926          slices = TRIM( slices ) // ' '  // TRIM( coor_chr )
927
928
929       ENDDO
930
931!
932!--    Write land surface model header
933       WRITE( io, 419 )
934       IF ( conserve_water_content )  THEN
935          WRITE( io, 440 )
936       ELSE
937          WRITE( io, 441 )
938       ENDIF
939
940       IF ( dewfall )  THEN
941          WRITE( io, 442 )
942       ELSE
943          WRITE( io, 443 )
944       ENDIF
945
946       WRITE( io, 438 ) TRIM( veg_type_name(veg_type) ),                       &
947                        TRIM (soil_type_name(soil_type) )
948       WRITE( io, 439 ) TRIM( coordinates ), TRIM( temperatures ),             &
949                        TRIM( gradients ), TRIM( roots ), TRIM( slices )
950
951
952    ENDIF
953
954    IF ( radiation )  THEN
955!
956!--    Write radiation model header
957       WRITE( io, 444 )
958
959       IF ( radiation_scheme == "constant" )  THEN
960          WRITE( io, 445 ) net_radiation
961       ELSEIF ( radiation_scheme == "clear-sky" )  THEN
962          WRITE( io, 446 )
963       ELSEIF ( radiation_scheme == "rrtmg" )  THEN
964          WRITE( io, 447 )
965          IF ( .NOT. lw_radiation )  WRITE( io, 458 )
966          IF ( .NOT. sw_radiation )  WRITE( io, 459 )
967       ENDIF
968
969       IF ( albedo_type == 0 )  THEN
970          WRITE( io, 448 ) albedo
971       ELSE
972          WRITE( io, 456 ) TRIM( albedo_type_name(albedo_type) )
973       ENDIF
974       IF ( constant_albedo )  THEN
975          WRITE( io, 457 )
976       ENDIF
977       WRITE( io, 449 ) dt_radiation
978    ENDIF
979
980
981!
982!-- Boundary conditions
983    IF ( ibc_p_b == 0 )  THEN
984       runten = 'p(0)     = 0      |'
985    ELSEIF ( ibc_p_b == 1 )  THEN
986       runten = 'p(0)     = p(1)   |'
987    ENDIF
988    IF ( ibc_p_t == 0 )  THEN
989       roben  = 'p(nzt+1) = 0      |'
990    ELSE
991       roben  = 'p(nzt+1) = p(nzt) |'
992    ENDIF
993
994    IF ( ibc_uv_b == 0 )  THEN
995       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
996    ELSE
997       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
998    ENDIF
999    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
1000       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
1001    ELSEIF ( ibc_uv_t == 0 )  THEN
1002       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
1003    ELSE
1004       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
1005    ENDIF
1006
1007    IF ( ibc_pt_b == 0 )  THEN
1008       IF ( land_surface )  THEN
1009          runten = TRIM( runten ) // ' pt(0)     = from soil model'
1010       ELSE
1011          runten = TRIM( runten ) // ' pt(0)     = pt_surface'
1012       ENDIF
1013    ELSEIF ( ibc_pt_b == 1 )  THEN
1014       runten = TRIM( runten ) // ' pt(0)     = pt(1)'
1015    ELSEIF ( ibc_pt_b == 2 )  THEN
1016       runten = TRIM( runten ) // ' pt(0)     = from coupled model'
1017    ENDIF
1018    IF ( ibc_pt_t == 0 )  THEN
1019       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
1020    ELSEIF( ibc_pt_t == 1 )  THEN
1021       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
1022    ELSEIF( ibc_pt_t == 2 )  THEN
1023       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
1024
1025    ENDIF
1026
1027    WRITE ( io, 300 )  runten, roben
1028
1029    IF ( .NOT. constant_diffusion )  THEN
1030       IF ( ibc_e_b == 1 )  THEN
1031          runten = 'e(0)     = e(1)'
1032       ELSE
1033          runten = 'e(0)     = e(1) = (u*/0.1)**2'
1034       ENDIF
1035       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
1036
1037       WRITE ( io, 301 )  'e', runten, roben       
1038
1039    ENDIF
1040
1041    IF ( ocean )  THEN
1042       runten = 'sa(0)    = sa(1)'
1043       IF ( ibc_sa_t == 0 )  THEN
1044          roben =  'sa(nzt+1) = sa_surface'
1045       ELSE
1046          roben =  'sa(nzt+1) = sa(nzt)'
1047       ENDIF
1048       WRITE ( io, 301 ) 'sa', runten, roben
1049    ENDIF
1050
1051    IF ( humidity )  THEN
1052       IF ( ibc_q_b == 0 )  THEN
1053          IF ( land_surface )  THEN
1054             runten = 'q(0)     = from soil model'
1055          ELSE
1056             runten = 'q(0)     = q_surface'
1057          ENDIF
1058
1059       ELSE
1060          runten = 'q(0)     = q(1)'
1061       ENDIF
1062       IF ( ibc_q_t == 0 )  THEN
1063          roben =  'q(nzt)   = q_top'
1064       ELSE
1065          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
1066       ENDIF
1067       WRITE ( io, 301 ) 'q', runten, roben
1068    ENDIF
1069
1070    IF ( passive_scalar )  THEN
1071       IF ( ibc_q_b == 0 )  THEN
1072          runten = 's(0)     = s_surface'
1073       ELSE
1074          runten = 's(0)     = s(1)'
1075       ENDIF
1076       IF ( ibc_q_t == 0 )  THEN
1077          roben =  's(nzt)   = s_top'
1078       ELSE
1079          roben =  's(nzt)   = s(nzt-1) + ds/dz'
1080       ENDIF
1081       WRITE ( io, 301 ) 's', runten, roben
1082    ENDIF
1083
1084    IF ( use_surface_fluxes )  THEN
1085       WRITE ( io, 303 )
1086       IF ( constant_heatflux )  THEN
1087          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1088             WRITE ( io, 306 )  shf(0,0)
1089          ELSE
1090             WRITE ( io, 306 )  surface_heatflux
1091          ENDIF
1092          IF ( random_heatflux )  WRITE ( io, 307 )
1093       ENDIF
1094       IF ( humidity  .AND.  constant_waterflux )  THEN
1095          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1096             WRITE ( io, 311 ) qsws(0,0)
1097          ELSE
1098             WRITE ( io, 311 ) surface_waterflux
1099          ENDIF
1100       ENDIF
1101       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1102          WRITE ( io, 313 ) surface_waterflux
1103       ENDIF
1104    ENDIF
1105
1106    IF ( use_top_fluxes )  THEN
1107       WRITE ( io, 304 )
1108       IF ( coupling_mode == 'uncoupled' )  THEN
1109          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
1110          IF ( constant_top_heatflux )  THEN
1111             WRITE ( io, 306 )  top_heatflux
1112          ENDIF
1113       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1114          WRITE ( io, 316 )
1115       ENDIF
1116       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1117          WRITE ( io, 309 )  top_salinityflux
1118       ENDIF
1119       IF ( humidity  .OR.  passive_scalar )  THEN
1120          WRITE ( io, 315 )
1121       ENDIF
1122    ENDIF
1123
1124    IF ( constant_flux_layer )  THEN
1125       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
1126                          z0h_factor*roughness_length, kappa,                  &
1127                          zeta_min, zeta_max
1128       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
1129       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
1130          WRITE ( io, 312 )
1131       ENDIF
1132       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1133          WRITE ( io, 314 )
1134       ENDIF
1135    ELSE
1136       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
1137          WRITE ( io, 310 )  zeta_min, zeta_max
1138       ENDIF
1139    ENDIF
1140
1141    WRITE ( io, 317 )  bc_lr, bc_ns
1142    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1143       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
1144       IF ( turbulent_inflow )  THEN
1145          IF ( .NOT. recycling_yshift ) THEN
1146             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1147                                inflow_damping_height, inflow_damping_width
1148          ELSE
1149             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1150                                inflow_damping_height, inflow_damping_width
1151          END IF
1152       ENDIF
1153    ENDIF
1154
1155!
1156!-- Initial Profiles
1157    WRITE ( io, 321 )
1158!
1159!-- Initial wind profiles
1160    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1161
1162!
1163!-- Initial temperature profile
1164!-- Building output strings, starting with surface temperature
1165    WRITE ( temperatures, '(F6.2)' )  pt_surface
1166    gradients = '------'
1167    slices = '     0'
1168    coordinates = '   0.0'
1169    i = 1
1170    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1171
1172       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1173       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1174
1175       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1176       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1177
1178       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1179       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1180
1181       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1182       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1183
1184       IF ( i == 10 )  THEN
1185          EXIT
1186       ELSE
1187          i = i + 1
1188       ENDIF
1189
1190    ENDDO
1191
1192    IF ( .NOT. nudging )  THEN
1193       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1194                          TRIM( gradients ), TRIM( slices )
1195    ELSE
1196       WRITE ( io, 428 ) 
1197    ENDIF
1198
1199!
1200!-- Initial humidity profile
1201!-- Building output strings, starting with surface humidity
1202    IF ( humidity  .OR.  passive_scalar )  THEN
1203       WRITE ( temperatures, '(E8.1)' )  q_surface
1204       gradients = '--------'
1205       slices = '       0'
1206       coordinates = '     0.0'
1207       i = 1
1208       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1209         
1210          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1211          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1212
1213          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1214          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1215         
1216          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1217          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1218         
1219          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1220          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1221
1222          IF ( i == 10 )  THEN
1223             EXIT
1224          ELSE
1225             i = i + 1
1226          ENDIF
1227
1228       ENDDO
1229
1230       IF ( humidity )  THEN
1231          IF ( .NOT. nudging )  THEN
1232             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1233                                TRIM( gradients ), TRIM( slices )
1234          ENDIF
1235       ELSE
1236          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1237                             TRIM( gradients ), TRIM( slices )
1238       ENDIF
1239    ENDIF
1240
1241!
1242!-- Initial salinity profile
1243!-- Building output strings, starting with surface salinity
1244    IF ( ocean )  THEN
1245       WRITE ( temperatures, '(F6.2)' )  sa_surface
1246       gradients = '------'
1247       slices = '     0'
1248       coordinates = '   0.0'
1249       i = 1
1250       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1251
1252          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1253          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1254
1255          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1256          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1257
1258          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1259          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1260
1261          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1262          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1263
1264          IF ( i == 10 )  THEN
1265             EXIT
1266          ELSE
1267             i = i + 1
1268          ENDIF
1269
1270       ENDDO
1271
1272       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1273                          TRIM( gradients ), TRIM( slices )
1274    ENDIF
1275
1276
1277!
1278!-- Listing of 1D-profiles
1279    WRITE ( io, 325 )  dt_dopr_listing
1280    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1281       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1282    ENDIF
1283
1284!
1285!-- DATA output
1286    WRITE ( io, 330 )
1287    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1288       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1289    ENDIF
1290
1291!
1292!-- 1D-profiles
1293    dopr_chr = 'Profile:'
1294    IF ( dopr_n /= 0 )  THEN
1295       WRITE ( io, 331 )
1296
1297       output_format = ''
1298       output_format = output_format_netcdf
1299       WRITE ( io, 344 )  output_format
1300
1301       DO  i = 1, dopr_n
1302          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1303          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1304             WRITE ( io, 332 )  dopr_chr
1305             dopr_chr = '       :'
1306          ENDIF
1307       ENDDO
1308
1309       IF ( dopr_chr /= '' )  THEN
1310          WRITE ( io, 332 )  dopr_chr
1311       ENDIF
1312       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1313       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1314    ENDIF
1315
1316!
1317!-- 2D-arrays
1318    DO  av = 0, 1
1319
1320       i = 1
1321       do2d_xy = ''
1322       do2d_xz = ''
1323       do2d_yz = ''
1324       DO  WHILE ( do2d(av,i) /= ' ' )
1325
1326          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1327          do2d_mode = do2d(av,i)(l-1:l)
1328
1329          SELECT CASE ( do2d_mode )
1330             CASE ( 'xy' )
1331                ll = LEN_TRIM( do2d_xy )
1332                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1333             CASE ( 'xz' )
1334                ll = LEN_TRIM( do2d_xz )
1335                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1336             CASE ( 'yz' )
1337                ll = LEN_TRIM( do2d_yz )
1338                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1339          END SELECT
1340
1341          i = i + 1
1342
1343       ENDDO
1344
1345       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1346              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1347              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1348
1349          IF (  av == 0 )  THEN
1350             WRITE ( io, 334 )  ''
1351          ELSE
1352             WRITE ( io, 334 )  '(time-averaged)'
1353          ENDIF
1354
1355          IF ( do2d_at_begin )  THEN
1356             begin_chr = 'and at the start'
1357          ELSE
1358             begin_chr = ''
1359          ENDIF
1360
1361          output_format = ''
1362          output_format = output_format_netcdf
1363          WRITE ( io, 344 )  output_format
1364
1365          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1366             i = 1
1367             slices = '/'
1368             coordinates = '/'
1369!
1370!--          Building strings with index and coordinate information of the
1371!--          slices
1372             DO  WHILE ( section(i,1) /= -9999 )
1373
1374                WRITE (section_chr,'(I5)')  section(i,1)
1375                section_chr = ADJUSTL( section_chr )
1376                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1377
1378                IF ( section(i,1) == -1 )  THEN
1379                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1380                ELSE
1381                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1382                ENDIF
1383                coor_chr = ADJUSTL( coor_chr )
1384                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1385
1386                i = i + 1
1387             ENDDO
1388             IF ( av == 0 )  THEN
1389                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1390                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1391                                   TRIM( coordinates )
1392                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1393                   WRITE ( io, 339 )  skip_time_do2d_xy
1394                ENDIF
1395             ELSE
1396                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1397                                   TRIM( begin_chr ), averaging_interval, &
1398                                   dt_averaging_input, 'k', TRIM( slices ), &
1399                                   TRIM( coordinates )
1400                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1401                   WRITE ( io, 339 )  skip_time_data_output_av
1402                ENDIF
1403             ENDIF
1404             IF ( netcdf_data_format > 4 )  THEN
1405                WRITE ( io, 352 )  ntdim_2d_xy(av)
1406             ELSE
1407                WRITE ( io, 353 )
1408             ENDIF
1409          ENDIF
1410
1411          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1412             i = 1
1413             slices = '/'
1414             coordinates = '/'
1415!
1416!--          Building strings with index and coordinate information of the
1417!--          slices
1418             DO  WHILE ( section(i,2) /= -9999 )
1419
1420                WRITE (section_chr,'(I5)')  section(i,2)
1421                section_chr = ADJUSTL( section_chr )
1422                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1423
1424                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1425                coor_chr = ADJUSTL( coor_chr )
1426                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1427
1428                i = i + 1
1429             ENDDO
1430             IF ( av == 0 )  THEN
1431                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1432                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1433                                   TRIM( coordinates )
1434                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1435                   WRITE ( io, 339 )  skip_time_do2d_xz
1436                ENDIF
1437             ELSE
1438                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1439                                   TRIM( begin_chr ), averaging_interval, &
1440                                   dt_averaging_input, 'j', TRIM( slices ), &
1441                                   TRIM( coordinates )
1442                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1443                   WRITE ( io, 339 )  skip_time_data_output_av
1444                ENDIF
1445             ENDIF
1446             IF ( netcdf_data_format > 4 )  THEN
1447                WRITE ( io, 352 )  ntdim_2d_xz(av)
1448             ELSE
1449                WRITE ( io, 353 )
1450             ENDIF
1451          ENDIF
1452
1453          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1454             i = 1
1455             slices = '/'
1456             coordinates = '/'
1457!
1458!--          Building strings with index and coordinate information of the
1459!--          slices
1460             DO  WHILE ( section(i,3) /= -9999 )
1461
1462                WRITE (section_chr,'(I5)')  section(i,3)
1463                section_chr = ADJUSTL( section_chr )
1464                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1465
1466                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1467                coor_chr = ADJUSTL( coor_chr )
1468                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1469
1470                i = i + 1
1471             ENDDO
1472             IF ( av == 0 )  THEN
1473                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1474                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1475                                   TRIM( coordinates )
1476                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1477                   WRITE ( io, 339 )  skip_time_do2d_yz
1478                ENDIF
1479             ELSE
1480                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1481                                   TRIM( begin_chr ), averaging_interval, &
1482                                   dt_averaging_input, 'i', TRIM( slices ), &
1483                                   TRIM( coordinates )
1484                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1485                   WRITE ( io, 339 )  skip_time_data_output_av
1486                ENDIF
1487             ENDIF
1488             IF ( netcdf_data_format > 4 )  THEN
1489                WRITE ( io, 352 )  ntdim_2d_yz(av)
1490             ELSE
1491                WRITE ( io, 353 )
1492             ENDIF
1493          ENDIF
1494
1495       ENDIF
1496
1497    ENDDO
1498
1499!
1500!-- 3d-arrays
1501    DO  av = 0, 1
1502
1503       i = 1
1504       do3d_chr = ''
1505       DO  WHILE ( do3d(av,i) /= ' ' )
1506
1507          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1508          i = i + 1
1509
1510       ENDDO
1511
1512       IF ( do3d_chr /= '' )  THEN
1513          IF ( av == 0 )  THEN
1514             WRITE ( io, 336 )  ''
1515          ELSE
1516             WRITE ( io, 336 )  '(time-averaged)'
1517          ENDIF
1518
1519          output_format = output_format_netcdf
1520          WRITE ( io, 344 )  output_format
1521
1522          IF ( do3d_at_begin )  THEN
1523             begin_chr = 'and at the start'
1524          ELSE
1525             begin_chr = ''
1526          ENDIF
1527          IF ( av == 0 )  THEN
1528             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1529                                zu(nz_do3d), nz_do3d
1530          ELSE
1531             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1532                                TRIM( begin_chr ), averaging_interval, &
1533                                dt_averaging_input, zu(nz_do3d), nz_do3d
1534          ENDIF
1535
1536          IF ( netcdf_data_format > 4 )  THEN
1537             WRITE ( io, 352 )  ntdim_3d(av)
1538          ELSE
1539             WRITE ( io, 353 )
1540          ENDIF
1541
1542          IF ( av == 0 )  THEN
1543             IF ( skip_time_do3d /= 0.0_wp )  THEN
1544                WRITE ( io, 339 )  skip_time_do3d
1545             ENDIF
1546          ELSE
1547             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1548                WRITE ( io, 339 )  skip_time_data_output_av
1549             ENDIF
1550          ENDIF
1551
1552       ENDIF
1553
1554    ENDDO
1555
1556!
1557!-- masked arrays
1558    IF ( masks > 0 )  WRITE ( io, 345 )  &
1559         mask_scale_x, mask_scale_y, mask_scale_z
1560    DO  mid = 1, masks
1561       DO  av = 0, 1
1562
1563          i = 1
1564          domask_chr = ''
1565          DO  WHILE ( domask(mid,av,i) /= ' ' )
1566             domask_chr = TRIM( domask_chr ) // ' ' //  &
1567                          TRIM( domask(mid,av,i) ) // ','
1568             i = i + 1
1569          ENDDO
1570
1571          IF ( domask_chr /= '' )  THEN
1572             IF ( av == 0 )  THEN
1573                WRITE ( io, 346 )  '', mid
1574             ELSE
1575                WRITE ( io, 346 )  ' (time-averaged)', mid
1576             ENDIF
1577
1578             output_format = output_format_netcdf
1579!--          Parallel output not implemented for mask data, hence
1580!--          output_format must be adjusted.
1581             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1582             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1583             WRITE ( io, 344 )  output_format
1584
1585             IF ( av == 0 )  THEN
1586                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1587             ELSE
1588                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1589                                   averaging_interval, dt_averaging_input
1590             ENDIF
1591
1592             IF ( av == 0 )  THEN
1593                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1594                   WRITE ( io, 339 )  skip_time_domask(mid)
1595                ENDIF
1596             ELSE
1597                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1598                   WRITE ( io, 339 )  skip_time_data_output_av
1599                ENDIF
1600             ENDIF
1601!
1602!--          output locations
1603             DO  dim = 1, 3
1604                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1605                   count = 0
1606                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1607                      count = count + 1
1608                   ENDDO
1609                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1610                                      mask(mid,dim,:count)
1611                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1612                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1613                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1614                   WRITE ( io, 350 )  dir(dim), dir(dim)
1615                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1616                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1617                                      mask_loop(mid,dim,1:2)
1618                ELSE
1619                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1620                                      mask_loop(mid,dim,1:3)
1621                ENDIF
1622             ENDDO
1623          ENDIF
1624
1625       ENDDO
1626    ENDDO
1627
1628!
1629!-- Timeseries
1630    IF ( dt_dots /= 9999999.9_wp )  THEN
1631       WRITE ( io, 340 )
1632
1633       output_format = output_format_netcdf
1634       WRITE ( io, 344 )  output_format
1635       WRITE ( io, 341 )  dt_dots
1636    ENDIF
1637
1638#if defined( __dvrp_graphics )
1639!
1640!-- Dvrp-output
1641    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1642       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1643                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1644       i = 1
1645       l = 0
1646       m = 0
1647       DO WHILE ( mode_dvrp(i) /= ' ' )
1648          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1649             READ ( mode_dvrp(i), '(10X,I2)' )  j
1650             l = l + 1
1651             IF ( do3d(0,j) /= ' ' )  THEN
1652                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1653                                   isosurface_color(:,l)
1654             ENDIF
1655          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1656             READ ( mode_dvrp(i), '(6X,I2)' )  j
1657             m = m + 1
1658             IF ( do2d(0,j) /= ' ' )  THEN
1659                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1660                                   slicer_range_limits_dvrp(:,m)
1661             ENDIF
1662          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1663             WRITE ( io, 363 )  dvrp_psize
1664             IF ( particle_dvrpsize /= 'none' )  THEN
1665                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1666                                   dvrpsize_interval
1667             ENDIF
1668             IF ( particle_color /= 'none' )  THEN
1669                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1670                                   color_interval
1671             ENDIF
1672          ENDIF
1673          i = i + 1
1674       ENDDO
1675
1676       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1677                          superelevation_y, superelevation, clip_dvrp_l, &
1678                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1679
1680       IF ( TRIM( topography ) /= 'flat' )  THEN
1681          WRITE ( io, 366 )  topography_color
1682          IF ( cluster_size > 1 )  THEN
1683             WRITE ( io, 367 )  cluster_size
1684          ENDIF
1685       ENDIF
1686
1687    ENDIF
1688#endif
1689
1690#if defined( __spectra )
1691!
1692!-- Spectra output
1693    IF ( dt_dosp /= 9999999.9_wp )  THEN
1694       WRITE ( io, 370 )
1695
1696       output_format = output_format_netcdf
1697       WRITE ( io, 344 )  output_format
1698       WRITE ( io, 371 )  dt_dosp
1699       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
1700       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1701                          ( spectra_direction(i), i = 1,10 ),  &
1702                          ( comp_spectra_level(i), i = 1,100 ), &
1703                          ( plot_spectra_level(i), i = 1,100 ), &
1704                          averaging_interval_sp, dt_averaging_input_pr
1705    ENDIF
1706#endif
1707
1708    WRITE ( io, 99 )
1709
1710!
1711!-- Physical quantities
1712    WRITE ( io, 400 )
1713
1714!
1715!-- Geostrophic parameters
1716    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1717       WRITE ( io, 417 )  lambda
1718    ENDIF
1719    WRITE ( io, 410 )  phi, omega, f, fs
1720
1721!
1722!-- Other quantities
1723    WRITE ( io, 411 )  g
1724    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1725       WRITE ( io, 418 )  day_init, time_utc_init
1726    ENDIF
1727
1728    WRITE ( io, 412 )  TRIM( reference_state )
1729    IF ( use_single_reference_value )  THEN
1730       IF ( ocean )  THEN
1731          WRITE ( io, 413 )  prho_reference
1732       ELSE
1733          WRITE ( io, 414 )  pt_reference
1734       ENDIF
1735    ENDIF
1736
1737!
1738!-- Cloud physics parameters
1739    IF ( cloud_physics )  THEN
1740       WRITE ( io, 415 )
1741       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1742       IF ( icloud_scheme == 0 )  THEN
1743          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1744          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1745       ENDIF
1746    ENDIF
1747
1748!
1749!-- Cloud physcis parameters / quantities / numerical methods
1750    WRITE ( io, 430 )
1751    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1752       WRITE ( io, 431 )
1753    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1754       WRITE ( io, 432 )
1755       IF ( cloud_top_radiation )  WRITE ( io, 132 )
1756       IF ( icloud_scheme == 1 )  THEN
1757          IF ( precipitation )  WRITE ( io, 133 )
1758       ELSEIF ( icloud_scheme == 0 )  THEN
1759          IF ( drizzle )  WRITE ( io, 506 )
1760          IF ( precipitation )  THEN
1761             WRITE ( io, 505 )
1762             IF ( turbulence )  WRITE ( io, 507 )
1763             IF ( ventilation_effect )  WRITE ( io, 508 )
1764             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1765          ENDIF
1766       ENDIF
1767    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1768       WRITE ( io, 433 )
1769       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1770       IF ( collision_kernel /= 'none' )  THEN
1771          WRITE ( io, 435 )  TRIM( collision_kernel )
1772          IF ( collision_kernel(6:9) == 'fast' )  THEN
1773             WRITE ( io, 436 )  radius_classes, dissipation_classes
1774          ENDIF
1775       ELSE
1776          WRITE ( io, 437 )
1777       ENDIF
1778    ENDIF
1779
1780!
1781!-- LES / turbulence parameters
1782    WRITE ( io, 450 )
1783
1784!--
1785! ... LES-constants used must still be added here
1786!--
1787    IF ( constant_diffusion )  THEN
1788       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1789                          prandtl_number
1790    ENDIF
1791    IF ( .NOT. constant_diffusion)  THEN
1792       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1793       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1794       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1795    ENDIF
1796
1797!
1798!-- Special actions during the run
1799    WRITE ( io, 470 )
1800    IF ( create_disturbances )  THEN
1801       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1802                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1803                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1804       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1805          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1806       ELSE
1807          WRITE ( io, 473 )  disturbance_energy_limit
1808       ENDIF
1809       WRITE ( io, 474 )  TRIM( random_generator )
1810    ENDIF
1811    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1812       WRITE ( io, 475 )  pt_surface_initial_change
1813    ENDIF
1814    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1815       WRITE ( io, 476 )  q_surface_initial_change       
1816    ENDIF
1817    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1818       WRITE ( io, 477 )  q_surface_initial_change       
1819    ENDIF
1820
1821    IF ( particle_advection )  THEN
1822!
1823!--    Particle attributes
1824       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1825                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1826                          end_time_prel
1827       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1828       IF ( random_start_position )  WRITE ( io, 481 )
1829       IF ( seed_follows_topography )  WRITE ( io, 496 )
1830       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1831       WRITE ( io, 495 )  total_number_of_particles
1832       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1833          WRITE ( io, 483 )  maximum_number_of_tailpoints
1834          IF ( minimum_tailpoint_distance /= 0 )  THEN
1835             WRITE ( io, 484 )  total_number_of_tails,      &
1836                                minimum_tailpoint_distance, &
1837                                maximum_tailpoint_age
1838          ENDIF
1839       ENDIF
1840       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1841          WRITE ( io, 485 )  dt_write_particle_data
1842          IF ( netcdf_data_format > 1 )  THEN
1843             output_format = 'netcdf (64 bit offset) and binary'
1844          ELSE
1845             output_format = 'netcdf and binary'
1846          ENDIF
1847          WRITE ( io, 344 )  output_format
1848       ENDIF
1849       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1850       IF ( write_particle_statistics )  WRITE ( io, 486 )
1851
1852       WRITE ( io, 487 )  number_of_particle_groups
1853
1854       DO  i = 1, number_of_particle_groups
1855          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1856             WRITE ( io, 490 )  i, 0.0_wp
1857             WRITE ( io, 492 )
1858          ELSE
1859             WRITE ( io, 490 )  i, radius(i)
1860             IF ( density_ratio(i) /= 0.0_wp )  THEN
1861                WRITE ( io, 491 )  density_ratio(i)
1862             ELSE
1863                WRITE ( io, 492 )
1864             ENDIF
1865          ENDIF
1866          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1867                             pdx(i), pdy(i), pdz(i)
1868          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1869       ENDDO
1870
1871    ENDIF
1872
1873
1874!
1875!-- Parameters of 1D-model
1876    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1877       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1878                          mixing_length_1d, dissipation_1d
1879       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1880          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1881       ENDIF
1882    ENDIF
1883
1884!
1885!-- User-defined information
1886    CALL user_header( io )
1887
1888    WRITE ( io, 99 )
1889
1890!
1891!-- Write buffer contents to disc immediately
1892    CALL local_flush( io )
1893
1894!
1895!-- Here the FORMATs start
1896
1897 99 FORMAT (1X,78('-'))
1898100 FORMAT (/1X,'******************************',4X,44('-')/        &
1899            1X,'* ',A,' *',4X,A/                               &
1900            1X,'******************************',4X,44('-'))
1901101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1902            35X,42('-'))
1903102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1904            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1905            ' Run on host:        ',A10)
1906#if defined( __parallel )
1907103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1908              ')',1X,A)
1909104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1910              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1911105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1912106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1913            35X,'because the job is running on an SMP-cluster')
1914107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1915108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1916109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1917            35X,42('-'))
1918114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1919            35X,'independent precursor runs'/             &
1920            35X,42('-'))
1921117 FORMAT (' Accelerator boards / node:  ',I2)
1922#endif
1923110 FORMAT (/' Numerical Schemes:'/ &
1924             ' -----------------'/)
1925111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1926112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1927            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1928113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1929                  ' or Upstream')
1930115 FORMAT ('     FFT and transpositions are overlapping')
1931116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1932                  ' or Upstream')
1933118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1934119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1935            '     translation velocity = ',A/ &
1936            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1937120 FORMAT (' Accelerator boards: ',8X,I2)
1938122 FORMAT (' --> Time differencing scheme: ',A)
1939123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1940            '     maximum damping coefficient: ',F5.3, ' 1/s')
1941129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1942130 FORMAT (' --> Additional prognostic equation for the total water content')
1943131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1944                  F6.2, ' K assumed')
1945132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1946            '     effective emissivity scheme')
1947133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1948134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1949135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1950                  A,'-cycle)'/ &
1951            '     number of grid levels:                   ',I2/ &
1952            '     Gauss-Seidel red/black iterations:       ',I2)
1953136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1954                  I3,')')
1955137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1956            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1957                  I3,')'/ &
1958            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1959                  I3,')')
1960139 FORMAT (' --> Loop optimization method: ',A)
1961140 FORMAT ('     maximum residual allowed:                ',E10.3)
1962141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1963142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1964                  'step')
1965143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1966                  'kinetic energy')
1967144 FORMAT ('     masking method is used')
1968150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1969                  'conserved'/ &
1970            '     using the ',A,' mode')
1971151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1972152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1973           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1974           /'     starting from dp_level_b =', F8.3, 'm', A /)
1975160 FORMAT (//' Large scale forcing and nudging:'/ &
1976              ' -------------------------------'/)
1977161 FORMAT (' --> No large scale forcing from external is used (default) ')
1978162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1979163 FORMAT ('     - large scale advection tendencies ')
1980164 FORMAT ('     - large scale subsidence velocity w_subs ')
1981165 FORMAT ('     - large scale subsidence tendencies ')
1982167 FORMAT ('     - and geostrophic wind components ug and vg')
1983168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1984                  'prognostic equation(s) for')
1985169 FORMAT ('     the scalar(s) only')
1986170 FORMAT (' --> Nudging is used')
1987171 FORMAT (' --> No nudging is used (default) ')
1988180 FORMAT ('     - prescribed surface values for temperature')
1989181 FORMAT ('     - prescribed surface fluxes for temperature')
1990182 FORMAT ('     - prescribed surface values for humidity')
1991183 FORMAT ('     - prescribed surface fluxes for humidity')
1992200 FORMAT (//' Run time and time step information:'/ &
1993             ' ----------------------------------'/)
1994201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1995             '    CFL-factor: ',F4.2)
1996202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1997203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1998             ' End time:            ',F9.3,' s')
1999204 FORMAT ( A,F9.3,' s')
2000205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
2001206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
2002             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
2003               '  ',F9.3,' s'/                                                    &
2004             '                                      per second of simulated tim', &
2005               'e: ',F9.3,' s')
2006207 FORMAT ( ' Coupling start time: ',F9.3,' s')
2007250 FORMAT (//' Computational grid and domain size:'/ &
2008              ' ----------------------------------'// &
2009              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
2010              ' m    dz =    ',F7.3,' m'/ &
2011              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
2012              ' m  z(u) = ',F10.3,' m'/)
2013252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
2014              ' factor: ',F5.3/ &
2015            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
2016254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
2017            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
2018260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
2019             ' degrees')
2020270 FORMAT (//' Topography information:'/ &
2021              ' ----------------------'// &
2022              1X,'Topography: ',A)
2023271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
2024              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
2025                ' / ',I4)
2026272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
2027              ' direction' / &
2028              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
2029              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
2030278 FORMAT (' Topography grid definition convention:'/ &
2031            ' cell edge (staggered grid points'/  &
2032            ' (u in x-direction, v in y-direction))' /)
2033279 FORMAT (' Topography grid definition convention:'/ &
2034            ' cell center (scalar grid points)' /)
2035280 FORMAT (//' Vegetation canopy (drag) model:'/ &
2036              ' ------------------------------'// &
2037              ' Canopy mode: ', A / &
2038              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
2039              ' Leaf drag coefficient: ',F6.2 /)
2040281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
2041              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
2042282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
2043283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
2044              ' Height:              ',A,'  m'/ &
2045              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2046              ' Gradient:            ',A,'  m**2/m**4'/ &
2047              ' Gridpoint:           ',A)
2048284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
2049              ' Height:              ',A,'  m'/ &
2050              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2051              ' Coefficient alpha: ',F6.2 / &
2052              ' Coefficient beta: ',F6.2 / &
2053              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
2054               
2055300 FORMAT (//' Boundary conditions:'/ &
2056             ' -------------------'// &
2057             '                     p                    uv             ', &
2058             '                     pt'// &
2059             ' B. bound.: ',A/ &
2060             ' T. bound.: ',A)
2061301 FORMAT (/'                     ',A// &
2062             ' B. bound.: ',A/ &
2063             ' T. bound.: ',A)
2064303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
2065304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
2066305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
2067               'computational u,v-level:'// &
2068             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
2069             ' m   kappa = ',F4.2/ &
2070             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2071306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
2072307 FORMAT ('       Heatflux has a random normal distribution')
2073308 FORMAT ('       Predefined surface temperature')
2074309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
2075310 FORMAT (//'    1D-Model:'// &
2076             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2077311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
2078312 FORMAT ('       Predefined surface humidity')
2079313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
2080314 FORMAT ('       Predefined scalar value at the surface')
2081315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
2082316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
2083                    'atmosphere model')
2084317 FORMAT (//' Lateral boundaries:'/ &
2085            '       left/right:  ',A/    &
2086            '       north/south: ',A)
2087318 FORMAT (/'       use_cmax: ',L1 / &
2088            '       pt damping layer width = ',F8.2,' m, pt ', &
2089                    'damping factor = ',F6.4)
2090319 FORMAT ('       turbulence recycling at inflow switched on'/ &
2091            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2092            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
2093320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
2094            '                                          v: ',F9.6,' m**2/s**2')
2095321 FORMAT (//' Initial profiles:'/ &
2096              ' ----------------')
2097322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2098            '       y shift of the recycled inflow turbulence switched on'/ &
2099            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2100            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
2101325 FORMAT (//' List output:'/ &
2102             ' -----------'//  &
2103            '    1D-Profiles:'/    &
2104            '       Output every             ',F8.2,' s')
2105326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
2106            '       Averaging input every    ',F8.2,' s')
2107330 FORMAT (//' Data output:'/ &
2108             ' -----------'/)
2109331 FORMAT (/'    1D-Profiles:')
2110332 FORMAT (/'       ',A)
2111333 FORMAT ('       Output every             ',F8.2,' s',/ &
2112            '       Time averaged over       ',F8.2,' s'/ &
2113            '       Averaging input every    ',F8.2,' s')
2114334 FORMAT (/'    2D-Arrays',A,':')
2115335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2116            '       Output every             ',F8.2,' s  ',A/ &
2117            '       Cross sections at ',A1,' = ',A/ &
2118            '       scalar-coordinates:   ',A,' m'/)
2119336 FORMAT (/'    3D-Arrays',A,':')
2120337 FORMAT (/'       Arrays: ',A/ &
2121            '       Output every             ',F8.2,' s  ',A/ &
2122            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2123339 FORMAT ('       No output during initial ',F8.2,' s')
2124340 FORMAT (/'    Time series:')
2125341 FORMAT ('       Output every             ',F8.2,' s'/)
2126342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2127            '       Output every             ',F8.2,' s  ',A/ &
2128            '       Time averaged over       ',F8.2,' s'/ &
2129            '       Averaging input every    ',F8.2,' s'/ &
2130            '       Cross sections at ',A1,' = ',A/ &
2131            '       scalar-coordinates:   ',A,' m'/)
2132343 FORMAT (/'       Arrays: ',A/ &
2133            '       Output every             ',F8.2,' s  ',A/ &
2134            '       Time averaged over       ',F8.2,' s'/ &
2135            '       Averaging input every    ',F8.2,' s'/ &
2136            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2137344 FORMAT ('       Output format: ',A/)
2138345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2139            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2140            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2141            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2142346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2143347 FORMAT ('       Variables: ',A/ &
2144            '       Output every             ',F8.2,' s')
2145348 FORMAT ('       Variables: ',A/ &
2146            '       Output every             ',F8.2,' s'/ &
2147            '       Time averaged over       ',F8.2,' s'/ &
2148            '       Averaging input every    ',F8.2,' s')
2149349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2150            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2151            13('       ',8(F8.2,',')/) )
2152350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2153            'all gridpoints along ',A,'-direction (default).' )
2154351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2155            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2156            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
2157352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2158353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
2159#if defined( __dvrp_graphics )
2160360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2161            '       Output every      ',F7.1,' s'/ &
2162            '       Output mode:      ',A/ &
2163            '       Host / User:      ',A,' / ',A/ &
2164            '       Directory:        ',A// &
2165            '       The sequence contains:')
2166361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2167            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2168362 FORMAT (/'       Slicer plane ',A/ &
2169            '       Slicer limits: [',F6.2,',',F6.2,']')
2170363 FORMAT (/'       Particles'/ &
2171            '          particle size:  ',F7.2,' m')
2172364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
2173                       F6.2,',',F6.2,']')
2174365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
2175            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2176                     ')'/ &
2177            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2178            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
2179366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2180367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
2181#endif
2182#if defined( __spectra )
2183370 FORMAT ('    Spectra:')
2184371 FORMAT ('       Output every ',F7.1,' s'/)
2185372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
2186            '       Directions: ', 10(A5,',')/                         &
2187            '       height levels  k = ', 20(I3,',')/                  &
2188            '                          ', 20(I3,',')/                  &
2189            '                          ', 20(I3,',')/                  &
2190            '                          ', 20(I3,',')/                  &
2191            '                          ', 19(I3,','),I3,'.'/           &
2192            '       height levels selected for standard plot:'/        &
2193            '                      k = ', 20(I3,',')/                  &
2194            '                          ', 20(I3,',')/                  &
2195            '                          ', 20(I3,',')/                  &
2196            '                          ', 20(I3,',')/                  &
2197            '                          ', 19(I3,','),I3,'.'/           &
2198            '       Time averaged over ', F7.1, ' s,' /                &
2199            '       Profiles for the time averaging are taken every ', &
2200                    F6.1,' s')
2201#endif
2202400 FORMAT (//' Physical quantities:'/ &
2203              ' -------------------'/)
2204410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
2205            '    Angular velocity    :   omega  = ',E9.3,' rad/s'/  &
2206            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2207            '                            f*     = ',F9.6,' 1/s')
2208411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
2209412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2210413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2211414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2212415 FORMAT (/' Cloud physics parameters:'/ &
2213             ' ------------------------'/)
2214416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2215            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2216            '    Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
2217            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2218            '    Vapourization heat :   L_v   = ',E8.2,' J/kg')
2219417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2220418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2221            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2222419 FORMAT (//' Land surface model information:'/ &
2223              ' ------------------------------'/)
2224420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2225            '       Height:        ',A,'  m'/ &
2226            '       Temperature:   ',A,'  K'/ &
2227            '       Gradient:      ',A,'  K/100m'/ &
2228            '       Gridpoint:     ',A)
2229421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2230            '       Height:      ',A,'  m'/ &
2231            '       Humidity:    ',A,'  kg/kg'/ &
2232            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2233            '       Gridpoint:   ',A)
2234422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2235            '       Height:                  ',A,'  m'/ &
2236            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2237            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2238            '       Gridpoint:               ',A)
2239423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2240            '       Height:      ',A,'  m'/ &
2241            '       ug:          ',A,'  m/s'/ &
2242            '       Gradient:    ',A,'  1/100s'/ &
2243            '       Gridpoint:   ',A)
2244424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2245            '       Height:      ',A,'  m'/ &
2246            '       vg:          ',A,'  m/s'/ &
2247            '       Gradient:    ',A,'  1/100s'/ &
2248            '       Gridpoint:   ',A)
2249425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2250            '       Height:     ',A,'  m'/ &
2251            '       Salinity:   ',A,'  psu'/ &
2252            '       Gradient:   ',A,'  psu/100m'/ &
2253            '       Gridpoint:  ',A)
2254426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2255            '       Height:      ',A,'  m'/ &
2256            '       w_subs:      ',A,'  m/s'/ &
2257            '       Gradient:    ',A,'  (m/s)/100m'/ &
2258            '       Gridpoint:   ',A)
2259427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2260                  ' profiles')
2261428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2262             '    NUDGING_DATA')
2263430 FORMAT (//' Cloud physics quantities / methods:'/ &
2264              ' ----------------------------------'/)
2265431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2266                 'on)')
2267432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2268            '    total water content is used.'/ &
2269            '    Condensation is parameterized via 0% - or 100% scheme.')
2270433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2271                 'icle model')
2272434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2273                 ' droplets < 1.0E-6 m')
2274435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2275436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2276                    'are used'/ &
2277            '          number of radius classes:       ',I3,'    interval ', &
2278                       '[1.0E-6,2.0E-4] m'/ &
2279            '          number of dissipation classes:   ',I2,'    interval ', &
2280                       '[0,1000] cm**2/s**3')
2281437 FORMAT ('    Droplet collision is switched off')
2282438 FORMAT (' --> Land surface type  : ',A,/ &
2283            ' --> Soil porosity type : ',A)
2284439 FORMAT (/'    Initial soil temperature and moisture profile:'// &
2285            '       Height:        ',A,'  m'/ &
2286            '       Temperature:   ',A,'  K'/ &
2287            '       Moisture:      ',A,'  m**3/m**3'/ &
2288            '       Root fraction: ',A,'  '/ &
2289            '       Gridpoint:     ',A)
2290440 FORMAT (/' --> Dewfall is allowed (default)')
2291441 FORMAT (' --> Dewfall is inhibited')
2292442 FORMAT (' --> Soil bottom is closed (water content is conserved, default)')
2293443 FORMAT (' --> Soil bottom is open (water content is not conserved)')
2294444 FORMAT (//' Radiation model information:'/                                 &
2295              ' ----------------------------'/)
2296445 FORMAT (' --> Using constant net radiation: net_radiation = ', F6.2, '  W/m**2')
2297446 FORMAT (' --> Simple radiation scheme for clear sky is used (no clouds,',  &
2298                   ' default)')
2299447 FORMAT (' --> RRTMG scheme is used')
2300448 FORMAT (/'     User-specific surface albedo: albedo = ', F5.3)
2301449 FORMAT  ('     Timestep: dt_radiation = ', F5.2, '  s')
2302
2303450 FORMAT (//' LES / Turbulence quantities:'/ &
2304              ' ---------------------------'/)
2305451 FORMAT ('    Diffusion coefficients are constant:'/ &
2306            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2307453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2308454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2309455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2310456 FORMAT (/'    Albedo is set for land surface type: ', A)
2311457 FORMAT (/'    --> Albedo is fixed during the run')
2312458 FORMAT (/'    --> Longwave radiation is disabled')
2313459 FORMAT (/'    --> Shortwave radiation is disabled.')
2314470 FORMAT (//' Actions during the simulation:'/ &
2315              ' -----------------------------'/)
2316471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2317            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2318            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2319            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2320472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2321                 ' to i/j =',I4)
2322473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2323                 1X,F5.3, ' m**2/s**2')
2324474 FORMAT ('    Random number generator used    : ',A/)
2325475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2326                 'respectively, if'/ &
2327            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2328                 ' 3D-simulation'/)
2329476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2330                 'respectively, if the'/ &
2331            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2332                 ' the 3D-simulation'/)
2333477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2334                 'respectively, if the'/ &
2335            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2336                 ' the 3D-simulation'/)
2337480 FORMAT ('    Particles:'/ &
2338            '    ---------'// &
2339            '       Particle advection is active (switched on at t = ', F7.1, &
2340                    ' s)'/ &
2341            '       Start of new particle generations every  ',F6.1,' s'/ &
2342            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2343            '                            bottom:     ', A, ' top:         ', A/&
2344            '       Maximum particle age:                 ',F9.1,' s'/ &
2345            '       Advection stopped at t = ',F9.1,' s'/)
2346481 FORMAT ('       Particles have random start positions'/)
2347482 FORMAT ('          Particles are advected only horizontally'/)
2348483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2349484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2350            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2351            '            Maximum age of the end of the tail:  ',F8.2,' s')
2352485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2353486 FORMAT ('       Particle statistics are written on file'/)
2354487 FORMAT ('       Number of particle groups: ',I2/)
2355488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2356            '          minimum timestep for advection: ', F7.5/)
2357489 FORMAT ('       Number of particles simultaneously released at each ', &
2358                    'point: ', I5/)
2359490 FORMAT ('       Particle group ',I2,':'/ &
2360            '          Particle radius: ',E10.3, 'm')
2361491 FORMAT ('          Particle inertia is activated'/ &
2362            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2363492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2364493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2365            '                                         y:',F8.1,' - ',F8.1,' m'/&
2366            '                                         z:',F8.1,' - ',F8.1,' m'/&
2367            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2368                       ' m  dz = ',F8.1,' m'/)
2369494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2370                    F8.2,' s'/)
2371495 FORMAT ('       Number of particles in total domain: ',I10/)
2372496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2373                    'as relative to the given topography')
2374500 FORMAT (//' 1D-Model parameters:'/                           &
2375              ' -------------------'//                           &
2376            '    Simulation time:                   ',F8.1,' s'/ &
2377            '    Run-controll output every:         ',F8.1,' s'/ &
2378            '    Vertical profile output every:     ',F8.1,' s'/ &
2379            '    Mixing length calculation:         ',A/         &
2380            '    Dissipation calculation:           ',A/)
2381502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2382503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2383504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2384505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2385506 FORMAT ('    Drizzle parameterization via Stokes law')
2386507 FORMAT ('    Turbulence effects on precipitation process')
2387508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2388509 FORMAT ('    Slope limiter used for sedimentation process')
2389510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2390511 FORMAT ('    Sedimentation Courant number:                  '/&
2391            '                               C_s   = ',F3.1,'        ')
2392512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2393            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2394            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2395513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2396            '+ monotonic adjustment')
2397
2398
2399 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.