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

Last change on this file since 1676 was 1676, checked in by gronemeier, 9 years ago

last commit documented

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