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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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