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

Last change on this file since 1683 was 1683, checked in by knoop, 9 years ago

last commit documented

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