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

Last change on this file since 1469 was 1469, checked in by maronga, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 82.7 KB
Line 
1 SUBROUTINE header
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 1469 2014-09-24 14:09:56Z maronga $
27!
28! 1468 2014-09-24 14:06:57Z maronga
29! Adapted for use on up to 6-digit processor cores
30!
31! 1429 2014-07-15 12:53:45Z knoop
32! header exended to provide ensemble_member_nr if specified
33!
34! 1376 2014-04-26 11:21:22Z boeske
35! Correction of typos
36!
37! 1365 2014-04-22 15:03:56Z boeske
38! New section 'Large scale forcing and nudging':
39! output of large scale forcing and nudging information,
40! new section for initial profiles created
41!
42! 1359 2014-04-11 17:15:14Z hoffmann
43! dt_sort_particles removed
44!
45! 1353 2014-04-08 15:21:23Z heinze
46! REAL constants provided with KIND-attribute
47!
48! 1327 2014-03-21 11:00:16Z raasch
49! parts concerning iso2d and avs output removed,
50! -netcdf output queries
51!
52! 1324 2014-03-21 09:13:16Z suehring
53! Bugfix: module spectrum added
54!
55! 1322 2014-03-20 16:38:49Z raasch
56! REAL functions provided with KIND-attribute,
57! some REAL constants defined as wp-kind
58!
59! 1320 2014-03-20 08:40:49Z raasch
60! ONLY-attribute added to USE-statements,
61! kind-parameters added to all INTEGER and REAL declaration statements,
62! kinds are defined in new module kinds,
63! revision history before 2012 removed,
64! comment fields (!:) to be used for variable explanations added to
65! all variable declaration statements
66!
67! 1308 2014-03-13 14:58:42Z fricke
68! output of the fixed number of output time levels
69! output_format adjusted for masked data if netcdf_data_format > 5
70!
71! 1299 2014-03-06 13:15:21Z heinze
72! output for using large_scale subsidence in combination
73! with large_scale_forcing
74! reformatting, more detailed explanations
75!
76! 1241 2013-10-30 11:36:58Z heinze
77! output for nudging + large scale forcing from external file
78!
79! 1216 2013-08-26 09:31:42Z raasch
80! output for transpose_compute_overlap
81!
82! 1212 2013-08-15 08:46:27Z raasch
83! output for poisfft_hybrid removed
84!
85! 1179 2013-06-14 05:57:58Z raasch
86! output of reference_state, use_reference renamed use_single_reference_value
87!
88! 1159 2013-05-21 11:58:22Z fricke
89! +use_cmax
90!
91! 1115 2013-03-26 18:16:16Z hoffmann
92! descriptions for Seifert-Beheng-cloud-physics-scheme added
93!
94! 1111 2013-03-08 23:54:10Z raasch
95! output of accelerator board information
96! ibc_p_b = 2 removed
97!
98! 1108 2013-03-05 07:03:32Z raasch
99! bugfix for r1106
100!
101! 1106 2013-03-04 05:31:38Z raasch
102! some format changes for coupled runs
103!
104! 1092 2013-02-02 11:24:22Z raasch
105! unused variables removed
106!
107! 1036 2012-10-22 13:43:42Z raasch
108! code put under GPL (PALM 3.9)
109!
110! 1031 2012-10-19 14:35:30Z raasch
111! output of netCDF data format modified
112!
113! 1015 2012-09-27 09:23:24Z raasch
114! output of Adjustment of mixing length to the Prandtl mixing length at first
115! grid point above ground removed
116!
117! 1003 2012-09-14 14:35:53Z raasch
118! output of information about equal/unequal subdomain size removed
119!
120! 1001 2012-09-13 14:08:46Z raasch
121! all actions concerning leapfrog- and upstream-spline-scheme removed
122!
123! 978 2012-08-09 08:28:32Z fricke
124! -km_damp_max, outflow_damping_width
125! +pt_damping_factor, pt_damping_width
126! +z0h
127!
128! 964 2012-07-26 09:14:24Z raasch
129! output of profil-related quantities removed
130!
131! 940 2012-07-09 14:31:00Z raasch
132! Output in case of simulations for pure neutral stratification (no pt-equation
133! solved)
134!
135! 927 2012-06-06 19:15:04Z raasch
136! output of masking_method for mg-solver
137!
138! 868 2012-03-28 12:21:07Z raasch
139! translation velocity in Galilean transformation changed to 0.6 * ug
140!
141! 833 2012-02-22 08:55:55Z maronga
142! Adjusted format for leaf area density
143!
144! 828 2012-02-21 12:00:36Z raasch
145! output of dissipation_classes + radius_classes
146!
147! 825 2012-02-19 03:03:44Z raasch
148! Output of cloud physics parameters/quantities complemented and restructured
149!
150! Revision 1.1  1997/08/11 06:17:20  raasch
151! Initial revision
152!
153!
154! Description:
155! ------------
156! Writing a header with all important informations about the actual run.
157! This subroutine is called three times, two times at the beginning
158! (writing information on files RUN_CONTROL and HEADER) and one time at the
159! end of the run, then writing additional information about CPU-usage on file
160! header.
161!-----------------------------------------------------------------------------!
162
163    USE arrays_3d,                                                             &
164        ONLY:  lad, pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
165       
166    USE control_parameters
167       
168    USE cloud_parameters,                                                      &
169        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
170               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
171       
172    USE cpulog,                                                                &
173        ONLY:  log_point_s
174       
175    USE dvrp_variables,                                                        &
176        ONLY:  use_seperate_pe_for_dvrp_output
177       
178    USE grid_variables,                                                        &
179        ONLY:  dx, dy
180       
181    USE indices,                                                               &
182        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
183               nys_mg, nzt, nzt_mg
184       
185    USE kinds
186   
187    USE model_1d,                                                              &
188        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
189       
190    USE particle_attributes,                                                   &
191        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
192               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
193               dt_write_particle_data, end_time_prel,                          &
194               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
195               minimum_tailpoint_distance, number_of_particle_groups,          &
196               particle_advection, particle_advection_start,                   &
197               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
198               pst, radius, radius_classes, random_start_position,             &
199               total_number_of_particles, use_particle_tails,                  &
200               use_sgs_for_particles, total_number_of_tails,                   &
201               vertical_particle_advection, write_particle_statistics
202       
203    USE pegrid
204   
205    USE spectrum,                                                              &
206        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
207               spectra_direction
208
209    IMPLICIT NONE
210
211    CHARACTER (LEN=1)  ::  prec                !:
212   
213    CHARACTER (LEN=2)  ::  do2d_mode           !:
214   
215    CHARACTER (LEN=5)  ::  section_chr         !:
216   
217    CHARACTER (LEN=10) ::  coor_chr            !:
218    CHARACTER (LEN=10) ::  host_chr            !:
219   
220    CHARACTER (LEN=16) ::  begin_chr           !:
221   
222    CHARACTER (LEN=26) ::  ver_rev             !:
223   
224    CHARACTER (LEN=40) ::  output_format       !:
225   
226    CHARACTER (LEN=70) ::  char1               !:
227    CHARACTER (LEN=70) ::  char2               !:
228    CHARACTER (LEN=70) ::  dopr_chr            !:
229    CHARACTER (LEN=70) ::  do2d_xy             !:
230    CHARACTER (LEN=70) ::  do2d_xz             !:
231    CHARACTER (LEN=70) ::  do2d_yz             !:
232    CHARACTER (LEN=70) ::  do3d_chr            !:
233    CHARACTER (LEN=70) ::  domask_chr          !:
234    CHARACTER (LEN=70) ::  run_classification  !:
235   
236    CHARACTER (LEN=85) ::  roben               !:
237    CHARACTER (LEN=85) ::  runten              !:
238   
239    CHARACTER (LEN=86) ::  coordinates         !:
240    CHARACTER (LEN=86) ::  gradients           !:
241    CHARACTER (LEN=86) ::  learde              !:
242    CHARACTER (LEN=86) ::  slices              !:
243    CHARACTER (LEN=86) ::  temperatures        !:
244    CHARACTER (LEN=86) ::  ugcomponent         !:
245    CHARACTER (LEN=86) ::  vgcomponent         !:
246
247    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
248
249    INTEGER(iwp) ::  av        !:
250    INTEGER(iwp) ::  bh        !:
251    INTEGER(iwp) ::  blx       !:
252    INTEGER(iwp) ::  bly       !:
253    INTEGER(iwp) ::  bxl       !:
254    INTEGER(iwp) ::  bxr       !:
255    INTEGER(iwp) ::  byn       !:
256    INTEGER(iwp) ::  bys       !:
257    INTEGER(iwp) ::  ch        !:
258    INTEGER(iwp) ::  count     !:
259    INTEGER(iwp) ::  cwx       !:
260    INTEGER(iwp) ::  cwy       !:
261    INTEGER(iwp) ::  cxl       !:
262    INTEGER(iwp) ::  cxr       !:
263    INTEGER(iwp) ::  cyn       !:
264    INTEGER(iwp) ::  cys       !:
265    INTEGER(iwp) ::  dim       !:
266    INTEGER(iwp) ::  i         !:
267    INTEGER(iwp) ::  io        !:
268    INTEGER(iwp) ::  j         !:
269    INTEGER(iwp) ::  l         !:
270    INTEGER(iwp) ::  ll        !:
271    INTEGER(iwp) ::  mpi_type  !:
272   
273    REAL(wp) ::  cpuseconds_per_simulated_second  !:
274
275!
276!-- Open the output file. At the end of the simulation, output is directed
277!-- to unit 19.
278    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
279         .NOT. simulated_time_at_begin /= simulated_time )  THEN
280       io = 15   !  header output on file RUN_CONTROL
281    ELSE
282       io = 19   !  header output on file HEADER
283    ENDIF
284    CALL check_open( io )
285
286!
287!-- At the end of the run, output file (HEADER) will be rewritten with
288!-- new informations
289    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
290
291!
292!-- Determine kind of model run
293    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
294       run_classification = '3D - restart run'
295    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
296       run_classification = '3D - run with cyclic fill of 3D - prerun data'
297    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
298       run_classification = '3D - run without 1D - prerun'
299    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
300       run_classification = '3D - run with 1D - prerun'
301    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
302       run_classification = '3D - run initialized by user'
303    ELSE
304       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
305       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
306    ENDIF
307    IF ( ocean )  THEN
308       run_classification = 'ocean - ' // run_classification
309    ELSE
310       run_classification = 'atmosphere - ' // run_classification
311    ENDIF
312
313!
314!-- Run-identification, date, time, host
315    host_chr = host(1:10)
316    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
317    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
318    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
319#if defined( __mpi2 )
320       mpi_type = 2
321#else
322       mpi_type = 1
323#endif
324       WRITE ( io, 101 )  mpi_type, coupling_mode
325    ENDIF
326#if defined( __parallel )
327    IF ( coupling_start_time /= 0.0_wp )  THEN
328       IF ( coupling_start_time > simulated_time_at_begin )  THEN
329          WRITE ( io, 109 )
330       ELSE
331          WRITE ( io, 114 )
332       ENDIF
333    ENDIF
334#endif
335    IF ( ensemble_member_nr /= 0 )  THEN
336       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
337                       ADJUSTR( host_chr ), ensemble_member_nr
338    ELSE
339       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
340                       ADJUSTR( host_chr )
341    ENDIF
342#if defined( __parallel )
343    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
344       char1 = 'calculated'
345    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
346               host(1:2) == 'lc' )  .AND.                          &
347             npex == -1  .AND.  pdims(2) == 1 )  THEN
348       char1 = 'forced'
349    ELSE
350       char1 = 'predefined'
351    ENDIF
352    IF ( threads_per_task == 1 )  THEN
353       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
354    ELSE
355       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
356                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
357    ENDIF
358    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
359    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
360           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
361         npex == -1  .AND.  pdims(2) == 1 )                      &
362    THEN
363       WRITE ( io, 106 )
364    ELSEIF ( pdims(2) == 1 )  THEN
365       WRITE ( io, 107 )  'x'
366    ELSEIF ( pdims(1) == 1 )  THEN
367       WRITE ( io, 107 )  'y'
368    ENDIF
369    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
370    IF ( numprocs /= maximum_parallel_io_streams )  THEN
371       WRITE ( io, 108 )  maximum_parallel_io_streams
372    ENDIF
373#else
374    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
375#endif
376    WRITE ( io, 99 )
377
378!
379!-- Numerical schemes
380    WRITE ( io, 110 )
381    IF ( psolver(1:7) == 'poisfft' )  THEN
382       WRITE ( io, 111 )  TRIM( fft_method )
383       IF ( transpose_compute_overlap )  WRITE( io, 115 )
384    ELSEIF ( psolver == 'sor' )  THEN
385       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
386    ELSEIF ( psolver == 'multigrid' )  THEN
387       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
388       IF ( mg_cycles == -1 )  THEN
389          WRITE ( io, 140 )  residual_limit
390       ELSE
391          WRITE ( io, 141 )  mg_cycles
392       ENDIF
393       IF ( mg_switch_to_pe0_level == 0 )  THEN
394          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
395                             nzt_mg(1)
396       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
397          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
398                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
399                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
400                             nzt_mg(mg_switch_to_pe0_level),    &
401                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
402                             nzt_mg(1)
403       ENDIF
404       IF ( masking_method )  WRITE ( io, 144 )
405    ENDIF
406    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
407    THEN
408       WRITE ( io, 142 )
409    ENDIF
410
411    IF ( momentum_advec == 'pw-scheme' )  THEN
412       WRITE ( io, 113 )
413    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
414       WRITE ( io, 503 )
415    ENDIF
416    IF ( scalar_advec == 'pw-scheme' )  THEN
417       WRITE ( io, 116 )
418    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
419       WRITE ( io, 504 )
420    ELSE
421       WRITE ( io, 118 )
422    ENDIF
423
424    WRITE ( io, 139 )  TRIM( loop_optimization )
425
426    IF ( galilei_transformation )  THEN
427       IF ( use_ug_for_galilei_tr )  THEN
428          char1 = '0.6 * geostrophic wind'
429       ELSE
430          char1 = 'mean wind in model domain'
431       ENDIF
432       IF ( simulated_time_at_begin == simulated_time )  THEN
433          char2 = 'at the start of the run'
434       ELSE
435          char2 = 'at the end of the run'
436       ENDIF
437       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
438                          advected_distance_x/1000.0_wp,                       &
439                          advected_distance_y/1000.0_wp
440    ENDIF
441    WRITE ( io, 122 )  timestep_scheme
442    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
443    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
444       IF ( .NOT. ocean )  THEN
445          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
446               rayleigh_damping_factor
447       ELSE
448          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
449               rayleigh_damping_factor
450       ENDIF
451    ENDIF
452    IF ( neutral )  WRITE ( io, 131 )  pt_surface
453    IF ( humidity )  THEN
454       IF ( .NOT. cloud_physics )  THEN
455          WRITE ( io, 129 )
456       ELSE
457          WRITE ( io, 130 )
458       ENDIF
459    ENDIF
460    IF ( passive_scalar )  WRITE ( io, 134 )
461    IF ( conserve_volume_flow )  THEN
462       WRITE ( io, 150 )  conserve_volume_flow_mode
463       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
464          WRITE ( io, 151 )  u_bulk, v_bulk
465       ENDIF
466    ELSEIF ( dp_external )  THEN
467       IF ( dp_smooth )  THEN
468          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
469       ELSE
470          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
471       ENDIF
472    ENDIF
473    WRITE ( io, 99 )
474
475!
476!-- Runtime and timestep informations
477    WRITE ( io, 200 )
478    IF ( .NOT. dt_fixed )  THEN
479       WRITE ( io, 201 )  dt_max, cfl_factor
480    ELSE
481       WRITE ( io, 202 )  dt
482    ENDIF
483    WRITE ( io, 203 )  simulated_time_at_begin, end_time
484
485    IF ( time_restart /= 9999999.9_wp  .AND. &
486         simulated_time_at_begin == simulated_time )  THEN
487       IF ( dt_restart == 9999999.9_wp )  THEN
488          WRITE ( io, 204 )  ' Restart at:       ',time_restart
489       ELSE
490          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
491       ENDIF
492    ENDIF
493
494    IF ( simulated_time_at_begin /= simulated_time )  THEN
495       i = MAX ( log_point_s(10)%counts, 1 )
496       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
497          cpuseconds_per_simulated_second = 0.0_wp
498       ELSE
499          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
500                                            ( simulated_time -    &
501                                              simulated_time_at_begin )
502       ENDIF
503       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
504                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
505                          cpuseconds_per_simulated_second
506       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
507          IF ( dt_restart == 9999999.9_wp )  THEN
508             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
509          ELSE
510             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
511          ENDIF
512       ENDIF
513    ENDIF
514
515
516!
517!-- Start time for coupled runs, if independent precursor runs for atmosphere
518!-- and ocean are used or have been used. In this case, coupling_start_time
519!-- defines the time when the coupling is switched on.
520    IF ( coupling_start_time /= 0.0_wp )  THEN
521       WRITE ( io, 207 )  coupling_start_time
522    ENDIF
523
524!
525!-- Computational grid
526    IF ( .NOT. ocean )  THEN
527       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
528       IF ( dz_stretch_level_index < nzt+1 )  THEN
529          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
530                             dz_stretch_factor, dz_max
531       ENDIF
532    ELSE
533       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
534       IF ( dz_stretch_level_index > 0 )  THEN
535          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
536                             dz_stretch_factor, dz_max
537       ENDIF
538    ENDIF
539    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
540                       MIN( nnz+2, nzt+2 )
541    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
542
543!
544!-- Large scale forcing and nudging
545    WRITE ( io, 160 )
546    IF ( large_scale_forcing )  THEN
547       WRITE ( io, 162 )
548       WRITE ( io, 163 )
549
550       IF ( large_scale_subsidence )  THEN
551          IF ( .NOT. use_subsidence_tendencies )  THEN
552             WRITE ( io, 164 )
553          ELSE
554             WRITE ( io, 165 )
555          ENDIF
556       ENDIF
557
558       IF ( bc_pt_b == 'dirichlet' )  THEN
559          WRITE ( io, 180 )
560       ELSEIF ( bc_pt_b == 'neumann' )  THEN
561          WRITE ( io, 181 )
562       ENDIF
563
564       IF ( bc_q_b == 'dirichlet' )  THEN
565          WRITE ( io, 182 )
566       ELSEIF ( bc_q_b == 'neumann' )  THEN
567          WRITE ( io, 183 )
568       ENDIF
569
570       WRITE ( io, 167 )
571       IF ( nudging )  THEN
572          WRITE ( io, 170 )
573       ENDIF
574    ELSE
575       WRITE ( io, 161 )
576       WRITE ( io, 171 )
577    ENDIF
578    IF ( large_scale_subsidence )  THEN
579       WRITE ( io, 168 )
580       WRITE ( io, 169 )
581    ENDIF
582
583!
584!-- Profile for the large scale vertial velocity
585!-- Building output strings, starting with surface value
586    IF ( large_scale_subsidence )  THEN
587       temperatures = '   0.0'
588       gradients = '------'
589       slices = '     0'
590       coordinates = '   0.0'
591       i = 1
592       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
593
594          WRITE (coor_chr,'(E10.2,7X)')  &
595                                w_subs(subs_vertical_gradient_level_i(i))
596          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
597
598          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
599          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
600
601          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
602          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
603
604          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
605          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
606
607          IF ( i == 10 )  THEN
608             EXIT
609          ELSE
610             i = i + 1
611          ENDIF
612
613       ENDDO
614
615 
616       IF ( .NOT. large_scale_forcing )  THEN
617          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
618                             TRIM( gradients ), TRIM( slices )
619       ENDIF
620
621
622    ENDIF
623
624!-- Profile of the geostrophic wind (component ug)
625!-- Building output strings
626    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
627    gradients = '------'
628    slices = '     0'
629    coordinates = '   0.0'
630    i = 1
631    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
632     
633       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
634       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
635
636       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
637       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
638
639       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
640       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
641
642       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
643       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
644
645       IF ( i == 10 )  THEN
646          EXIT
647       ELSE
648          i = i + 1
649       ENDIF
650
651    ENDDO
652
653    IF ( .NOT. large_scale_forcing )  THEN
654       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
655                          TRIM( gradients ), TRIM( slices )
656    ENDIF
657
658!-- Profile of the geostrophic wind (component vg)
659!-- Building output strings
660    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
661    gradients = '------'
662    slices = '     0'
663    coordinates = '   0.0'
664    i = 1
665    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
666
667       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
668       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
669
670       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
671       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
672
673       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
674       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
675
676       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
677       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
678
679       IF ( i == 10 )  THEN
680          EXIT
681       ELSE
682          i = i + 1
683       ENDIF
684 
685    ENDDO
686
687    IF ( .NOT. large_scale_forcing )  THEN
688       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
689                          TRIM( gradients ), TRIM( slices )
690    ENDIF
691
692!
693!-- Topography
694    WRITE ( io, 270 )  topography
695    SELECT CASE ( TRIM( topography ) )
696
697       CASE ( 'flat' )
698          ! no actions necessary
699
700       CASE ( 'single_building' )
701          blx = INT( building_length_x / dx )
702          bly = INT( building_length_y / dy )
703          bh  = INT( building_height / dz )
704
705          IF ( building_wall_left == 9999999.9_wp )  THEN
706             building_wall_left = ( nx + 1 - blx ) / 2 * dx
707          ENDIF
708          bxl = INT ( building_wall_left / dx + 0.5_wp )
709          bxr = bxl + blx
710
711          IF ( building_wall_south == 9999999.9_wp )  THEN
712             building_wall_south = ( ny + 1 - bly ) / 2 * dy
713          ENDIF
714          bys = INT ( building_wall_south / dy + 0.5_wp )
715          byn = bys + bly
716
717          WRITE ( io, 271 )  building_length_x, building_length_y, &
718                             building_height, bxl, bxr, bys, byn
719
720       CASE ( 'single_street_canyon' )
721          ch  = NINT( canyon_height / dz )
722          IF ( canyon_width_x /= 9999999.9_wp )  THEN
723!
724!--          Street canyon in y direction
725             cwx = NINT( canyon_width_x / dx )
726             IF ( canyon_wall_left == 9999999.9_wp )  THEN
727                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
728             ENDIF
729             cxl = NINT( canyon_wall_left / dx )
730             cxr = cxl + cwx
731             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
732
733          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
734!
735!--          Street canyon in x direction
736             cwy = NINT( canyon_width_y / dy )
737             IF ( canyon_wall_south == 9999999.9_wp )  THEN
738                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
739             ENDIF
740             cys = NINT( canyon_wall_south / dy )
741             cyn = cys + cwy
742             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
743          ENDIF
744
745    END SELECT
746
747    IF ( TRIM( topography ) /= 'flat' )  THEN
748       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
749          IF ( TRIM( topography ) == 'single_building' .OR.  &
750               TRIM( topography ) == 'single_street_canyon' )  THEN
751             WRITE ( io, 278 )
752          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
753             WRITE ( io, 279 )
754          ENDIF
755       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
756          WRITE ( io, 278 )
757       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
758          WRITE ( io, 279 )
759       ENDIF
760    ENDIF
761
762    IF ( plant_canopy )  THEN
763
764       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
765       IF ( passive_scalar )  THEN
766          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
767                            leaf_surface_concentration
768       ENDIF
769
770!
771!--    Heat flux at the top of vegetation
772       WRITE ( io, 282 ) cthf
773
774!
775!--    Leaf area density profile
776!--    Building output strings, starting with surface value
777       WRITE ( learde, '(F6.4)' )  lad_surface
778       gradients = '------'
779       slices = '     0'
780       coordinates = '   0.0'
781       i = 1
782       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
783
784          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
785          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
786
787          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
788          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
789
790          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
791          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
792
793          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
794          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
795
796          i = i + 1
797       ENDDO
798
799       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
800                          TRIM( gradients ), TRIM( slices )
801
802    ENDIF
803
804!
805!-- Boundary conditions
806    IF ( ibc_p_b == 0 )  THEN
807       runten = 'p(0)     = 0      |'
808    ELSEIF ( ibc_p_b == 1 )  THEN
809       runten = 'p(0)     = p(1)   |'
810    ENDIF
811    IF ( ibc_p_t == 0 )  THEN
812       roben  = 'p(nzt+1) = 0      |'
813    ELSE
814       roben  = 'p(nzt+1) = p(nzt) |'
815    ENDIF
816
817    IF ( ibc_uv_b == 0 )  THEN
818       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
819    ELSE
820       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
821    ENDIF
822    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
823       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
824    ELSEIF ( ibc_uv_t == 0 )  THEN
825       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
826    ELSE
827       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
828    ENDIF
829
830    IF ( ibc_pt_b == 0 )  THEN
831       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
832    ELSEIF ( ibc_pt_b == 1 )  THEN
833       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
834    ELSEIF ( ibc_pt_b == 2 )  THEN
835       runten = TRIM( runten ) // ' pt(0) = from coupled model'
836    ENDIF
837    IF ( ibc_pt_t == 0 )  THEN
838       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
839    ELSEIF( ibc_pt_t == 1 )  THEN
840       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
841    ELSEIF( ibc_pt_t == 2 )  THEN
842       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
843
844    ENDIF
845
846    WRITE ( io, 300 )  runten, roben
847
848    IF ( .NOT. constant_diffusion )  THEN
849       IF ( ibc_e_b == 1 )  THEN
850          runten = 'e(0)     = e(1)'
851       ELSE
852          runten = 'e(0)     = e(1) = (u*/0.1)**2'
853       ENDIF
854       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
855
856       WRITE ( io, 301 )  'e', runten, roben       
857
858    ENDIF
859
860    IF ( ocean )  THEN
861       runten = 'sa(0)    = sa(1)'
862       IF ( ibc_sa_t == 0 )  THEN
863          roben =  'sa(nzt+1) = sa_surface'
864       ELSE
865          roben =  'sa(nzt+1) = sa(nzt)'
866       ENDIF
867       WRITE ( io, 301 ) 'sa', runten, roben
868    ENDIF
869
870    IF ( humidity )  THEN
871       IF ( ibc_q_b == 0 )  THEN
872          runten = 'q(0)     = q_surface'
873       ELSE
874          runten = 'q(0)     = q(1)'
875       ENDIF
876       IF ( ibc_q_t == 0 )  THEN
877          roben =  'q(nzt)   = q_top'
878       ELSE
879          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
880       ENDIF
881       WRITE ( io, 301 ) 'q', runten, roben
882    ENDIF
883
884    IF ( passive_scalar )  THEN
885       IF ( ibc_q_b == 0 )  THEN
886          runten = 's(0)     = s_surface'
887       ELSE
888          runten = 's(0)     = s(1)'
889       ENDIF
890       IF ( ibc_q_t == 0 )  THEN
891          roben =  's(nzt)   = s_top'
892       ELSE
893          roben =  's(nzt)   = s(nzt-1) + ds/dz'
894       ENDIF
895       WRITE ( io, 301 ) 's', runten, roben
896    ENDIF
897
898    IF ( use_surface_fluxes )  THEN
899       WRITE ( io, 303 )
900       IF ( constant_heatflux )  THEN
901          IF ( large_scale_forcing .AND. lsf_surf )  THEN
902             WRITE ( io, 306 )  shf(0,0)
903          ELSE
904             WRITE ( io, 306 )  surface_heatflux
905          ENDIF
906          IF ( random_heatflux )  WRITE ( io, 307 )
907       ENDIF
908       IF ( humidity  .AND.  constant_waterflux )  THEN
909          IF ( large_scale_forcing .AND. lsf_surf )  THEN
910             WRITE ( io, 311 ) qsws(0,0)
911          ELSE
912             WRITE ( io, 311 ) surface_waterflux
913          ENDIF
914       ENDIF
915       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
916          WRITE ( io, 313 ) surface_waterflux
917       ENDIF
918    ENDIF
919
920    IF ( use_top_fluxes )  THEN
921       WRITE ( io, 304 )
922       IF ( coupling_mode == 'uncoupled' )  THEN
923          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
924          IF ( constant_top_heatflux )  THEN
925             WRITE ( io, 306 )  top_heatflux
926          ENDIF
927       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
928          WRITE ( io, 316 )
929       ENDIF
930       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
931          WRITE ( io, 309 )  top_salinityflux
932       ENDIF
933       IF ( humidity  .OR.  passive_scalar )  THEN
934          WRITE ( io, 315 )
935       ENDIF
936    ENDIF
937
938    IF ( prandtl_layer )  THEN
939       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
940                          z0h_factor*roughness_length, kappa, &
941                          rif_min, rif_max
942       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
943       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
944          WRITE ( io, 312 )
945       ENDIF
946       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
947          WRITE ( io, 314 )
948       ENDIF
949    ELSE
950       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
951          WRITE ( io, 310 )  rif_min, rif_max
952       ENDIF
953    ENDIF
954
955    WRITE ( io, 317 )  bc_lr, bc_ns
956    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
957       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
958       IF ( turbulent_inflow )  THEN
959          WRITE ( io, 319 )  recycling_width, recycling_plane, &
960                             inflow_damping_height, inflow_damping_width
961       ENDIF
962    ENDIF
963
964!
965!-- Initial Profiles
966    WRITE ( io, 321 )
967!
968!-- Initial wind profiles
969    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
970
971!
972!-- Initial temperature profile
973!-- Building output strings, starting with surface temperature
974    WRITE ( temperatures, '(F6.2)' )  pt_surface
975    gradients = '------'
976    slices = '     0'
977    coordinates = '   0.0'
978    i = 1
979    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
980
981       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
982       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
983
984       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
985       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
986
987       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
988       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
989
990       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
991       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
992
993       IF ( i == 10 )  THEN
994          EXIT
995       ELSE
996          i = i + 1
997       ENDIF
998
999    ENDDO
1000
1001    IF ( .NOT. nudging )  THEN
1002       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1003                          TRIM( gradients ), TRIM( slices )
1004    ELSE
1005       WRITE ( io, 428 ) 
1006    ENDIF
1007
1008!
1009!-- Initial humidity profile
1010!-- Building output strings, starting with surface humidity
1011    IF ( humidity  .OR.  passive_scalar )  THEN
1012       WRITE ( temperatures, '(E8.1)' )  q_surface
1013       gradients = '--------'
1014       slices = '       0'
1015       coordinates = '     0.0'
1016       i = 1
1017       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1018         
1019          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1020          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1021
1022          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1023          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1024         
1025          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1026          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1027         
1028          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1029          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1030
1031          IF ( i == 10 )  THEN
1032             EXIT
1033          ELSE
1034             i = i + 1
1035          ENDIF
1036
1037       ENDDO
1038
1039       IF ( humidity )  THEN
1040          IF ( .NOT. nudging )  THEN
1041             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1042                                TRIM( gradients ), TRIM( slices )
1043          ENDIF
1044       ELSE
1045          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1046                             TRIM( gradients ), TRIM( slices )
1047       ENDIF
1048    ENDIF
1049
1050!
1051!-- Initial salinity profile
1052!-- Building output strings, starting with surface salinity
1053    IF ( ocean )  THEN
1054       WRITE ( temperatures, '(F6.2)' )  sa_surface
1055       gradients = '------'
1056       slices = '     0'
1057       coordinates = '   0.0'
1058       i = 1
1059       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1060
1061          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1062          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1063
1064          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1065          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1066
1067          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1068          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1069
1070          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1071          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1072
1073          IF ( i == 10 )  THEN
1074             EXIT
1075          ELSE
1076             i = i + 1
1077          ENDIF
1078
1079       ENDDO
1080
1081       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1082                          TRIM( gradients ), TRIM( slices )
1083    ENDIF
1084
1085
1086!
1087!-- Listing of 1D-profiles
1088    WRITE ( io, 325 )  dt_dopr_listing
1089    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1090       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1091    ENDIF
1092
1093!
1094!-- DATA output
1095    WRITE ( io, 330 )
1096    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1097       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1098    ENDIF
1099
1100!
1101!-- 1D-profiles
1102    dopr_chr = 'Profile:'
1103    IF ( dopr_n /= 0 )  THEN
1104       WRITE ( io, 331 )
1105
1106       output_format = ''
1107       output_format = output_format_netcdf
1108       WRITE ( io, 344 )  output_format
1109
1110       DO  i = 1, dopr_n
1111          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1112          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1113             WRITE ( io, 332 )  dopr_chr
1114             dopr_chr = '       :'
1115          ENDIF
1116       ENDDO
1117
1118       IF ( dopr_chr /= '' )  THEN
1119          WRITE ( io, 332 )  dopr_chr
1120       ENDIF
1121       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1122       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1123    ENDIF
1124
1125!
1126!-- 2D-arrays
1127    DO  av = 0, 1
1128
1129       i = 1
1130       do2d_xy = ''
1131       do2d_xz = ''
1132       do2d_yz = ''
1133       DO  WHILE ( do2d(av,i) /= ' ' )
1134
1135          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1136          do2d_mode = do2d(av,i)(l-1:l)
1137
1138          SELECT CASE ( do2d_mode )
1139             CASE ( 'xy' )
1140                ll = LEN_TRIM( do2d_xy )
1141                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1142             CASE ( 'xz' )
1143                ll = LEN_TRIM( do2d_xz )
1144                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1145             CASE ( 'yz' )
1146                ll = LEN_TRIM( do2d_yz )
1147                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1148          END SELECT
1149
1150          i = i + 1
1151
1152       ENDDO
1153
1154       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1155              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1156              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1157
1158          IF (  av == 0 )  THEN
1159             WRITE ( io, 334 )  ''
1160          ELSE
1161             WRITE ( io, 334 )  '(time-averaged)'
1162          ENDIF
1163
1164          IF ( do2d_at_begin )  THEN
1165             begin_chr = 'and at the start'
1166          ELSE
1167             begin_chr = ''
1168          ENDIF
1169
1170          output_format = ''
1171          output_format = output_format_netcdf
1172          WRITE ( io, 344 )  output_format
1173
1174          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1175             i = 1
1176             slices = '/'
1177             coordinates = '/'
1178!
1179!--          Building strings with index and coordinate informations of the
1180!--          slices
1181             DO  WHILE ( section(i,1) /= -9999 )
1182
1183                WRITE (section_chr,'(I5)')  section(i,1)
1184                section_chr = ADJUSTL( section_chr )
1185                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1186
1187                IF ( section(i,1) == -1 )  THEN
1188                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1189                ELSE
1190                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1191                ENDIF
1192                coor_chr = ADJUSTL( coor_chr )
1193                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1194
1195                i = i + 1
1196             ENDDO
1197             IF ( av == 0 )  THEN
1198                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1199                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1200                                   TRIM( coordinates )
1201                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1202                   WRITE ( io, 339 )  skip_time_do2d_xy
1203                ENDIF
1204             ELSE
1205                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1206                                   TRIM( begin_chr ), averaging_interval, &
1207                                   dt_averaging_input, 'k', TRIM( slices ), &
1208                                   TRIM( coordinates )
1209                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1210                   WRITE ( io, 339 )  skip_time_data_output_av
1211                ENDIF
1212             ENDIF
1213             IF ( netcdf_data_format > 4 )  THEN
1214                WRITE ( io, 352 )  ntdim_2d_xy(av)
1215             ELSE
1216                WRITE ( io, 353 )
1217             ENDIF
1218          ENDIF
1219
1220          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1221             i = 1
1222             slices = '/'
1223             coordinates = '/'
1224!
1225!--          Building strings with index and coordinate informations of the
1226!--          slices
1227             DO  WHILE ( section(i,2) /= -9999 )
1228
1229                WRITE (section_chr,'(I5)')  section(i,2)
1230                section_chr = ADJUSTL( section_chr )
1231                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1232
1233                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1234                coor_chr = ADJUSTL( coor_chr )
1235                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1236
1237                i = i + 1
1238             ENDDO
1239             IF ( av == 0 )  THEN
1240                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1241                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1242                                   TRIM( coordinates )
1243                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1244                   WRITE ( io, 339 )  skip_time_do2d_xz
1245                ENDIF
1246             ELSE
1247                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1248                                   TRIM( begin_chr ), averaging_interval, &
1249                                   dt_averaging_input, 'j', TRIM( slices ), &
1250                                   TRIM( coordinates )
1251                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1252                   WRITE ( io, 339 )  skip_time_data_output_av
1253                ENDIF
1254             ENDIF
1255             IF ( netcdf_data_format > 4 )  THEN
1256                WRITE ( io, 352 )  ntdim_2d_xz(av)
1257             ELSE
1258                WRITE ( io, 353 )
1259             ENDIF
1260          ENDIF
1261
1262          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1263             i = 1
1264             slices = '/'
1265             coordinates = '/'
1266!
1267!--          Building strings with index and coordinate informations of the
1268!--          slices
1269             DO  WHILE ( section(i,3) /= -9999 )
1270
1271                WRITE (section_chr,'(I5)')  section(i,3)
1272                section_chr = ADJUSTL( section_chr )
1273                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1274
1275                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1276                coor_chr = ADJUSTL( coor_chr )
1277                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1278
1279                i = i + 1
1280             ENDDO
1281             IF ( av == 0 )  THEN
1282                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1283                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1284                                   TRIM( coordinates )
1285                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1286                   WRITE ( io, 339 )  skip_time_do2d_yz
1287                ENDIF
1288             ELSE
1289                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1290                                   TRIM( begin_chr ), averaging_interval, &
1291                                   dt_averaging_input, 'i', TRIM( slices ), &
1292                                   TRIM( coordinates )
1293                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1294                   WRITE ( io, 339 )  skip_time_data_output_av
1295                ENDIF
1296             ENDIF
1297             IF ( netcdf_data_format > 4 )  THEN
1298                WRITE ( io, 352 )  ntdim_2d_yz(av)
1299             ELSE
1300                WRITE ( io, 353 )
1301             ENDIF
1302          ENDIF
1303
1304       ENDIF
1305
1306    ENDDO
1307
1308!
1309!-- 3d-arrays
1310    DO  av = 0, 1
1311
1312       i = 1
1313       do3d_chr = ''
1314       DO  WHILE ( do3d(av,i) /= ' ' )
1315
1316          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1317          i = i + 1
1318
1319       ENDDO
1320
1321       IF ( do3d_chr /= '' )  THEN
1322          IF ( av == 0 )  THEN
1323             WRITE ( io, 336 )  ''
1324          ELSE
1325             WRITE ( io, 336 )  '(time-averaged)'
1326          ENDIF
1327
1328          output_format = output_format_netcdf
1329          WRITE ( io, 344 )  output_format
1330
1331          IF ( do3d_at_begin )  THEN
1332             begin_chr = 'and at the start'
1333          ELSE
1334             begin_chr = ''
1335          ENDIF
1336          IF ( av == 0 )  THEN
1337             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1338                                zu(nz_do3d), nz_do3d
1339          ELSE
1340             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1341                                TRIM( begin_chr ), averaging_interval, &
1342                                dt_averaging_input, zu(nz_do3d), nz_do3d
1343          ENDIF
1344
1345          IF ( netcdf_data_format > 4 )  THEN
1346             WRITE ( io, 352 )  ntdim_3d(av)
1347          ELSE
1348             WRITE ( io, 353 )
1349          ENDIF
1350
1351          IF ( av == 0 )  THEN
1352             IF ( skip_time_do3d /= 0.0_wp )  THEN
1353                WRITE ( io, 339 )  skip_time_do3d
1354             ENDIF
1355          ELSE
1356             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1357                WRITE ( io, 339 )  skip_time_data_output_av
1358             ENDIF
1359          ENDIF
1360
1361       ENDIF
1362
1363    ENDDO
1364
1365!
1366!-- masked arrays
1367    IF ( masks > 0 )  WRITE ( io, 345 )  &
1368         mask_scale_x, mask_scale_y, mask_scale_z
1369    DO  mid = 1, masks
1370       DO  av = 0, 1
1371
1372          i = 1
1373          domask_chr = ''
1374          DO  WHILE ( domask(mid,av,i) /= ' ' )
1375             domask_chr = TRIM( domask_chr ) // ' ' //  &
1376                          TRIM( domask(mid,av,i) ) // ','
1377             i = i + 1
1378          ENDDO
1379
1380          IF ( domask_chr /= '' )  THEN
1381             IF ( av == 0 )  THEN
1382                WRITE ( io, 346 )  '', mid
1383             ELSE
1384                WRITE ( io, 346 )  ' (time-averaged)', mid
1385             ENDIF
1386
1387             output_format = output_format_netcdf
1388!--          Parallel output not implemented for mask data, hence
1389!--          output_format must be adjusted.
1390             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1391             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1392             WRITE ( io, 344 )  output_format
1393
1394             IF ( av == 0 )  THEN
1395                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1396             ELSE
1397                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1398                                   averaging_interval, dt_averaging_input
1399             ENDIF
1400
1401             IF ( av == 0 )  THEN
1402                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1403                   WRITE ( io, 339 )  skip_time_domask(mid)
1404                ENDIF
1405             ELSE
1406                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1407                   WRITE ( io, 339 )  skip_time_data_output_av
1408                ENDIF
1409             ENDIF
1410!
1411!--          output locations
1412             DO  dim = 1, 3
1413                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1414                   count = 0
1415                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1416                      count = count + 1
1417                   ENDDO
1418                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1419                                      mask(mid,dim,:count)
1420                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1421                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1422                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1423                   WRITE ( io, 350 )  dir(dim), dir(dim)
1424                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1425                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1426                                      mask_loop(mid,dim,1:2)
1427                ELSE
1428                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1429                                      mask_loop(mid,dim,1:3)
1430                ENDIF
1431             ENDDO
1432          ENDIF
1433
1434       ENDDO
1435    ENDDO
1436
1437!
1438!-- Timeseries
1439    IF ( dt_dots /= 9999999.9_wp )  THEN
1440       WRITE ( io, 340 )
1441
1442       output_format = output_format_netcdf
1443       WRITE ( io, 344 )  output_format
1444       WRITE ( io, 341 )  dt_dots
1445    ENDIF
1446
1447#if defined( __dvrp_graphics )
1448!
1449!-- Dvrp-output
1450    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1451       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1452                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1453       i = 1
1454       l = 0
1455       m = 0
1456       DO WHILE ( mode_dvrp(i) /= ' ' )
1457          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1458             READ ( mode_dvrp(i), '(10X,I2)' )  j
1459             l = l + 1
1460             IF ( do3d(0,j) /= ' ' )  THEN
1461                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1462                                   isosurface_color(:,l)
1463             ENDIF
1464          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1465             READ ( mode_dvrp(i), '(6X,I2)' )  j
1466             m = m + 1
1467             IF ( do2d(0,j) /= ' ' )  THEN
1468                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1469                                   slicer_range_limits_dvrp(:,m)
1470             ENDIF
1471          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1472             WRITE ( io, 363 )  dvrp_psize
1473             IF ( particle_dvrpsize /= 'none' )  THEN
1474                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1475                                   dvrpsize_interval
1476             ENDIF
1477             IF ( particle_color /= 'none' )  THEN
1478                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1479                                   color_interval
1480             ENDIF
1481          ENDIF
1482          i = i + 1
1483       ENDDO
1484
1485       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1486                          superelevation_y, superelevation, clip_dvrp_l, &
1487                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1488
1489       IF ( TRIM( topography ) /= 'flat' )  THEN
1490          WRITE ( io, 366 )  topography_color
1491          IF ( cluster_size > 1 )  THEN
1492             WRITE ( io, 367 )  cluster_size
1493          ENDIF
1494       ENDIF
1495
1496    ENDIF
1497#endif
1498
1499#if defined( __spectra )
1500!
1501!-- Spectra output
1502    IF ( dt_dosp /= 9999999.9_wp )  THEN
1503       WRITE ( io, 370 )
1504
1505       output_format = output_format_netcdf
1506       WRITE ( io, 344 )  output_format
1507       WRITE ( io, 371 )  dt_dosp
1508       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
1509       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1510                          ( spectra_direction(i), i = 1,10 ),  &
1511                          ( comp_spectra_level(i), i = 1,100 ), &
1512                          ( plot_spectra_level(i), i = 1,100 ), &
1513                          averaging_interval_sp, dt_averaging_input_pr
1514    ENDIF
1515#endif
1516
1517    WRITE ( io, 99 )
1518
1519!
1520!-- Physical quantities
1521    WRITE ( io, 400 )
1522
1523!
1524!-- Geostrophic parameters
1525    WRITE ( io, 410 )  omega, phi, f, fs
1526
1527!
1528!-- Other quantities
1529    WRITE ( io, 411 )  g
1530    WRITE ( io, 412 )  TRIM( reference_state )
1531    IF ( use_single_reference_value )  THEN
1532       IF ( ocean )  THEN
1533          WRITE ( io, 413 )  prho_reference
1534       ELSE
1535          WRITE ( io, 414 )  pt_reference
1536       ENDIF
1537    ENDIF
1538
1539!
1540!-- Cloud physics parameters
1541    IF ( cloud_physics )  THEN
1542       WRITE ( io, 415 )
1543       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1544       IF ( icloud_scheme == 0 )  THEN
1545          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1546          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1547       ENDIF
1548    ENDIF
1549
1550!
1551!-- Cloud physcis parameters / quantities / numerical methods
1552    WRITE ( io, 430 )
1553    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1554       WRITE ( io, 431 )
1555    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1556       WRITE ( io, 432 )
1557       IF ( radiation )  WRITE ( io, 132 )
1558       IF ( icloud_scheme == 1 )  THEN
1559          IF ( precipitation )  WRITE ( io, 133 )
1560       ELSEIF ( icloud_scheme == 0 )  THEN
1561          IF ( drizzle )  WRITE ( io, 506 )
1562          IF ( precipitation )  THEN
1563             WRITE ( io, 505 )
1564             IF ( turbulence )  WRITE ( io, 507 )
1565             IF ( ventilation_effect )  WRITE ( io, 508 )
1566             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1567          ENDIF
1568       ENDIF
1569    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1570       WRITE ( io, 433 )
1571       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1572       IF ( collision_kernel /= 'none' )  THEN
1573          WRITE ( io, 435 )  TRIM( collision_kernel )
1574          IF ( collision_kernel(6:9) == 'fast' )  THEN
1575             WRITE ( io, 436 )  radius_classes, dissipation_classes
1576          ENDIF
1577       ELSE
1578          WRITE ( io, 437 )
1579       ENDIF
1580    ENDIF
1581
1582!
1583!-- LES / turbulence parameters
1584    WRITE ( io, 450 )
1585
1586!--
1587! ... LES-constants used must still be added here
1588!--
1589    IF ( constant_diffusion )  THEN
1590       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1591                          prandtl_number
1592    ENDIF
1593    IF ( .NOT. constant_diffusion)  THEN
1594       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1595       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1596       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1597    ENDIF
1598
1599!
1600!-- Special actions during the run
1601    WRITE ( io, 470 )
1602    IF ( create_disturbances )  THEN
1603       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1604                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1605                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1606       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1607          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1608       ELSE
1609          WRITE ( io, 473 )  disturbance_energy_limit
1610       ENDIF
1611       WRITE ( io, 474 )  TRIM( random_generator )
1612    ENDIF
1613    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1614       WRITE ( io, 475 )  pt_surface_initial_change
1615    ENDIF
1616    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1617       WRITE ( io, 476 )  q_surface_initial_change       
1618    ENDIF
1619    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1620       WRITE ( io, 477 )  q_surface_initial_change       
1621    ENDIF
1622
1623    IF ( particle_advection )  THEN
1624!
1625!--    Particle attributes
1626       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1627                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1628                          end_time_prel
1629       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1630       IF ( random_start_position )  WRITE ( io, 481 )
1631       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1632       WRITE ( io, 495 )  total_number_of_particles
1633       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1634          WRITE ( io, 483 )  maximum_number_of_tailpoints
1635          IF ( minimum_tailpoint_distance /= 0 )  THEN
1636             WRITE ( io, 484 )  total_number_of_tails,      &
1637                                minimum_tailpoint_distance, &
1638                                maximum_tailpoint_age
1639          ENDIF
1640       ENDIF
1641       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1642          WRITE ( io, 485 )  dt_write_particle_data
1643          IF ( netcdf_data_format > 1 )  THEN
1644             output_format = 'netcdf (64 bit offset) and binary'
1645          ELSE
1646             output_format = 'netcdf and binary'
1647          ENDIF
1648          WRITE ( io, 344 )  output_format
1649       ENDIF
1650       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1651       IF ( write_particle_statistics )  WRITE ( io, 486 )
1652
1653       WRITE ( io, 487 )  number_of_particle_groups
1654
1655       DO  i = 1, number_of_particle_groups
1656          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1657             WRITE ( io, 490 )  i, 0.0_wp
1658             WRITE ( io, 492 )
1659          ELSE
1660             WRITE ( io, 490 )  i, radius(i)
1661             IF ( density_ratio(i) /= 0.0_wp )  THEN
1662                WRITE ( io, 491 )  density_ratio(i)
1663             ELSE
1664                WRITE ( io, 492 )
1665             ENDIF
1666          ENDIF
1667          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1668                             pdx(i), pdy(i), pdz(i)
1669          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1670       ENDDO
1671
1672    ENDIF
1673
1674
1675!
1676!-- Parameters of 1D-model
1677    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1678       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1679                          mixing_length_1d, dissipation_1d
1680       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1681          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1682       ENDIF
1683    ENDIF
1684
1685!
1686!-- User-defined informations
1687    CALL user_header( io )
1688
1689    WRITE ( io, 99 )
1690
1691!
1692!-- Write buffer contents to disc immediately
1693    CALL local_flush( io )
1694
1695!
1696!-- Here the FORMATs start
1697
1698 99 FORMAT (1X,78('-'))
1699100 FORMAT (/1X,'******************************',4X,44('-')/        &
1700            1X,'* ',A,' *',4X,A/                               &
1701            1X,'******************************',4X,44('-'))
1702101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1703            35X,42('-'))
1704102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1705            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1706            ' Run on host:        ',A10)
1707#if defined( __parallel )
1708103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1709              ')',1X,A)
1710104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1711              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1712105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1713106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1714            35X,'because the job is running on an SMP-cluster')
1715107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1716108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1717109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1718            35X,42('-'))
1719114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1720            35X,'independent precursor runs'/             &
1721            35X,42('-'))
1722117 FORMAT (' Accelerator boards / node:  ',I2)
1723#endif
1724110 FORMAT (/' Numerical Schemes:'/ &
1725             ' -----------------'/)
1726111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1727112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1728            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1729113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1730                  ' or Upstream')
1731115 FORMAT ('     FFT and transpositions are overlapping')
1732116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1733                  ' or Upstream')
1734118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1735119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1736            '     translation velocity = ',A/ &
1737            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1738120 FORMAT (' Accelerator boards: ',8X,I2)
1739122 FORMAT (' --> Time differencing scheme: ',A)
1740123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1741            '     maximum damping coefficient: ',F5.3, ' 1/s')
1742129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1743130 FORMAT (' --> Additional prognostic equation for the total water content')
1744131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1745                  F6.2, ' K assumed')
1746132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1747            '     effective emissivity scheme')
1748133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1749134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1750135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1751                  A,'-cycle)'/ &
1752            '     number of grid levels:                   ',I2/ &
1753            '     Gauss-Seidel red/black iterations:       ',I2)
1754136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1755                  I3,')')
1756137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1757            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1758                  I3,')'/ &
1759            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1760                  I3,')')
1761139 FORMAT (' --> Loop optimization method: ',A)
1762140 FORMAT ('     maximum residual allowed:                ',E10.3)
1763141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1764142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1765                  'step')
1766143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1767                  'kinetic energy')
1768144 FORMAT ('     masking method is used')
1769150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1770                  'conserved'/ &
1771            '     using the ',A,' mode')
1772151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1773152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1774           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1775           /'     starting from dp_level_b =', F8.3, 'm', A /)
1776160 FORMAT (//' Large scale forcing and nudging:'/ &
1777              ' -------------------------------'/)
1778161 FORMAT (' --> No large scale forcing from external is used (default) ')
1779162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1780163 FORMAT ('     - large scale advection tendencies ')
1781164 FORMAT ('     - large scale subsidence velocity w_subs ')
1782165 FORMAT ('     - large scale subsidence tendencies ')
1783167 FORMAT ('     - and geostrophic wind components ug and vg')
1784168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1785                  'prognostic equation(s) for')
1786169 FORMAT ('     the scalar(s) only')
1787170 FORMAT (' --> Nudging is used')
1788171 FORMAT (' --> No nudging is used (default) ')
1789180 FORMAT ('     - prescribed surface values for temperature')
1790181 FORMAT ('     - prescribed surface fluxes for temperature')
1791182 FORMAT ('     - prescribed surface values for humidity')
1792183 FORMAT ('     - prescribed surface fluxes for humidity')
1793200 FORMAT (//' Run time and time step information:'/ &
1794             ' ----------------------------------'/)
1795201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1796             '    CFL-factor: ',F4.2)
1797202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1798203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1799             ' End time:            ',F9.3,' s')
1800204 FORMAT ( A,F9.3,' s')
1801205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1802206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1803             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1804               '  ',F9.3,' s'/                                                    &
1805             '                                      per second of simulated tim', &
1806               'e: ',F9.3,' s')
1807207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1808250 FORMAT (//' Computational grid and domain size:'/ &
1809              ' ----------------------------------'// &
1810              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1811              ' m    dz =    ',F7.3,' m'/ &
1812              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1813              ' m  z(u) = ',F10.3,' m'/)
1814252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1815              ' factor: ',F5.3/ &
1816            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1817254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1818            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1819260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1820             ' degrees')
1821270 FORMAT (//' Topography informations:'/ &
1822              ' -----------------------'// &
1823              1X,'Topography: ',A)
1824271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1825              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1826                ' / ',I4)
1827272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1828              ' direction' / &
1829              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1830              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1831278 FORMAT (' Topography grid definition convention:'/ &
1832            ' cell edge (staggered grid points'/  &
1833            ' (u in x-direction, v in y-direction))' /)
1834279 FORMAT (' Topography grid definition convention:'/ &
1835            ' cell center (scalar grid points)' /)
1836280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1837              ' ------------------------------'// &
1838              ' Canopy mode: ', A / &
1839              ' Canopy top: ',I4 / &
1840              ' Leaf drag coefficient: ',F6.2 /)
1841281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1842              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1843282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1844283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1845              ' Height:              ',A,'  m'/ &
1846              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1847              ' Gradient:            ',A,'  m**2/m**4'/ &
1848              ' Gridpoint:           ',A)
1849               
1850300 FORMAT (//' Boundary conditions:'/ &
1851             ' -------------------'// &
1852             '                     p                    uv             ', &
1853             '                   pt'// &
1854             ' B. bound.: ',A/ &
1855             ' T. bound.: ',A)
1856301 FORMAT (/'                     ',A// &
1857             ' B. bound.: ',A/ &
1858             ' T. bound.: ',A)
1859303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1860304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1861305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1862               'computational u,v-level:'// &
1863             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1864             ' m   kappa = ',F4.2/ &
1865             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1866306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1867307 FORMAT ('       Heatflux has a random normal distribution')
1868308 FORMAT ('       Predefined surface temperature')
1869309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1870310 FORMAT (//'    1D-Model:'// &
1871             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1872311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1873312 FORMAT ('       Predefined surface humidity')
1874313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1875314 FORMAT ('       Predefined scalar value at the surface')
1876315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1877316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1878                    'atmosphere model')
1879317 FORMAT (//' Lateral boundaries:'/ &
1880            '       left/right:  ',A/    &
1881            '       north/south: ',A)
1882318 FORMAT (/'       use_cmax: ',L1 / &
1883            '       pt damping layer width = ',F8.2,' m, pt ', &
1884                    'damping factor = ',F6.4)
1885319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1886            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1887            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1888320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1889            '                                          v: ',F9.6,' m**2/s**2')
1890321 FORMAT (//' Initial profiles:'/ &
1891              ' ----------------')
1892325 FORMAT (//' List output:'/ &
1893             ' -----------'//  &
1894            '    1D-Profiles:'/    &
1895            '       Output every             ',F8.2,' s')
1896326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1897            '       Averaging input every    ',F8.2,' s')
1898330 FORMAT (//' Data output:'/ &
1899             ' -----------'/)
1900331 FORMAT (/'    1D-Profiles:')
1901332 FORMAT (/'       ',A)
1902333 FORMAT ('       Output every             ',F8.2,' s',/ &
1903            '       Time averaged over       ',F8.2,' s'/ &
1904            '       Averaging input every    ',F8.2,' s')
1905334 FORMAT (/'    2D-Arrays',A,':')
1906335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1907            '       Output every             ',F8.2,' s  ',A/ &
1908            '       Cross sections at ',A1,' = ',A/ &
1909            '       scalar-coordinates:   ',A,' m'/)
1910336 FORMAT (/'    3D-Arrays',A,':')
1911337 FORMAT (/'       Arrays: ',A/ &
1912            '       Output every             ',F8.2,' s  ',A/ &
1913            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1914339 FORMAT ('       No output during initial ',F8.2,' s')
1915340 FORMAT (/'    Time series:')
1916341 FORMAT ('       Output every             ',F8.2,' s'/)
1917342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1918            '       Output every             ',F8.2,' s  ',A/ &
1919            '       Time averaged over       ',F8.2,' s'/ &
1920            '       Averaging input every    ',F8.2,' s'/ &
1921            '       Cross sections at ',A1,' = ',A/ &
1922            '       scalar-coordinates:   ',A,' m'/)
1923343 FORMAT (/'       Arrays: ',A/ &
1924            '       Output every             ',F8.2,' s  ',A/ &
1925            '       Time averaged over       ',F8.2,' s'/ &
1926            '       Averaging input every    ',F8.2,' s'/ &
1927            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1928344 FORMAT ('       Output format: ',A/)
1929345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1930            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1931            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1932            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1933346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1934347 FORMAT ('       Variables: ',A/ &
1935            '       Output every             ',F8.2,' s')
1936348 FORMAT ('       Variables: ',A/ &
1937            '       Output every             ',F8.2,' s'/ &
1938            '       Time averaged over       ',F8.2,' s'/ &
1939            '       Averaging input every    ',F8.2,' s')
1940349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1941            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1942            13('       ',8(F8.2,',')/) )
1943350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1944            'all gridpoints along ',A,'-direction (default).' )
1945351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1946            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1947            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1948352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
1949353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
1950#if defined( __dvrp_graphics )
1951360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1952            '       Output every      ',F7.1,' s'/ &
1953            '       Output mode:      ',A/ &
1954            '       Host / User:      ',A,' / ',A/ &
1955            '       Directory:        ',A// &
1956            '       The sequence contains:')
1957361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1958            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1959362 FORMAT (/'       Slicer plane ',A/ &
1960            '       Slicer limits: [',F6.2,',',F6.2,']')
1961363 FORMAT (/'       Particles'/ &
1962            '          particle size:  ',F7.2,' m')
1963364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1964                       F6.2,',',F6.2,']')
1965365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1966            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1967                     ')'/ &
1968            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1969            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1970366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1971367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1972#endif
1973#if defined( __spectra )
1974370 FORMAT ('    Spectra:')
1975371 FORMAT ('       Output every ',F7.1,' s'/)
1976372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1977            '       Directions: ', 10(A5,',')/                         &
1978            '       height levels  k = ', 20(I3,',')/                  &
1979            '                          ', 20(I3,',')/                  &
1980            '                          ', 20(I3,',')/                  &
1981            '                          ', 20(I3,',')/                  &
1982            '                          ', 19(I3,','),I3,'.'/           &
1983            '       height levels selected for standard plot:'/        &
1984            '                      k = ', 20(I3,',')/                  &
1985            '                          ', 20(I3,',')/                  &
1986            '                          ', 20(I3,',')/                  &
1987            '                          ', 20(I3,',')/                  &
1988            '                          ', 19(I3,','),I3,'.'/           &
1989            '       Time averaged over ', F7.1, ' s,' /                &
1990            '       Profiles for the time averaging are taken every ', &
1991                    F6.1,' s')
1992#endif
1993400 FORMAT (//' Physical quantities:'/ &
1994              ' -------------------'/)
1995410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1996            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1997            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1998            '                            f*    = ',F9.6,' 1/s')
1999411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
2000412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2001413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2002414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2003415 FORMAT (/'    Cloud physics parameters:'/ &
2004             '    ------------------------'/)
2005416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2006            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2007            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
2008            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2009            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
2010420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2011            '       Height:        ',A,'  m'/ &
2012            '       Temperature:   ',A,'  K'/ &
2013            '       Gradient:      ',A,'  K/100m'/ &
2014            '       Gridpoint:     ',A)
2015421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2016            '       Height:      ',A,'  m'/ &
2017            '       Humidity:    ',A,'  kg/kg'/ &
2018            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2019            '       Gridpoint:   ',A)
2020422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2021            '       Height:                  ',A,'  m'/ &
2022            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2023            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2024            '       Gridpoint:               ',A)
2025423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2026            '       Height:      ',A,'  m'/ &
2027            '       ug:          ',A,'  m/s'/ &
2028            '       Gradient:    ',A,'  1/100s'/ &
2029            '       Gridpoint:   ',A)
2030424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2031            '       Height:      ',A,'  m'/ &
2032            '       vg:          ',A,'  m/s'/ &
2033            '       Gradient:    ',A,'  1/100s'/ &
2034            '       Gridpoint:   ',A)
2035425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2036            '       Height:     ',A,'  m'/ &
2037            '       Salinity:   ',A,'  psu'/ &
2038            '       Gradient:   ',A,'  psu/100m'/ &
2039            '       Gridpoint:  ',A)
2040426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2041            '       Height:      ',A,'  m'/ &
2042            '       w_subs:      ',A,'  m/s'/ &
2043            '       Gradient:    ',A,'  (m/s)/100m'/ &
2044            '       Gridpoint:   ',A)
2045427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2046                  ' profiles')
2047428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2048             '    NUDGING_DATA')
2049430 FORMAT (//' Cloud physics quantities / methods:'/ &
2050              ' ----------------------------------'/)
2051431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2052                 'on)')
2053432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2054            '    total water content is used.'/ &
2055            '    Condensation is parameterized via 0% - or 100% scheme.')
2056433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2057                 'icle model')
2058434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2059                 ' droplets < 1.0E-6 m')
2060435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2061436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2062                    'are used'/ &
2063            '          number of radius classes:       ',I3,'    interval ', &
2064                       '[1.0E-6,2.0E-4] m'/ &
2065            '          number of dissipation classes:   ',I2,'    interval ', &
2066                       '[0,1000] cm**2/s**3')
2067437 FORMAT ('    Droplet collision is switched off')
2068450 FORMAT (//' LES / Turbulence quantities:'/ &
2069              ' ---------------------------'/)
2070451 FORMAT ('    Diffusion coefficients are constant:'/ &
2071            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2072453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2073454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2074455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2075470 FORMAT (//' Actions during the simulation:'/ &
2076              ' -----------------------------'/)
2077471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2078            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2079            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2080            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2081472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2082                 ' to i/j =',I4)
2083473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2084                 1X,F5.3, ' m**2/s**2')
2085474 FORMAT ('    Random number generator used    : ',A/)
2086475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2087                 'respectively, if'/ &
2088            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2089                 ' 3D-simulation'/)
2090476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2091                 'respectively, if the'/ &
2092            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2093                 ' the 3D-simulation'/)
2094477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2095                 'respectively, if the'/ &
2096            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2097                 ' the 3D-simulation'/)
2098480 FORMAT ('    Particles:'/ &
2099            '    ---------'// &
2100            '       Particle advection is active (switched on at t = ', F7.1, &
2101                    ' s)'/ &
2102            '       Start of new particle generations every  ',F6.1,' s'/ &
2103            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2104            '                            bottom:     ', A, ' top:         ', A/&
2105            '       Maximum particle age:                 ',F9.1,' s'/ &
2106            '       Advection stopped at t = ',F9.1,' s'/)
2107481 FORMAT ('       Particles have random start positions'/)
2108482 FORMAT ('          Particles are advected only horizontally'/)
2109483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2110484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2111            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2112            '            Maximum age of the end of the tail:  ',F8.2,' s')
2113485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2114486 FORMAT ('       Particle statistics are written on file'/)
2115487 FORMAT ('       Number of particle groups: ',I2/)
2116488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2117            '          minimum timestep for advection: ', F7.5/)
2118489 FORMAT ('       Number of particles simultaneously released at each ', &
2119                    'point: ', I5/)
2120490 FORMAT ('       Particle group ',I2,':'/ &
2121            '          Particle radius: ',E10.3, 'm')
2122491 FORMAT ('          Particle inertia is activated'/ &
2123            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2124492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2125493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2126            '                                         y:',F8.1,' - ',F8.1,' m'/&
2127            '                                         z:',F8.1,' - ',F8.1,' m'/&
2128            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2129                       ' m  dz = ',F8.1,' m'/)
2130494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2131                    F8.2,' s'/)
2132495 FORMAT ('       Number of particles in total domain: ',I10/)
2133500 FORMAT (//' 1D-Model parameters:'/                           &
2134              ' -------------------'//                           &
2135            '    Simulation time:                   ',F8.1,' s'/ &
2136            '    Run-controll output every:         ',F8.1,' s'/ &
2137            '    Vertical profile output every:     ',F8.1,' s'/ &
2138            '    Mixing length calculation:         ',A/         &
2139            '    Dissipation calculation:           ',A/)
2140502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2141503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2142504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2143505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2144506 FORMAT ('    Drizzle parameterization via Stokes law')
2145507 FORMAT ('    Turbulence effects on precipitation process')
2146508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2147509 FORMAT ('    Slope limiter used for sedimentation process')
2148510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2149511 FORMAT ('        Sedimentation Courant number:                  '/&
2150            '                               C_s   = ',F3.1,'        ')
2151512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2152            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2153            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2154
2155 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.