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

Last change on this file since 1691 was 1691, checked in by maronga, 9 years ago

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

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