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

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

last commit documented

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