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

Last change on this file since 1575 was 1575, checked in by raasch, 9 years ago

optimized multigrid method installed, new parameter seed_follows_topography for particle release, small adjustment in subjob for HLRN

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