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

Last change on this file since 979 was 979, checked in by fricke, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 79.8 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: header.f90 979 2012-08-09 08:50:11Z fricke $
11!
12! 978 2012-08-09 08:28:32Z fricke
13! -km_damp_max, outflow_damping_width
14! +pt_damping_factor, pt_damping_width
15! +z0h
16!
17! 964 2012-07-26 09:14:24Z raasch
18! output of profil-related quantities removed
19!
20! 940 2012-07-09 14:31:00Z raasch
21! Output in case of simulations for pure neutral stratification (no pt-equation
22! solved)
23!
24! 927 2012-06-06 19:15:04Z raasch
25! output of masking_method for mg-solver
26!
27! 868 2012-03-28 12:21:07Z raasch
28! translation velocity in Galilean transformation changed to 0.6 * ug
29!
30! 833 2012-02-22 08:55:55Z maronga
31! Adjusted format for leaf area density
32!
33! 828 2012-02-21 12:00:36Z raasch
34! output of dissipation_classes + radius_classes
35!
36! 825 2012-02-19 03:03:44Z raasch
37! Output of cloud physics parameters/quantities complemented and restructured
38!
39! 767 2011-10-14 06:39:12Z raasch
40! Output of given initial u,v-profiles
41!
42! 759 2011-09-15 13:58:31Z raasch
43! output of maximum number of parallel io streams
44!
45! 707 2011-03-29 11:39:40Z raasch
46! bc_lr/ns replaced by bc_lr/ns_cyc
47!
48! 667 2010-12-23 12:06:00Z suehring/gryschka
49! Output of advection scheme.
50! Modified output of Prandtl-layer height.
51!
52! 580 2010-10-05 13:59:11Z heinze
53! Renaming of ws_vertical_gradient to subs_vertical_gradient,
54! ws_vertical_gradient_level to subs_vertical_gradient_level and
55! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
56!
57! 493 2010-03-01 08:30:24Z raasch
58! NetCDF data output format extendend for NetCDF4/HDF5
59!
60! 449 2010-02-02 11:23:59Z raasch
61! +large scale vertical motion (subsidence/ascent)
62! Bugfix: index problem concerning gradient_level indices removed
63!
64! 410 2009-12-04 17:05:40Z letzel
65! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
66! mask_scale|_x|y|z, masks, skip_time_domask
67!
68! 346 2009-07-06 10:13:41Z raasch
69! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
70! Coupling with independent precursor runs.
71! Output of messages replaced by message handling routine.
72! Output of several additional dvr parameters
73! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
74! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
75! dp_smooth, dpdxy, u_bulk, v_bulk
76! topography_grid_convention moved from user_header
77! small bugfix concerning 3d 64bit netcdf output format
78!
79! 206 2008-10-13 14:59:11Z raasch
80! Bugfix: error in zu index in case of section_xy = -1
81!
82! 198 2008-09-17 08:55:28Z raasch
83! Format adjustments allowing output of larger revision numbers
84!
85! 197 2008-09-16 15:29:03Z raasch
86! allow 100 spectra levels instead of 10 for consistency with
87! define_netcdf_header,
88! bugfix in the output of the characteristic levels of potential temperature,
89! geostrophic wind, scalar concentration, humidity and leaf area density,
90! output of turbulence recycling informations
91!
92! 138 2007-11-28 10:03:58Z letzel
93! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
94! Allow two instead of one digit to specify isosurface and slicer variables.
95! Output of sorting frequency of particles
96!
97! 108 2007-08-24 15:10:38Z letzel
98! Output of informations for coupled model runs (boundary conditions etc.)
99! + output of momentumfluxes at the top boundary
100! Rayleigh damping for ocean, e_init
101!
102! 97 2007-06-21 08:23:15Z raasch
103! Adjustments for the ocean version.
104! use_pt_reference renamed use_reference
105!
106! 87 2007-05-22 15:46:47Z raasch
107! Bugfix: output of use_upstream_for_tke
108!
109! 82 2007-04-16 15:40:52Z raasch
110! Preprocessor strings for different linux clusters changed to "lc",
111! routine local_flush is used for buffer flushing
112!
113! 76 2007-03-29 00:58:32Z raasch
114! Output of netcdf_64bit_3d, particles-package is now part of the default code,
115! output of the loop optimization method, moisture renamed humidity,
116! output of subversion revision number
117!
118! 19 2007-02-23 04:53:48Z raasch
119! Output of scalar flux applied at top boundary
120!
121! RCS Log replace by Id keyword, revision history cleaned up
122!
123! Revision 1.63  2006/08/22 13:53:13  raasch
124! Output of dz_max
125!
126! Revision 1.1  1997/08/11 06:17:20  raasch
127! Initial revision
128!
129!
130! Description:
131! ------------
132! Writing a header with all important informations about the actual run.
133! This subroutine is called three times, two times at the beginning
134! (writing information on files RUN_CONTROL and HEADER) and one time at the
135! end of the run, then writing additional information about CPU-usage on file
136! header.
137!-----------------------------------------------------------------------------!
138
139    USE arrays_3d
140    USE control_parameters
141    USE cloud_parameters
142    USE cpulog
143    USE dvrp_variables
144    USE grid_variables
145    USE indices
146    USE model_1d
147    USE particle_attributes
148    USE pegrid
149    USE subsidence_mod
150    USE spectrum
151
152    IMPLICIT NONE
153
154    CHARACTER (LEN=1)  ::  prec
155    CHARACTER (LEN=2)  ::  do2d_mode
156    CHARACTER (LEN=5)  ::  section_chr
157    CHARACTER (LEN=9)  ::  time_to_string
158    CHARACTER (LEN=10) ::  coor_chr, host_chr
159    CHARACTER (LEN=16) ::  begin_chr
160    CHARACTER (LEN=23) ::  ver_rev
161    CHARACTER (LEN=40) ::  output_format
162    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
163                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
164                           domask_chr, run_classification
165    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
166                           temperatures, ugcomponent, vgcomponent
167    CHARACTER (LEN=85) ::  roben, runten
168
169    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
170
171    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
172         cxl, cxr, cyn, cys, dim, i, ihost, io, j, l, ll, m, mpi_type
173    REAL    ::  cpuseconds_per_simulated_second
174
175!
176!-- Open the output file. At the end of the simulation, output is directed
177!-- to unit 19.
178    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
179         .NOT. simulated_time_at_begin /= simulated_time )  THEN
180       io = 15   !  header output on file RUN_CONTROL
181    ELSE
182       io = 19   !  header output on file HEADER
183    ENDIF
184    CALL check_open( io )
185
186!
187!-- At the end of the run, output file (HEADER) will be rewritten with
188!-- new informations
189    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
190
191!
192!-- Determine kind of model run
193    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
194       run_classification = '3D - restart run'
195    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
196       run_classification = '3D - run with cyclic fill of 3D - prerun data'
197    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
198       run_classification = '3D - run without 1D - prerun'
199    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
200       run_classification = '3D - run with 1D - prerun'
201    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
202       run_classification = '3D - run initialized by user'
203    ELSE
204       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
205       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
206    ENDIF
207    IF ( ocean )  THEN
208       run_classification = 'ocean - ' // run_classification
209    ELSE
210       run_classification = 'atmosphere - ' // run_classification
211    ENDIF
212
213!
214!-- Run-identification, date, time, host
215    host_chr = host(1:10)
216    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
217    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
218    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
219#if defined( __mpi2 )
220       mpi_type = 2
221#else
222       mpi_type = 1
223#endif
224       WRITE ( io, 101 )  mpi_type, coupling_mode
225    ENDIF
226    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
227                       ADJUSTR( host_chr )
228#if defined( __parallel )
229    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
230       char1 = 'calculated'
231    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
232               host(1:2) == 'lc' )  .AND.                          &
233             npex == -1  .AND.  pdims(2) == 1 )  THEN
234       char1 = 'forced'
235    ELSE
236       char1 = 'predefined'
237    ENDIF
238    IF ( threads_per_task == 1 )  THEN
239       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
240    ELSE
241       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
242                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
243    ENDIF
244    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
245           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
246         npex == -1  .AND.  pdims(2) == 1 )                      &
247    THEN
248       WRITE ( io, 106 )
249    ELSEIF ( pdims(2) == 1 )  THEN
250       WRITE ( io, 107 )  'x'
251    ELSEIF ( pdims(1) == 1 )  THEN
252       WRITE ( io, 107 )  'y'
253    ENDIF
254    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
255    IF ( numprocs /= maximum_parallel_io_streams )  THEN
256       WRITE ( io, 108 )  maximum_parallel_io_streams
257    ENDIF
258#endif
259    WRITE ( io, 99 )
260
261!
262!-- Numerical schemes
263    WRITE ( io, 110 )
264    IF ( psolver(1:7) == 'poisfft' )  THEN
265       WRITE ( io, 111 )  TRIM( fft_method )
266       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
267    ELSEIF ( psolver == 'sor' )  THEN
268       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
269    ELSEIF ( psolver == 'multigrid' )  THEN
270       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
271       IF ( mg_cycles == -1 )  THEN
272          WRITE ( io, 140 )  residual_limit
273       ELSE
274          WRITE ( io, 141 )  mg_cycles
275       ENDIF
276       IF ( mg_switch_to_pe0_level == 0 )  THEN
277          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
278                             nzt_mg(1)
279       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
280          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
281                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
282                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
283                             nzt_mg(mg_switch_to_pe0_level),    &
284                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
285                             nzt_mg(1)
286       ENDIF
287       IF ( masking_method )  WRITE ( io, 144 )
288    ENDIF
289    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
290    THEN
291       WRITE ( io, 142 )
292    ENDIF
293
294    IF ( momentum_advec == 'pw-scheme' )  THEN
295       WRITE ( io, 113 )
296    ELSEIF (momentum_advec == 'ws-scheme' ) THEN
297       WRITE ( io, 503 )
298    ELSEIF (momentum_advec == 'ups-scheme' ) THEN
299       WRITE ( io, 114 )
300       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
301       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
302            overshoot_limit_w /= 0.0 )  THEN
303          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
304                             overshoot_limit_w
305       ENDIF
306       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
307            ups_limit_w /= 0.0 )                               &
308       THEN
309          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
310       ENDIF
311       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
312    ENDIF
313    IF ( scalar_advec == 'pw-scheme' )  THEN
314       WRITE ( io, 116 )
315    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
316       WRITE ( io, 504 )
317    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
318       WRITE ( io, 117 )
319       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
320       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
321          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
322       ENDIF
323       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
324          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
325       ENDIF
326    ELSE
327       WRITE ( io, 118 )
328    ENDIF
329
330    WRITE ( io, 139 )  TRIM( loop_optimization )
331
332    IF ( galilei_transformation )  THEN
333       IF ( use_ug_for_galilei_tr )  THEN
334          char1 = '0.6 * geostrophic wind'
335       ELSE
336          char1 = 'mean wind in model domain'
337       ENDIF
338       IF ( simulated_time_at_begin == simulated_time )  THEN
339          char2 = 'at the start of the run'
340       ELSE
341          char2 = 'at the end of the run'
342       ENDIF
343       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
344                          advected_distance_x/1000.0, advected_distance_y/1000.0
345    ENDIF
346    IF ( timestep_scheme == 'leapfrog' )  THEN
347       WRITE ( io, 120 )
348    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
349       WRITE ( io, 121 )
350    ELSE
351       WRITE ( io, 122 )  timestep_scheme
352    ENDIF
353    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
354    IF ( rayleigh_damping_factor /= 0.0 )  THEN
355       IF ( .NOT. ocean )  THEN
356          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
357               rayleigh_damping_factor
358       ELSE
359          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
360               rayleigh_damping_factor
361       ENDIF
362    ENDIF
363    IF ( neutral )  WRITE ( io, 131 )  pt_surface
364    IF ( humidity )  THEN
365       IF ( .NOT. cloud_physics )  THEN
366          WRITE ( io, 129 )
367       ELSE
368          WRITE ( io, 130 )
369       ENDIF
370    ENDIF
371    IF ( passive_scalar )  WRITE ( io, 134 )
372    IF ( conserve_volume_flow )  THEN
373       WRITE ( io, 150 )  conserve_volume_flow_mode
374       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
375          WRITE ( io, 151 )  u_bulk, v_bulk
376       ENDIF
377    ELSEIF ( dp_external )  THEN
378       IF ( dp_smooth )  THEN
379          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
380       ELSE
381          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
382       ENDIF
383    ENDIF
384    IF ( large_scale_subsidence )  THEN
385        WRITE ( io, 153 )
386        WRITE ( io, 154 )
387    ENDIF
388    WRITE ( io, 99 )
389
390!
391!-- Runtime and timestep informations
392    WRITE ( io, 200 )
393    IF ( .NOT. dt_fixed )  THEN
394       WRITE ( io, 201 )  dt_max, cfl_factor
395    ELSE
396       WRITE ( io, 202 )  dt
397    ENDIF
398    WRITE ( io, 203 )  simulated_time_at_begin, end_time
399
400    IF ( time_restart /= 9999999.9  .AND. &
401         simulated_time_at_begin == simulated_time )  THEN
402       IF ( dt_restart == 9999999.9 )  THEN
403          WRITE ( io, 204 )  ' Restart at:       ',time_restart
404       ELSE
405          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
406       ENDIF
407    ENDIF
408
409    IF ( simulated_time_at_begin /= simulated_time )  THEN
410       i = MAX ( log_point_s(10)%counts, 1 )
411       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
412          cpuseconds_per_simulated_second = 0.0
413       ELSE
414          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
415                                            ( simulated_time -    &
416                                              simulated_time_at_begin )
417       ENDIF
418       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
419                          log_point_s(10)%sum / REAL( i ),     &
420                          cpuseconds_per_simulated_second
421       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
422          IF ( dt_restart == 9999999.9 )  THEN
423             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
424          ELSE
425             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
426          ENDIF
427       ENDIF
428    ENDIF
429
430!
431!-- Start time for coupled runs, if independent precursor runs for atmosphere
432!-- and ocean are used. In this case, coupling_start_time defines the time
433!-- when the coupling is switched on.
434    IF ( coupling_start_time /= 0.0 )  THEN
435       IF ( coupling_start_time >= simulated_time_at_begin )  THEN
436          char1 = 'Precursor run for a coupled atmosphere-ocean run'
437       ELSE
438          char1 = 'Coupled atmosphere-ocean run following independent ' // &
439                  'precursor runs'
440       ENDIF
441       WRITE ( io, 207 )  char1, coupling_start_time
442    ENDIF
443
444!
445!-- Computational grid
446    IF ( .NOT. ocean )  THEN
447       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
448       IF ( dz_stretch_level_index < nzt+1 )  THEN
449          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
450                             dz_stretch_factor, dz_max
451       ENDIF
452    ELSE
453       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
454       IF ( dz_stretch_level_index > 0 )  THEN
455          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
456                             dz_stretch_factor, dz_max
457       ENDIF
458    ENDIF
459    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
460                       MIN( nnz+2, nzt+2 )
461    IF ( numprocs > 1 )  THEN
462       IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
463          WRITE ( io, 255 )
464       ELSE
465          WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
466       ENDIF
467    ENDIF
468    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
469
470!
471!-- Topography
472    WRITE ( io, 270 )  topography
473    SELECT CASE ( TRIM( topography ) )
474
475       CASE ( 'flat' )
476          ! no actions necessary
477
478       CASE ( 'single_building' )
479          blx = INT( building_length_x / dx )
480          bly = INT( building_length_y / dy )
481          bh  = INT( building_height / dz )
482
483          IF ( building_wall_left == 9999999.9 )  THEN
484             building_wall_left = ( nx + 1 - blx ) / 2 * dx
485          ENDIF
486          bxl = INT ( building_wall_left / dx + 0.5 )
487          bxr = bxl + blx
488
489          IF ( building_wall_south == 9999999.9 )  THEN
490             building_wall_south = ( ny + 1 - bly ) / 2 * dy
491          ENDIF
492          bys = INT ( building_wall_south / dy + 0.5 )
493          byn = bys + bly
494
495          WRITE ( io, 271 )  building_length_x, building_length_y, &
496                             building_height, bxl, bxr, bys, byn
497
498       CASE ( 'single_street_canyon' )
499          ch  = NINT( canyon_height / dz )
500          IF ( canyon_width_x /= 9999999.9 )  THEN
501!
502!--          Street canyon in y direction
503             cwx = NINT( canyon_width_x / dx )
504             IF ( canyon_wall_left == 9999999.9 )  THEN
505                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
506             ENDIF
507             cxl = NINT( canyon_wall_left / dx )
508             cxr = cxl + cwx
509             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
510
511          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
512!
513!--          Street canyon in x direction
514             cwy = NINT( canyon_width_y / dy )
515             IF ( canyon_wall_south == 9999999.9 )  THEN
516                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
517             ENDIF
518             cys = NINT( canyon_wall_south / dy )
519             cyn = cys + cwy
520             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
521          ENDIF
522
523    END SELECT
524
525    IF ( TRIM( topography ) /= 'flat' )  THEN
526       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
527          IF ( TRIM( topography ) == 'single_building' .OR.  &
528               TRIM( topography ) == 'single_street_canyon' )  THEN
529             WRITE ( io, 278 )
530          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
531             WRITE ( io, 279 )
532          ENDIF
533       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
534          WRITE ( io, 278 )
535       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
536          WRITE ( io, 279 )
537       ENDIF
538    ENDIF
539
540    IF ( plant_canopy ) THEN
541
542       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
543       IF ( passive_scalar ) THEN
544          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
545                            leaf_surface_concentration
546       ENDIF
547
548!
549!--    Heat flux at the top of vegetation
550       WRITE ( io, 282 ) cthf
551
552!
553!--    Leaf area density profile
554!--    Building output strings, starting with surface value
555       WRITE ( learde, '(F6.4)' )  lad_surface
556       gradients = '------'
557       slices = '     0'
558       coordinates = '   0.0'
559       i = 1
560       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
561
562          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
563          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
564
565          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
566          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
567
568          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
569          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
570
571          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
572          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
573
574          i = i + 1
575       ENDDO
576
577       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
578                          TRIM( gradients ), TRIM( slices )
579
580    ENDIF
581
582!
583!-- Boundary conditions
584    IF ( ibc_p_b == 0 )  THEN
585       runten = 'p(0)     = 0      |'
586    ELSEIF ( ibc_p_b == 1 )  THEN
587       runten = 'p(0)     = p(1)   |'
588    ELSE
589       runten = 'p(0)     = p(1) +R|'
590    ENDIF
591    IF ( ibc_p_t == 0 )  THEN
592       roben  = 'p(nzt+1) = 0      |'
593    ELSE
594       roben  = 'p(nzt+1) = p(nzt) |'
595    ENDIF
596
597    IF ( ibc_uv_b == 0 )  THEN
598       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
599    ELSE
600       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
601    ENDIF
602    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
603       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
604    ELSEIF ( ibc_uv_t == 0 )  THEN
605       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
606    ELSE
607       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
608    ENDIF
609
610    IF ( ibc_pt_b == 0 )  THEN
611       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
612    ELSEIF ( ibc_pt_b == 1 )  THEN
613       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
614    ELSEIF ( ibc_pt_b == 2 )  THEN
615       runten = TRIM( runten ) // ' pt(0) = from coupled model'
616    ENDIF
617    IF ( ibc_pt_t == 0 )  THEN
618       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
619    ELSEIF( ibc_pt_t == 1 )  THEN
620       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
621    ELSEIF( ibc_pt_t == 2 )  THEN
622       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
623
624    ENDIF
625
626    WRITE ( io, 300 )  runten, roben
627
628    IF ( .NOT. constant_diffusion )  THEN
629       IF ( ibc_e_b == 1 )  THEN
630          runten = 'e(0)     = e(1)'
631       ELSE
632          runten = 'e(0)     = e(1) = (u*/0.1)**2'
633       ENDIF
634       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
635
636       WRITE ( io, 301 )  'e', runten, roben       
637
638    ENDIF
639
640    IF ( ocean )  THEN
641       runten = 'sa(0)    = sa(1)'
642       IF ( ibc_sa_t == 0 )  THEN
643          roben =  'sa(nzt+1) = sa_surface'
644       ELSE
645          roben =  'sa(nzt+1) = sa(nzt)'
646       ENDIF
647       WRITE ( io, 301 ) 'sa', runten, roben
648    ENDIF
649
650    IF ( humidity )  THEN
651       IF ( ibc_q_b == 0 )  THEN
652          runten = 'q(0)     = q_surface'
653       ELSE
654          runten = 'q(0)     = q(1)'
655       ENDIF
656       IF ( ibc_q_t == 0 )  THEN
657          roben =  'q(nzt)   = q_top'
658       ELSE
659          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
660       ENDIF
661       WRITE ( io, 301 ) 'q', runten, roben
662    ENDIF
663
664    IF ( passive_scalar )  THEN
665       IF ( ibc_q_b == 0 )  THEN
666          runten = 's(0)     = s_surface'
667       ELSE
668          runten = 's(0)     = s(1)'
669       ENDIF
670       IF ( ibc_q_t == 0 )  THEN
671          roben =  's(nzt)   = s_top'
672       ELSE
673          roben =  's(nzt)   = s(nzt-1) + ds/dz'
674       ENDIF
675       WRITE ( io, 301 ) 's', runten, roben
676    ENDIF
677
678    IF ( use_surface_fluxes )  THEN
679       WRITE ( io, 303 )
680       IF ( constant_heatflux )  THEN
681          WRITE ( io, 306 )  surface_heatflux
682          IF ( random_heatflux )  WRITE ( io, 307 )
683       ENDIF
684       IF ( humidity  .AND.  constant_waterflux )  THEN
685          WRITE ( io, 311 ) surface_waterflux
686       ENDIF
687       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
688          WRITE ( io, 313 ) surface_waterflux
689       ENDIF
690    ENDIF
691
692    IF ( use_top_fluxes )  THEN
693       WRITE ( io, 304 )
694       IF ( coupling_mode == 'uncoupled' )  THEN
695          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
696          IF ( constant_top_heatflux )  THEN
697             WRITE ( io, 306 )  top_heatflux
698          ENDIF
699       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
700          WRITE ( io, 316 )
701       ENDIF
702       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
703          WRITE ( io, 309 )  top_salinityflux
704       ENDIF
705       IF ( humidity  .OR.  passive_scalar )  THEN
706          WRITE ( io, 315 )
707       ENDIF
708    ENDIF
709
710    IF ( prandtl_layer )  THEN
711       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
712                          z0h_factor*roughness_length, kappa, &
713                          rif_min, rif_max
714       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
715       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
716          WRITE ( io, 312 )
717       ENDIF
718       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
719          WRITE ( io, 314 )
720       ENDIF
721    ELSE
722       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
723          WRITE ( io, 310 )  rif_min, rif_max
724       ENDIF
725    ENDIF
726
727    WRITE ( io, 317 )  bc_lr, bc_ns
728    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
729       WRITE ( io, 318 )  pt_damping_width, pt_damping_factor       
730       IF ( turbulent_inflow )  THEN
731          WRITE ( io, 319 )  recycling_width, recycling_plane, &
732                             inflow_damping_height, inflow_damping_width
733       ENDIF
734    ENDIF
735
736!
737!-- Listing of 1D-profiles
738    WRITE ( io, 325 )  dt_dopr_listing
739    IF ( averaging_interval_pr /= 0.0 )  THEN
740       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
741    ENDIF
742
743!
744!-- DATA output
745    WRITE ( io, 330 )
746    IF ( averaging_interval_pr /= 0.0 )  THEN
747       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
748    ENDIF
749
750!
751!-- 1D-profiles
752    dopr_chr = 'Profile:'
753    IF ( dopr_n /= 0 )  THEN
754       WRITE ( io, 331 )
755
756       output_format = ''
757       IF ( netcdf_output )  THEN
758          IF ( netcdf_data_format == 1 )  THEN
759             output_format = 'NetCDF classic'
760          ELSE
761             output_format = 'NetCDF 64bit offset'
762          ENDIF
763       ENDIF
764       WRITE ( io, 344 )  output_format
765
766       DO  i = 1, dopr_n
767          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
768          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
769             WRITE ( io, 332 )  dopr_chr
770             dopr_chr = '       :'
771          ENDIF
772       ENDDO
773
774       IF ( dopr_chr /= '' )  THEN
775          WRITE ( io, 332 )  dopr_chr
776       ENDIF
777       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
778       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
779    ENDIF
780
781!
782!-- 2D-arrays
783    DO  av = 0, 1
784
785       i = 1
786       do2d_xy = ''
787       do2d_xz = ''
788       do2d_yz = ''
789       DO  WHILE ( do2d(av,i) /= ' ' )
790
791          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
792          do2d_mode = do2d(av,i)(l-1:l)
793
794          SELECT CASE ( do2d_mode )
795             CASE ( 'xy' )
796                ll = LEN_TRIM( do2d_xy )
797                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
798             CASE ( 'xz' )
799                ll = LEN_TRIM( do2d_xz )
800                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
801             CASE ( 'yz' )
802                ll = LEN_TRIM( do2d_yz )
803                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
804          END SELECT
805
806          i = i + 1
807
808       ENDDO
809
810       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
811              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
812              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
813            ( netcdf_output  .OR.  iso2d_output ) )  THEN
814
815          IF (  av == 0 )  THEN
816             WRITE ( io, 334 )  ''
817          ELSE
818             WRITE ( io, 334 )  '(time-averaged)'
819          ENDIF
820
821          IF ( do2d_at_begin )  THEN
822             begin_chr = 'and at the start'
823          ELSE
824             begin_chr = ''
825          ENDIF
826
827          output_format = ''
828          IF ( netcdf_output )  THEN
829             IF ( netcdf_data_format == 1 )  THEN
830                output_format = 'NetCDF classic'
831             ELSEIF ( netcdf_data_format == 2 )  THEN
832                output_format = 'NetCDF 64bit offset'
833             ELSEIF ( netcdf_data_format == 3 )  THEN
834                output_format = 'NetCDF4/HDF5'
835             ELSEIF ( netcdf_data_format == 4 )  THEN
836                output_format = 'NetCDF4/HDF5 clasic'
837             ENDIF
838          ENDIF
839          IF ( iso2d_output )  THEN
840             IF ( netcdf_output )  THEN
841                output_format = TRIM( output_format ) // ' and iso2d'
842             ELSE
843                output_format = 'iso2d'
844             ENDIF
845          ENDIF
846          WRITE ( io, 344 )  output_format
847
848          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
849             i = 1
850             slices = '/'
851             coordinates = '/'
852!
853!--          Building strings with index and coordinate informations of the
854!--          slices
855             DO  WHILE ( section(i,1) /= -9999 )
856
857                WRITE (section_chr,'(I5)')  section(i,1)
858                section_chr = ADJUSTL( section_chr )
859                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
860
861                IF ( section(i,1) == -1 )  THEN
862                   WRITE (coor_chr,'(F10.1)')  -1.0
863                ELSE
864                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
865                ENDIF
866                coor_chr = ADJUSTL( coor_chr )
867                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
868
869                i = i + 1
870             ENDDO
871             IF ( av == 0 )  THEN
872                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
873                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
874                                   TRIM( coordinates )
875                IF ( skip_time_do2d_xy /= 0.0 )  THEN
876                   WRITE ( io, 339 )  skip_time_do2d_xy
877                ENDIF
878             ELSE
879                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
880                                   TRIM( begin_chr ), averaging_interval, &
881                                   dt_averaging_input, 'k', TRIM( slices ), &
882                                   TRIM( coordinates )
883                IF ( skip_time_data_output_av /= 0.0 )  THEN
884                   WRITE ( io, 339 )  skip_time_data_output_av
885                ENDIF
886             ENDIF
887
888          ENDIF
889
890          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
891             i = 1
892             slices = '/'
893             coordinates = '/'
894!
895!--          Building strings with index and coordinate informations of the
896!--          slices
897             DO  WHILE ( section(i,2) /= -9999 )
898
899                WRITE (section_chr,'(I5)')  section(i,2)
900                section_chr = ADJUSTL( section_chr )
901                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
902
903                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
904                coor_chr = ADJUSTL( coor_chr )
905                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
906
907                i = i + 1
908             ENDDO
909             IF ( av == 0 )  THEN
910                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
911                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
912                                   TRIM( coordinates )
913                IF ( skip_time_do2d_xz /= 0.0 )  THEN
914                   WRITE ( io, 339 )  skip_time_do2d_xz
915                ENDIF
916             ELSE
917                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
918                                   TRIM( begin_chr ), averaging_interval, &
919                                   dt_averaging_input, 'j', TRIM( slices ), &
920                                   TRIM( coordinates )
921                IF ( skip_time_data_output_av /= 0.0 )  THEN
922                   WRITE ( io, 339 )  skip_time_data_output_av
923                ENDIF
924             ENDIF
925          ENDIF
926
927          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
928             i = 1
929             slices = '/'
930             coordinates = '/'
931!
932!--          Building strings with index and coordinate informations of the
933!--          slices
934             DO  WHILE ( section(i,3) /= -9999 )
935
936                WRITE (section_chr,'(I5)')  section(i,3)
937                section_chr = ADJUSTL( section_chr )
938                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
939
940                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
941                coor_chr = ADJUSTL( coor_chr )
942                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
943
944                i = i + 1
945             ENDDO
946             IF ( av == 0 )  THEN
947                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
948                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
949                                   TRIM( coordinates )
950                IF ( skip_time_do2d_yz /= 0.0 )  THEN
951                   WRITE ( io, 339 )  skip_time_do2d_yz
952                ENDIF
953             ELSE
954                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
955                                   TRIM( begin_chr ), averaging_interval, &
956                                   dt_averaging_input, 'i', TRIM( slices ), &
957                                   TRIM( coordinates )
958                IF ( skip_time_data_output_av /= 0.0 )  THEN
959                   WRITE ( io, 339 )  skip_time_data_output_av
960                ENDIF
961             ENDIF
962          ENDIF
963
964       ENDIF
965
966    ENDDO
967
968!
969!-- 3d-arrays
970    DO  av = 0, 1
971
972       i = 1
973       do3d_chr = ''
974       DO  WHILE ( do3d(av,i) /= ' ' )
975
976          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
977          i = i + 1
978
979       ENDDO
980
981       IF ( do3d_chr /= '' )  THEN
982          IF ( av == 0 )  THEN
983             WRITE ( io, 336 )  ''
984          ELSE
985             WRITE ( io, 336 )  '(time-averaged)'
986          ENDIF
987
988          output_format = ''
989          IF ( netcdf_output )  THEN
990             IF ( netcdf_data_format == 1 )  THEN
991                output_format = 'NetCDF classic'
992             ELSEIF ( netcdf_data_format == 2 )  THEN
993                output_format = 'NetCDF 64bit offset'
994             ELSEIF ( netcdf_data_format == 3 )  THEN
995                output_format = 'NetCDF4/HDF5'
996             ELSEIF ( netcdf_data_format == 4 )  THEN
997                output_format = 'NetCDF4/HDF5 clasic'
998             ENDIF
999          ENDIF
1000          IF ( avs_output )  THEN
1001             IF ( netcdf_output )  THEN
1002                output_format = TRIM( output_format ) // ' and avs'
1003             ELSE
1004                output_format = 'avs'
1005             ENDIF
1006          ENDIF
1007          WRITE ( io, 344 )  output_format
1008
1009          IF ( do3d_at_begin )  THEN
1010             begin_chr = 'and at the start'
1011          ELSE
1012             begin_chr = ''
1013          ENDIF
1014          IF ( av == 0 )  THEN
1015             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1016                                zu(nz_do3d), nz_do3d
1017          ELSE
1018             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1019                                TRIM( begin_chr ), averaging_interval, &
1020                                dt_averaging_input, zu(nz_do3d), nz_do3d
1021          ENDIF
1022
1023          IF ( do3d_compress )  THEN
1024             do3d_chr = ''
1025             i = 1
1026             DO WHILE ( do3d(av,i) /= ' ' )
1027
1028                SELECT CASE ( do3d(av,i) )
1029                   CASE ( 'u' )
1030                      j = 1
1031                   CASE ( 'v' )
1032                      j = 2
1033                   CASE ( 'w' )
1034                      j = 3
1035                   CASE ( 'p' )
1036                      j = 4
1037                   CASE ( 'pt' )
1038                      j = 5
1039                END SELECT
1040                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1041                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1042                           ':' // prec // ','
1043                i = i + 1
1044
1045             ENDDO
1046             WRITE ( io, 338 )  do3d_chr
1047
1048          ENDIF
1049
1050          IF ( av == 0 )  THEN
1051             IF ( skip_time_do3d /= 0.0 )  THEN
1052                WRITE ( io, 339 )  skip_time_do3d
1053             ENDIF
1054          ELSE
1055             IF ( skip_time_data_output_av /= 0.0 )  THEN
1056                WRITE ( io, 339 )  skip_time_data_output_av
1057             ENDIF
1058          ENDIF
1059
1060       ENDIF
1061
1062    ENDDO
1063
1064!
1065!-- masked arrays
1066    IF ( masks > 0 )  WRITE ( io, 345 )  &
1067         mask_scale_x, mask_scale_y, mask_scale_z
1068    DO  mid = 1, masks
1069       DO  av = 0, 1
1070
1071          i = 1
1072          domask_chr = ''
1073          DO  WHILE ( domask(mid,av,i) /= ' ' )
1074             domask_chr = TRIM( domask_chr ) // ' ' //  &
1075                          TRIM( domask(mid,av,i) ) // ','
1076             i = i + 1
1077          ENDDO
1078
1079          IF ( domask_chr /= '' )  THEN
1080             IF ( av == 0 )  THEN
1081                WRITE ( io, 346 )  '', mid
1082             ELSE
1083                WRITE ( io, 346 )  ' (time-averaged)', mid
1084             ENDIF
1085
1086             output_format = ''
1087             IF ( netcdf_output )  THEN
1088                IF ( netcdf_data_format == 1 )  THEN
1089                   output_format = 'NetCDF classic'
1090                ELSEIF ( netcdf_data_format == 2 )  THEN
1091                   output_format = 'NetCDF 64bit offset'
1092                ELSEIF ( netcdf_data_format == 3 )  THEN
1093                   output_format = 'NetCDF4/HDF5'
1094                ELSEIF ( netcdf_data_format == 4 )  THEN
1095                   output_format = 'NetCDF4/HDF5 clasic'
1096                ENDIF
1097             ENDIF
1098             WRITE ( io, 344 )  output_format
1099
1100             IF ( av == 0 )  THEN
1101                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1102             ELSE
1103                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1104                                   averaging_interval, dt_averaging_input
1105             ENDIF
1106
1107             IF ( av == 0 )  THEN
1108                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1109                   WRITE ( io, 339 )  skip_time_domask(mid)
1110                ENDIF
1111             ELSE
1112                IF ( skip_time_data_output_av /= 0.0 )  THEN
1113                   WRITE ( io, 339 )  skip_time_data_output_av
1114                ENDIF
1115             ENDIF
1116!
1117!--          output locations
1118             DO  dim = 1, 3
1119                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1120                   count = 0
1121                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1122                      count = count + 1
1123                   ENDDO
1124                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1125                                      mask(mid,dim,:count)
1126                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1127                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1128                         mask_loop(mid,dim,3) == 0.0 )  THEN
1129                   WRITE ( io, 350 )  dir(dim), dir(dim)
1130                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1131                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1132                                      mask_loop(mid,dim,1:2)
1133                ELSE
1134                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1135                                      mask_loop(mid,dim,1:3)
1136                ENDIF
1137             ENDDO
1138          ENDIF
1139
1140       ENDDO
1141    ENDDO
1142
1143!
1144!-- Timeseries
1145    IF ( dt_dots /= 9999999.9 )  THEN
1146       WRITE ( io, 340 )
1147
1148       output_format = ''
1149       IF ( netcdf_output )  THEN
1150          IF ( netcdf_data_format == 1 )  THEN
1151             output_format = 'NetCDF classic'
1152          ELSE
1153             output_format = 'NetCDF 64bit offset'
1154          ENDIF
1155       ENDIF
1156       WRITE ( io, 344 )  output_format
1157       WRITE ( io, 341 )  dt_dots
1158    ENDIF
1159
1160#if defined( __dvrp_graphics )
1161!
1162!-- Dvrp-output
1163    IF ( dt_dvrp /= 9999999.9 )  THEN
1164       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1165                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1166       i = 1
1167       l = 0
1168       m = 0
1169       DO WHILE ( mode_dvrp(i) /= ' ' )
1170          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1171             READ ( mode_dvrp(i), '(10X,I2)' )  j
1172             l = l + 1
1173             IF ( do3d(0,j) /= ' ' )  THEN
1174                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1175                                   isosurface_color(:,l)
1176             ENDIF
1177          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1178             READ ( mode_dvrp(i), '(6X,I2)' )  j
1179             m = m + 1
1180             IF ( do2d(0,j) /= ' ' )  THEN
1181                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1182                                   slicer_range_limits_dvrp(:,m)
1183             ENDIF
1184          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1185             WRITE ( io, 363 )  dvrp_psize
1186             IF ( particle_dvrpsize /= 'none' )  THEN
1187                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1188                                   dvrpsize_interval
1189             ENDIF
1190             IF ( particle_color /= 'none' )  THEN
1191                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1192                                   color_interval
1193             ENDIF
1194          ENDIF
1195          i = i + 1
1196       ENDDO
1197
1198       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1199                          superelevation_y, superelevation, clip_dvrp_l, &
1200                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1201
1202       IF ( TRIM( topography ) /= 'flat' )  THEN
1203          WRITE ( io, 366 )  topography_color
1204          IF ( cluster_size > 1 )  THEN
1205             WRITE ( io, 367 )  cluster_size
1206          ENDIF
1207       ENDIF
1208
1209    ENDIF
1210#endif
1211
1212#if defined( __spectra )
1213!
1214!-- Spectra output
1215    IF ( dt_dosp /= 9999999.9 ) THEN
1216       WRITE ( io, 370 )
1217
1218       output_format = ''
1219       IF ( netcdf_output )  THEN
1220          IF ( netcdf_data_format == 1 )  THEN
1221             output_format = 'NetCDF classic'
1222          ELSE
1223             output_format = 'NetCDF 64bit offset'
1224          ENDIF
1225       ENDIF
1226       WRITE ( io, 344 )  output_format
1227       WRITE ( io, 371 )  dt_dosp
1228       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1229       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1230                          ( spectra_direction(i), i = 1,10 ),  &
1231                          ( comp_spectra_level(i), i = 1,100 ), &
1232                          ( plot_spectra_level(i), i = 1,100 ), &
1233                          averaging_interval_sp, dt_averaging_input_pr
1234    ENDIF
1235#endif
1236
1237    WRITE ( io, 99 )
1238
1239!
1240!-- Physical quantities
1241    WRITE ( io, 400 )
1242
1243!
1244!-- Geostrophic parameters
1245    WRITE ( io, 410 )  omega, phi, f, fs
1246
1247!
1248!-- Other quantities
1249    WRITE ( io, 411 )  g
1250    IF ( use_reference )  THEN
1251       IF ( ocean )  THEN
1252          WRITE ( io, 412 )  prho_reference
1253       ELSE
1254          WRITE ( io, 413 )  pt_reference
1255       ENDIF
1256    ENDIF
1257
1258!
1259!-- Cloud physics parameters
1260    IF ( cloud_physics ) THEN
1261       WRITE ( io, 415 )
1262       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1263    ENDIF
1264
1265!-- Profile of the geostrophic wind (component ug)
1266!-- Building output strings
1267    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1268    gradients = '------'
1269    slices = '     0'
1270    coordinates = '   0.0'
1271    i = 1
1272    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1273     
1274       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1275       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1276
1277       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1278       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1279
1280       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1281       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1282
1283       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1284       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1285
1286       IF ( i == 10 )  THEN
1287          EXIT
1288       ELSE
1289          i = i + 1
1290       ENDIF
1291
1292    ENDDO
1293
1294    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1295                       TRIM( gradients ), TRIM( slices )
1296
1297!-- Profile of the geostrophic wind (component vg)
1298!-- Building output strings
1299    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1300    gradients = '------'
1301    slices = '     0'
1302    coordinates = '   0.0'
1303    i = 1
1304    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1305
1306       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1307       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1308
1309       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1310       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1311
1312       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1313       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1314
1315       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1316       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1317
1318       IF ( i == 10 )  THEN
1319          EXIT
1320       ELSE
1321          i = i + 1
1322       ENDIF
1323 
1324    ENDDO
1325
1326    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1327                       TRIM( gradients ), TRIM( slices )
1328
1329!
1330!-- Initial wind profiles
1331    IF ( u_profile(1) /= 9999999.9 )  WRITE ( io, 427 )
1332
1333!
1334!-- Initial temperature profile
1335!-- Building output strings, starting with surface temperature
1336    WRITE ( temperatures, '(F6.2)' )  pt_surface
1337    gradients = '------'
1338    slices = '     0'
1339    coordinates = '   0.0'
1340    i = 1
1341    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1342
1343       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1344       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1345
1346       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1347       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1348
1349       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1350       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1351
1352       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1353       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1354
1355       IF ( i == 10 )  THEN
1356          EXIT
1357       ELSE
1358          i = i + 1
1359       ENDIF
1360
1361    ENDDO
1362
1363    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1364                       TRIM( gradients ), TRIM( slices )
1365
1366!
1367!-- Initial humidity profile
1368!-- Building output strings, starting with surface humidity
1369    IF ( humidity  .OR.  passive_scalar )  THEN
1370       WRITE ( temperatures, '(E8.1)' )  q_surface
1371       gradients = '--------'
1372       slices = '       0'
1373       coordinates = '     0.0'
1374       i = 1
1375       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1376         
1377          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1378          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1379
1380          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1381          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1382         
1383          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1384          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1385         
1386          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1387          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1388
1389          IF ( i == 10 )  THEN
1390             EXIT
1391          ELSE
1392             i = i + 1
1393          ENDIF
1394
1395       ENDDO
1396
1397       IF ( humidity )  THEN
1398          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1399                             TRIM( gradients ), TRIM( slices )
1400       ELSE
1401          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1402                             TRIM( gradients ), TRIM( slices )
1403       ENDIF
1404    ENDIF
1405
1406!
1407!-- Initial salinity profile
1408!-- Building output strings, starting with surface salinity
1409    IF ( ocean )  THEN
1410       WRITE ( temperatures, '(F6.2)' )  sa_surface
1411       gradients = '------'
1412       slices = '     0'
1413       coordinates = '   0.0'
1414       i = 1
1415       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1416
1417          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1418          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1419
1420          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1421          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1422
1423          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1424          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1425
1426          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1427          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1428
1429          IF ( i == 10 )  THEN
1430             EXIT
1431          ELSE
1432             i = i + 1
1433          ENDIF
1434
1435       ENDDO
1436
1437       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1438                          TRIM( gradients ), TRIM( slices )
1439    ENDIF
1440
1441!
1442!-- Profile for the large scale vertial velocity
1443!-- Building output strings, starting with surface value
1444    IF ( large_scale_subsidence )  THEN
1445       temperatures = '   0.0'
1446       gradients = '------'
1447       slices = '     0'
1448       coordinates = '   0.0'
1449       i = 1
1450       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
1451
1452          WRITE (coor_chr,'(E10.2,7X)')  &
1453                                w_subs(subs_vertical_gradient_level_i(i))
1454          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1455
1456          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
1457          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1458
1459          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
1460          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1461
1462          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
1463          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1464
1465          IF ( i == 10 )  THEN
1466             EXIT
1467          ELSE
1468             i = i + 1
1469          ENDIF
1470
1471       ENDDO
1472
1473       WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1474                          TRIM( gradients ), TRIM( slices )
1475    ENDIF
1476
1477!
1478!-- Cloud physcis parameters / quantities / numerical methods
1479    WRITE ( io, 430 )
1480    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1481       WRITE ( io, 431 )
1482    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1483       WRITE ( io, 432 )
1484       IF ( radiation )      WRITE ( io, 132 )
1485       IF ( precipitation )  WRITE ( io, 133 )
1486    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1487       WRITE ( io, 433 )
1488       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1489       IF ( collision_kernel /= 'none' )  THEN
1490          WRITE ( io, 435 )  TRIM( collision_kernel )
1491          IF ( collision_kernel(6:9) == 'fast' )  THEN
1492             WRITE ( io, 436 )  radius_classes, dissipation_classes
1493          ENDIF
1494       ELSE
1495          WRITE ( io, 437 )
1496       ENDIF
1497    ENDIF
1498
1499!
1500!-- LES / turbulence parameters
1501    WRITE ( io, 450 )
1502
1503!--
1504! ... LES-constants used must still be added here
1505!--
1506    IF ( constant_diffusion )  THEN
1507       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1508                          prandtl_number
1509    ENDIF
1510    IF ( .NOT. constant_diffusion)  THEN
1511       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1512       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1513       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1514       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1515    ENDIF
1516
1517!
1518!-- Special actions during the run
1519    WRITE ( io, 470 )
1520    IF ( create_disturbances )  THEN
1521       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1522                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1523                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1524       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1525          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1526       ELSE
1527          WRITE ( io, 473 )  disturbance_energy_limit
1528       ENDIF
1529       WRITE ( io, 474 )  TRIM( random_generator )
1530    ENDIF
1531    IF ( pt_surface_initial_change /= 0.0 )  THEN
1532       WRITE ( io, 475 )  pt_surface_initial_change
1533    ENDIF
1534    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1535       WRITE ( io, 476 )  q_surface_initial_change       
1536    ENDIF
1537    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1538       WRITE ( io, 477 )  q_surface_initial_change       
1539    ENDIF
1540
1541    IF ( particle_advection )  THEN
1542!
1543!--    Particle attributes
1544       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1545                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1546                          end_time_prel, dt_sort_particles
1547       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1548       IF ( random_start_position )  WRITE ( io, 481 )
1549       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1550       WRITE ( io, 495 )  total_number_of_particles
1551       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1552          WRITE ( io, 483 )  maximum_number_of_tailpoints
1553          IF ( minimum_tailpoint_distance /= 0 )  THEN
1554             WRITE ( io, 484 )  total_number_of_tails,      &
1555                                minimum_tailpoint_distance, &
1556                                maximum_tailpoint_age
1557          ENDIF
1558       ENDIF
1559       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1560          WRITE ( io, 485 )  dt_write_particle_data
1561          output_format = ''
1562          IF ( netcdf_output )  THEN
1563             IF ( netcdf_data_format > 1 )  THEN
1564                output_format = 'netcdf (64 bit offset) and binary'
1565             ELSE
1566                output_format = 'netcdf and binary'
1567             ENDIF
1568          ELSE
1569             output_format = 'binary'
1570          ENDIF
1571          WRITE ( io, 344 )  output_format
1572       ENDIF
1573       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1574       IF ( write_particle_statistics )  WRITE ( io, 486 )
1575
1576       WRITE ( io, 487 )  number_of_particle_groups
1577
1578       DO  i = 1, number_of_particle_groups
1579          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1580             WRITE ( io, 490 )  i, 0.0
1581             WRITE ( io, 492 )
1582          ELSE
1583             WRITE ( io, 490 )  i, radius(i)
1584             IF ( density_ratio(i) /= 0.0 )  THEN
1585                WRITE ( io, 491 )  density_ratio(i)
1586             ELSE
1587                WRITE ( io, 492 )
1588             ENDIF
1589          ENDIF
1590          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1591                             pdx(i), pdy(i), pdz(i)
1592          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1593       ENDDO
1594
1595    ENDIF
1596
1597
1598!
1599!-- Parameters of 1D-model
1600    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1601       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1602                          mixing_length_1d, dissipation_1d
1603       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1604          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1605       ENDIF
1606    ENDIF
1607
1608!
1609!-- User-defined informations
1610    CALL user_header( io )
1611
1612    WRITE ( io, 99 )
1613
1614!
1615!-- Write buffer contents to disc immediately
1616    CALL local_flush( io )
1617
1618!
1619!-- Here the FORMATs start
1620
1621 99 FORMAT (1X,78('-'))
1622100 FORMAT (/1X,'***************************',9X,42('-')/        &
1623            1X,'* ',A,' *',9X,A/                               &
1624            1X,'***************************',9X,42('-'))
1625101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1626            37X,42('-'))
1627102 FORMAT (/' Date:              ',A8,9X,'Run:       ',A20/      &
1628            ' Time:              ',A8,9X,'Run-No.:   ',I2.2/     &
1629            ' Run on host:     ',A10)
1630#if defined( __parallel )
1631103 FORMAT (' Number of PEs:',8X,I5,9X,'Processor grid (x,y): (',I3,',',I3, &
1632              ')',1X,A)
1633104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1634              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1635105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1636106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1637            37X,'because the job is running on an SMP-cluster')
1638107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1639108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
1640#endif
1641110 FORMAT (/' Numerical Schemes:'/ &
1642             ' -----------------'/)
1643111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1644112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1645            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1646113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1647                  ' or Upstream')
1648114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1649115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1650116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1651                  ' or Upstream')
1652117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1653118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1654119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1655            '     Translation velocity = ',A/ &
1656            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1657120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1658                  ' of timestep changes)')
1659121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1660                  ' timestep changes')
1661122 FORMAT (' --> Time differencing scheme: ',A)
1662123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1663            '     maximum damping coefficient: ',F5.3, ' 1/s')
1664124 FORMAT ('     Spline-overshoots are being suppressed')
1665125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1666                  ' of'/                                                       &
1667            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1668126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1669                  ' of'/                                                       &
1670            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1671127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1672            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1673128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1674            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1675129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1676130 FORMAT (' --> Additional prognostic equation for the total water content')
1677131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1678                  F6.2, ' K assumed')
1679132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1680            '     effective emissivity scheme')
1681133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1682134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1683135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1684                  A,'-cycle)'/ &
1685            '     number of grid levels:                   ',I2/ &
1686            '     Gauss-Seidel red/black iterations:       ',I2)
1687136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1688                  I3,')')
1689137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1690            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1691                  I3,')'/ &
1692            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1693                  I3,')')
1694138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1695139 FORMAT (' --> Loop optimization method: ',A)
1696140 FORMAT ('     maximum residual allowed:                ',E10.3)
1697141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1698142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1699                  'step')
1700143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1701                  'kinetic energy')
1702144 FORMAT ('     masking method is used')
1703150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1704                  'conserved'/ &
1705            '     using the ',A,' mode')
1706151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1707152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1708           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1709           /'     starting from dp_level_b =', F8.3, 'm', A /)
1710153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1711                  'prognostic equation for')
1712154 FORMAT ('     the potential temperature')
1713200 FORMAT (//' Run time and time step information:'/ &
1714             ' ----------------------------------'/)
1715201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1716             '    CFL-factor: ',F4.2)
1717202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1718203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1719             ' End time:         ',F9.3,' s')
1720204 FORMAT ( A,F9.3,' s')
1721205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1722206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1723             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1724               '  ',F9.3,' s'/                                                 &
1725             '                                   per second of simulated tim', &
1726               'e: ',F9.3,' s')
1727207 FORMAT ( A/' Coupling start time:',F9.3,' s')
1728250 FORMAT (//' Computational grid and domain size:'/ &
1729              ' ----------------------------------'// &
1730              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1731              ' m    dz =    ',F7.3,' m'/ &
1732              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1733              ' m  z(u) = ',F10.3,' m'/)
1734252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1735              ' factor: ',F5.3/ &
1736            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1737254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1738            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1739255 FORMAT (' Subdomains have equal size')
1740256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1741              'have smaller sizes'/                                          &
1742            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1743260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1744             ' degrees')
1745270 FORMAT (//' Topography informations:'/ &
1746              ' -----------------------'// &
1747              1X,'Topography: ',A)
1748271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1749              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1750                ' / ',I4)
1751272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1752              ' direction' / &
1753              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1754              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1755278 FORMAT (' Topography grid definition convention:'/ &
1756            ' cell edge (staggered grid points'/  &
1757            ' (u in x-direction, v in y-direction))' /)
1758279 FORMAT (' Topography grid definition convention:'/ &
1759            ' cell center (scalar grid points)' /)
1760280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1761              ' ------------------------------'// &
1762              ' Canopy mode: ', A / &
1763              ' Canopy top: ',I4 / &
1764              ' Leaf drag coefficient: ',F6.2 /)
1765281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1766              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1767282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1768283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1769              ' Height:              ',A,'  m'/ &
1770              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1771              ' Gradient:            ',A,'  m**2/m**4'/ &
1772              ' Gridpoint:           ',A)
1773               
1774300 FORMAT (//' Boundary conditions:'/ &
1775             ' -------------------'// &
1776             '                     p                    uv             ', &
1777             '                   pt'// &
1778             ' B. bound.: ',A/ &
1779             ' T. bound.: ',A)
1780301 FORMAT (/'                     ',A// &
1781             ' B. bound.: ',A/ &
1782             ' T. bound.: ',A)
1783303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1784304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1785305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1786               'computational u,v-level:'// &
1787             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1788             ' m   kappa = ',F4.2/ &
1789             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1790306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1791307 FORMAT ('       Heatflux has a random normal distribution')
1792308 FORMAT ('       Predefined surface temperature')
1793309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1794310 FORMAT (//'    1D-Model:'// &
1795             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1796311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1797312 FORMAT ('       Predefined surface humidity')
1798313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1799314 FORMAT ('       Predefined scalar value at the surface')
1800315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1801316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1802                    'atmosphere model')
1803317 FORMAT (//' Lateral boundaries:'/ &
1804            '       left/right:  ',A/    &
1805            '       north/south: ',A)
1806318 FORMAT (/'       pt damping layer width = ',F7.2,' m, pt ', &
1807                    'damping factor = ',F6.4)
1808319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1809            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1810            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1811320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1812            '                                          v: ',F9.6,' m**2/s**2')
1813325 FORMAT (//' List output:'/ &
1814             ' -----------'//  &
1815            '    1D-Profiles:'/    &
1816            '       Output every             ',F8.2,' s')
1817326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1818            '       Averaging input every    ',F8.2,' s')
1819330 FORMAT (//' Data output:'/ &
1820             ' -----------'/)
1821331 FORMAT (/'    1D-Profiles:')
1822332 FORMAT (/'       ',A)
1823333 FORMAT ('       Output every             ',F8.2,' s',/ &
1824            '       Time averaged over       ',F8.2,' s'/ &
1825            '       Averaging input every    ',F8.2,' s')
1826334 FORMAT (/'    2D-Arrays',A,':')
1827335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1828            '       Output every             ',F8.2,' s  ',A/ &
1829            '       Cross sections at ',A1,' = ',A/ &
1830            '       scalar-coordinates:   ',A,' m'/)
1831336 FORMAT (/'    3D-Arrays',A,':')
1832337 FORMAT (/'       Arrays: ',A/ &
1833            '       Output every             ',F8.2,' s  ',A/ &
1834            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1835338 FORMAT ('       Compressed data output'/ &
1836            '       Decimal precision: ',A/)
1837339 FORMAT ('       No output during initial ',F8.2,' s')
1838340 FORMAT (/'    Time series:')
1839341 FORMAT ('       Output every             ',F8.2,' s'/)
1840342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1841            '       Output every             ',F8.2,' s  ',A/ &
1842            '       Time averaged over       ',F8.2,' s'/ &
1843            '       Averaging input every    ',F8.2,' s'/ &
1844            '       Cross sections at ',A1,' = ',A/ &
1845            '       scalar-coordinates:   ',A,' m'/)
1846343 FORMAT (/'       Arrays: ',A/ &
1847            '       Output every             ',F8.2,' s  ',A/ &
1848            '       Time averaged over       ',F8.2,' s'/ &
1849            '       Averaging input every    ',F8.2,' s'/ &
1850            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1851344 FORMAT ('       Output format: ',A/)
1852345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1853            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1854            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1855            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1856346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1857347 FORMAT ('       Variables: ',A/ &
1858            '       Output every             ',F8.2,' s')
1859348 FORMAT ('       Variables: ',A/ &
1860            '       Output every             ',F8.2,' s'/ &
1861            '       Time averaged over       ',F8.2,' s'/ &
1862            '       Averaging input every    ',F8.2,' s')
1863349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1864            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1865            13('       ',8(F8.2,',')/) )
1866350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1867            'all gridpoints along ',A,'-direction (default).' )
1868351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1869            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1870            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1871#if defined( __dvrp_graphics )
1872360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1873            '       Output every      ',F7.1,' s'/ &
1874            '       Output mode:      ',A/ &
1875            '       Host / User:      ',A,' / ',A/ &
1876            '       Directory:        ',A// &
1877            '       The sequence contains:')
1878361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1879            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1880362 FORMAT (/'       Slicer plane ',A/ &
1881            '       Slicer limits: [',F6.2,',',F6.2,']')
1882363 FORMAT (/'       Particles'/ &
1883            '          particle size:  ',F7.2,' m')
1884364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1885                       F6.2,',',F6.2,']')
1886365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1887            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1888                     ')'/ &
1889            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1890            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1891366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1892367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1893#endif
1894#if defined( __spectra )
1895370 FORMAT ('    Spectra:')
1896371 FORMAT ('       Output every ',F7.1,' s'/)
1897372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1898            '       Directions: ', 10(A5,',')/                         &
1899            '       height levels  k = ', 20(I3,',')/                  &
1900            '                          ', 20(I3,',')/                  &
1901            '                          ', 20(I3,',')/                  &
1902            '                          ', 20(I3,',')/                  &
1903            '                          ', 19(I3,','),I3,'.'/           &
1904            '       height levels selected for standard plot:'/        &
1905            '                      k = ', 20(I3,',')/                  &
1906            '                          ', 20(I3,',')/                  &
1907            '                          ', 20(I3,',')/                  &
1908            '                          ', 20(I3,',')/                  &
1909            '                          ', 19(I3,','),I3,'.'/           &
1910            '       Time averaged over ', F7.1, ' s,' /                &
1911            '       Profiles for the time averaging are taken every ', &
1912                    F6.1,' s')
1913#endif
1914400 FORMAT (//' Physical quantities:'/ &
1915              ' -------------------'/)
1916410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1917            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1918            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1919            '                            f*    = ',F9.6,' 1/s')
1920411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1921412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1922413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1923415 FORMAT (/'    Cloud physics parameters:'/ &
1924             '    ------------------------'/)
1925416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1926            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1927            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1928            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1929            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1930420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1931            '       Height:        ',A,'  m'/ &
1932            '       Temperature:   ',A,'  K'/ &
1933            '       Gradient:      ',A,'  K/100m'/ &
1934            '       Gridpoint:     ',A)
1935421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1936            '       Height:      ',A,'  m'/ &
1937            '       Humidity:    ',A,'  kg/kg'/ &
1938            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1939            '       Gridpoint:   ',A)
1940422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1941            '       Height:                  ',A,'  m'/ &
1942            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1943            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1944            '       Gridpoint:               ',A)
1945423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1946            '       Height:      ',A,'  m'/ &
1947            '       ug:          ',A,'  m/s'/ &
1948            '       Gradient:    ',A,'  1/100s'/ &
1949            '       Gridpoint:   ',A)
1950424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1951            '       Height:      ',A,'  m'/ &
1952            '       vg:          ',A,'  m/s'/ &
1953            '       Gradient:    ',A,'  1/100s'/ &
1954            '       Gridpoint:   ',A)
1955425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1956            '       Height:     ',A,'  m'/ &
1957            '       Salinity:   ',A,'  psu'/ &
1958            '       Gradient:   ',A,'  psu/100m'/ &
1959            '       Gridpoint:  ',A)
1960426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1961            '       Height:      ',A,'  m'/ &
1962            '       w_subs:      ',A,'  m/s'/ &
1963            '       Gradient:    ',A,'  (m/s)/100m'/ &
1964            '       Gridpoint:   ',A)
1965427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1966                  ' profiles')
1967430 FORMAT (//' Cloud physics quantities / methods:'/ &
1968              ' ----------------------------------'/)
1969431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1970                 'on)')
1971432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1972            '    total water content is used.'/ &
1973            '    Condensation is parameterized via 0% - or 100% scheme.')
1974433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1975                 'icle model')
1976434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1977                 ' droplets < 1.0E-6 m')
1978435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
1979436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1980                    'are used'/ &
1981            '          number of radius classes:       ',I3,'    interval ', &
1982                       '[1.0E-6,2.0E-4] m'/ &
1983            '          number of dissipation classes:   ',I2,'    interval ', &
1984                       '[0,1000] cm**2/s**3')
1985437 FORMAT ('    Droplet collision is switched off')
1986450 FORMAT (//' LES / Turbulence quantities:'/ &
1987              ' ---------------------------'/)
1988451 FORMAT ('    Diffusion coefficients are constant:'/ &
1989            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1990452 FORMAT ('    Mixing length is limited to the Prandtl mixing lenth.')
1991453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
1992454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1993455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
1994470 FORMAT (//' Actions during the simulation:'/ &
1995              ' -----------------------------'/)
1996471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1997            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1998            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1999            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2000472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2001                 ' to i/j =',I4)
2002473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2003                 1X,F5.3, ' m**2/s**2')
2004474 FORMAT ('    Random number generator used    : ',A/)
2005475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2006                 'respectively, if'/ &
2007            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2008                 ' 3D-simulation'/)
2009476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2010                 'respectively, if the'/ &
2011            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2012                 ' the 3D-simulation'/)
2013477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2014                 'respectively, if the'/ &
2015            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2016                 ' the 3D-simulation'/)
2017480 FORMAT ('    Particles:'/ &
2018            '    ---------'// &
2019            '       Particle advection is active (switched on at t = ', F7.1, &
2020                    ' s)'/ &
2021            '       Start of new particle generations every  ',F6.1,' s'/ &
2022            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2023            '                            bottom:     ', A, ' top:         ', A/&
2024            '       Maximum particle age:                 ',F9.1,' s'/ &
2025            '       Advection stopped at t = ',F9.1,' s'/ &
2026            '       Particles are sorted every ',F9.1,' s'/)
2027481 FORMAT ('       Particles have random start positions'/)
2028482 FORMAT ('          Particles are advected only horizontally'/)
2029483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2030484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2031            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2032            '            Maximum age of the end of the tail:  ',F8.2,' s')
2033485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2034486 FORMAT ('       Particle statistics are written on file'/)
2035487 FORMAT ('       Number of particle groups: ',I2/)
2036488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2037            '          minimum timestep for advection: ', F7.5/)
2038489 FORMAT ('       Number of particles simultaneously released at each ', &
2039                    'point: ', I5/)
2040490 FORMAT ('       Particle group ',I2,':'/ &
2041            '          Particle radius: ',E10.3, 'm')
2042491 FORMAT ('          Particle inertia is activated'/ &
2043            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2044492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2045493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2046            '                                         y:',F8.1,' - ',F8.1,' m'/&
2047            '                                         z:',F8.1,' - ',F8.1,' m'/&
2048            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2049                       ' m  dz = ',F8.1,' m'/)
2050494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2051                    F8.2,' s'/)
2052495 FORMAT ('       Number of particles in total domain: ',I10/)
2053500 FORMAT (//' 1D-Model parameters:'/                           &
2054              ' -------------------'//                           &
2055            '    Simulation time:                   ',F8.1,' s'/ &
2056            '    Run-controll output every:         ',F8.1,' s'/ &
2057            '    Vertical profile output every:     ',F8.1,' s'/ &
2058            '    Mixing length calculation:         ',A/         &
2059            '    Dissipation calculation:           ',A/)
2060502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2061503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2062504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2063
2064
2065 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.