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

Last change on this file since 855 was 834, checked in by maronga, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 79.6 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: header.f90 834 2012-02-22 08:57:06Z heinze $
11!
12! 833 2012-02-22 08:55:55Z maronga
13! Adjusted format for leaf area density
14!
15! 828 2012-02-21 12:00:36Z raasch
16! output of dissipation_classes + radius_classes
17!
18! 825 2012-02-19 03:03:44Z raasch
19! Output of cloud physics parameters/quantities complemented and restructured
20!
21! 767 2011-10-14 06:39:12Z raasch
22! Output of given initial u,v-profiles
23!
24! 759 2011-09-15 13:58:31Z raasch
25! output of maximum number of parallel io streams
26!
27! 707 2011-03-29 11:39:40Z raasch
28! bc_lr/ns replaced by bc_lr/ns_cyc
29!
30! 667 2010-12-23 12:06:00Z suehring/gryschka
31! Output of advection scheme.
32! Modified output of Prandtl-layer height.
33!
34! 580 2010-10-05 13:59:11Z heinze
35! Renaming of ws_vertical_gradient to subs_vertical_gradient,
36! ws_vertical_gradient_level to subs_vertical_gradient_level and
37! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
38!
39! 493 2010-03-01 08:30:24Z raasch
40! NetCDF data output format extendend for NetCDF4/HDF5
41!
42! 449 2010-02-02 11:23:59Z raasch
43! +large scale vertical motion (subsidence/ascent)
44! Bugfix: index problem concerning gradient_level indices removed
45!
46! 410 2009-12-04 17:05:40Z letzel
47! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
48! mask_scale|_x|y|z, masks, skip_time_domask
49!
50! 346 2009-07-06 10:13:41Z raasch
51! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
52! Coupling with independent precursor runs.
53! Output of messages replaced by message handling routine.
54! Output of several additional dvr parameters
55! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
56! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
57! dp_smooth, dpdxy, u_bulk, v_bulk
58! topography_grid_convention moved from user_header
59! small bugfix concerning 3d 64bit netcdf output format
60!
61! 206 2008-10-13 14:59:11Z raasch
62! Bugfix: error in zu index in case of section_xy = -1
63!
64! 198 2008-09-17 08:55:28Z raasch
65! Format adjustments allowing output of larger revision numbers
66!
67! 197 2008-09-16 15:29:03Z raasch
68! allow 100 spectra levels instead of 10 for consistency with
69! define_netcdf_header,
70! bugfix in the output of the characteristic levels of potential temperature,
71! geostrophic wind, scalar concentration, humidity and leaf area density,
72! output of turbulence recycling informations
73!
74! 138 2007-11-28 10:03:58Z letzel
75! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
76! Allow two instead of one digit to specify isosurface and slicer variables.
77! Output of sorting frequency of particles
78!
79! 108 2007-08-24 15:10:38Z letzel
80! Output of informations for coupled model runs (boundary conditions etc.)
81! + output of momentumfluxes at the top boundary
82! Rayleigh damping for ocean, e_init
83!
84! 97 2007-06-21 08:23:15Z raasch
85! Adjustments for the ocean version.
86! use_pt_reference renamed use_reference
87!
88! 87 2007-05-22 15:46:47Z raasch
89! Bugfix: output of use_upstream_for_tke
90!
91! 82 2007-04-16 15:40:52Z raasch
92! Preprocessor strings for different linux clusters changed to "lc",
93! routine local_flush is used for buffer flushing
94!
95! 76 2007-03-29 00:58:32Z raasch
96! Output of netcdf_64bit_3d, particles-package is now part of the default code,
97! output of the loop optimization method, moisture renamed humidity,
98! output of subversion revision number
99!
100! 19 2007-02-23 04:53:48Z raasch
101! Output of scalar flux applied at top boundary
102!
103! RCS Log replace by Id keyword, revision history cleaned up
104!
105! Revision 1.63  2006/08/22 13:53:13  raasch
106! Output of dz_max
107!
108! Revision 1.1  1997/08/11 06:17:20  raasch
109! Initial revision
110!
111!
112! Description:
113! ------------
114! Writing a header with all important informations about the actual run.
115! This subroutine is called three times, two times at the beginning
116! (writing information on files RUN_CONTROL and HEADER) and one time at the
117! end of the run, then writing additional information about CPU-usage on file
118! header.
119!-----------------------------------------------------------------------------!
120
121    USE arrays_3d
122    USE control_parameters
123    USE cloud_parameters
124    USE cpulog
125    USE dvrp_variables
126    USE grid_variables
127    USE indices
128    USE model_1d
129    USE particle_attributes
130    USE pegrid
131    USE subsidence_mod
132    USE spectrum
133
134    IMPLICIT NONE
135
136    CHARACTER (LEN=1)  ::  prec
137    CHARACTER (LEN=2)  ::  do2d_mode
138    CHARACTER (LEN=5)  ::  section_chr
139    CHARACTER (LEN=9)  ::  time_to_string
140    CHARACTER (LEN=10) ::  coor_chr, host_chr
141    CHARACTER (LEN=16) ::  begin_chr
142    CHARACTER (LEN=23) ::  ver_rev
143    CHARACTER (LEN=40) ::  output_format
144    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
145                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
146                           domask_chr, run_classification
147    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
148                           temperatures, ugcomponent, vgcomponent
149    CHARACTER (LEN=85) ::  roben, runten
150
151    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
152
153    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
154         cxl, cxr, cyn, cys, dim, i, ihost, io, j, l, ll, m, mpi_type
155    REAL    ::  cpuseconds_per_simulated_second
156
157!
158!-- Open the output file. At the end of the simulation, output is directed
159!-- to unit 19.
160    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
161         .NOT. simulated_time_at_begin /= simulated_time )  THEN
162       io = 15   !  header output on file RUN_CONTROL
163    ELSE
164       io = 19   !  header output on file HEADER
165    ENDIF
166    CALL check_open( io )
167
168!
169!-- At the end of the run, output file (HEADER) will be rewritten with
170!-- new informations
171    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
172
173!
174!-- Determine kind of model run
175    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
176       run_classification = '3D - restart run'
177    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
178       run_classification = '3D - run with cyclic fill of 3D - prerun data'
179    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
180       run_classification = '3D - run without 1D - prerun'
181    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
182       run_classification = '3D - run with 1D - prerun'
183    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
184       run_classification = '3D - run initialized by user'
185    ELSE
186       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
187       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
188    ENDIF
189    IF ( ocean )  THEN
190       run_classification = 'ocean - ' // run_classification
191    ELSE
192       run_classification = 'atmosphere - ' // run_classification
193    ENDIF
194
195!
196!-- Run-identification, date, time, host
197    host_chr = host(1:10)
198    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
199    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
200    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
201#if defined( __mpi2 )
202       mpi_type = 2
203#else
204       mpi_type = 1
205#endif
206       WRITE ( io, 101 )  mpi_type, coupling_mode
207    ENDIF
208    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
209                       ADJUSTR( host_chr )
210#if defined( __parallel )
211    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
212       char1 = 'calculated'
213    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
214               host(1:2) == 'lc' )  .AND.                          &
215             npex == -1  .AND.  pdims(2) == 1 )  THEN
216       char1 = 'forced'
217    ELSE
218       char1 = 'predefined'
219    ENDIF
220    IF ( threads_per_task == 1 )  THEN
221       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
222    ELSE
223       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
224                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
225    ENDIF
226    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
227           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
228         npex == -1  .AND.  pdims(2) == 1 )                      &
229    THEN
230       WRITE ( io, 106 )
231    ELSEIF ( pdims(2) == 1 )  THEN
232       WRITE ( io, 107 )  'x'
233    ELSEIF ( pdims(1) == 1 )  THEN
234       WRITE ( io, 107 )  'y'
235    ENDIF
236    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
237    IF ( numprocs /= maximum_parallel_io_streams )  THEN
238       WRITE ( io, 108 )  maximum_parallel_io_streams
239    ENDIF
240#endif
241    WRITE ( io, 99 )
242
243!
244!-- Numerical schemes
245    WRITE ( io, 110 )
246    IF ( psolver(1:7) == 'poisfft' )  THEN
247       WRITE ( io, 111 )  TRIM( fft_method )
248       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
249    ELSEIF ( psolver == 'sor' )  THEN
250       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
251    ELSEIF ( psolver == 'multigrid' )  THEN
252       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
253       IF ( mg_cycles == -1 )  THEN
254          WRITE ( io, 140 )  residual_limit
255       ELSE
256          WRITE ( io, 141 )  mg_cycles
257       ENDIF
258       IF ( mg_switch_to_pe0_level == 0 )  THEN
259          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
260                             nzt_mg(1)
261       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
262          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
263                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
264                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
265                             nzt_mg(mg_switch_to_pe0_level),    &
266                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
267                             nzt_mg(1)
268       ENDIF
269    ENDIF
270    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
271    THEN
272       WRITE ( io, 142 )
273    ENDIF
274
275    IF ( momentum_advec == 'pw-scheme' )  THEN
276       WRITE ( io, 113 )
277    ELSEIF (momentum_advec == 'ws-scheme' ) THEN
278       WRITE ( io, 503 )
279    ELSEIF (momentum_advec == 'ups-scheme' ) THEN
280       WRITE ( io, 114 )
281       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
282       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
283            overshoot_limit_w /= 0.0 )  THEN
284          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
285                             overshoot_limit_w
286       ENDIF
287       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
288            ups_limit_w /= 0.0 )                               &
289       THEN
290          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
291       ENDIF
292       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
293    ENDIF
294    IF ( scalar_advec == 'pw-scheme' )  THEN
295       WRITE ( io, 116 )
296    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
297       WRITE ( io, 504 )
298    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
299       WRITE ( io, 117 )
300       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
301       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
302          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
303       ENDIF
304       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
305          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
306       ENDIF
307    ELSE
308       WRITE ( io, 118 )
309    ENDIF
310
311    WRITE ( io, 139 )  TRIM( loop_optimization )
312
313    IF ( galilei_transformation )  THEN
314       IF ( use_ug_for_galilei_tr )  THEN
315          char1 = 'geostrophic wind'
316       ELSE
317          char1 = 'mean wind in model domain'
318       ENDIF
319       IF ( simulated_time_at_begin == simulated_time )  THEN
320          char2 = 'at the start of the run'
321       ELSE
322          char2 = 'at the end of the run'
323       ENDIF
324       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
325                          advected_distance_x/1000.0, advected_distance_y/1000.0
326    ENDIF
327    IF ( timestep_scheme == 'leapfrog' )  THEN
328       WRITE ( io, 120 )
329    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
330       WRITE ( io, 121 )
331    ELSE
332       WRITE ( io, 122 )  timestep_scheme
333    ENDIF
334    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
335    IF ( rayleigh_damping_factor /= 0.0 )  THEN
336       IF ( .NOT. ocean )  THEN
337          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
338               rayleigh_damping_factor
339       ELSE
340          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
341               rayleigh_damping_factor
342       ENDIF
343    ENDIF
344    IF ( humidity )  THEN
345       IF ( .NOT. cloud_physics )  THEN
346          WRITE ( io, 129 )
347       ELSE
348          WRITE ( io, 130 )
349       ENDIF
350    ENDIF
351    IF ( passive_scalar )  WRITE ( io, 134 )
352    IF ( conserve_volume_flow )  THEN
353       WRITE ( io, 150 )  conserve_volume_flow_mode
354       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
355          WRITE ( io, 151 )  u_bulk, v_bulk
356       ENDIF
357    ELSEIF ( dp_external )  THEN
358       IF ( dp_smooth )  THEN
359          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
360       ELSE
361          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
362       ENDIF
363    ENDIF
364    IF ( large_scale_subsidence )  THEN
365        WRITE ( io, 153 )
366        WRITE ( io, 154 )
367    ENDIF
368    WRITE ( io, 99 )
369
370!
371!-- Runtime and timestep informations
372    WRITE ( io, 200 )
373    IF ( .NOT. dt_fixed )  THEN
374       WRITE ( io, 201 )  dt_max, cfl_factor
375    ELSE
376       WRITE ( io, 202 )  dt
377    ENDIF
378    WRITE ( io, 203 )  simulated_time_at_begin, end_time
379
380    IF ( time_restart /= 9999999.9  .AND. &
381         simulated_time_at_begin == simulated_time )  THEN
382       IF ( dt_restart == 9999999.9 )  THEN
383          WRITE ( io, 204 )  ' Restart at:       ',time_restart
384       ELSE
385          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
386       ENDIF
387    ENDIF
388
389    IF ( simulated_time_at_begin /= simulated_time )  THEN
390       i = MAX ( log_point_s(10)%counts, 1 )
391       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
392          cpuseconds_per_simulated_second = 0.0
393       ELSE
394          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
395                                            ( simulated_time -    &
396                                              simulated_time_at_begin )
397       ENDIF
398       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
399                          log_point_s(10)%sum / REAL( i ),     &
400                          cpuseconds_per_simulated_second
401       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
402          IF ( dt_restart == 9999999.9 )  THEN
403             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
404          ELSE
405             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
406          ENDIF
407       ENDIF
408    ENDIF
409
410!
411!-- Start time for coupled runs, if independent precursor runs for atmosphere
412!-- and ocean are used. In this case, coupling_start_time defines the time
413!-- when the coupling is switched on.
414    IF ( coupling_start_time /= 0.0 )  THEN
415       IF ( coupling_start_time >= simulated_time_at_begin )  THEN
416          char1 = 'Precursor run for a coupled atmosphere-ocean run'
417       ELSE
418          char1 = 'Coupled atmosphere-ocean run following independent ' // &
419                  'precursor runs'
420       ENDIF
421       WRITE ( io, 207 )  char1, coupling_start_time
422    ENDIF
423
424!
425!-- Computational grid
426    IF ( .NOT. ocean )  THEN
427       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
428       IF ( dz_stretch_level_index < nzt+1 )  THEN
429          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
430                             dz_stretch_factor, dz_max
431       ENDIF
432    ELSE
433       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
434       IF ( dz_stretch_level_index > 0 )  THEN
435          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
436                             dz_stretch_factor, dz_max
437       ENDIF
438    ENDIF
439    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
440                       MIN( nnz+2, nzt+2 )
441    IF ( numprocs > 1 )  THEN
442       IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
443          WRITE ( io, 255 )
444       ELSE
445          WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
446       ENDIF
447    ENDIF
448    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
449
450!
451!-- Topography
452    WRITE ( io, 270 )  topography
453    SELECT CASE ( TRIM( topography ) )
454
455       CASE ( 'flat' )
456          ! no actions necessary
457
458       CASE ( 'single_building' )
459          blx = INT( building_length_x / dx )
460          bly = INT( building_length_y / dy )
461          bh  = INT( building_height / dz )
462
463          IF ( building_wall_left == 9999999.9 )  THEN
464             building_wall_left = ( nx + 1 - blx ) / 2 * dx
465          ENDIF
466          bxl = INT ( building_wall_left / dx + 0.5 )
467          bxr = bxl + blx
468
469          IF ( building_wall_south == 9999999.9 )  THEN
470             building_wall_south = ( ny + 1 - bly ) / 2 * dy
471          ENDIF
472          bys = INT ( building_wall_south / dy + 0.5 )
473          byn = bys + bly
474
475          WRITE ( io, 271 )  building_length_x, building_length_y, &
476                             building_height, bxl, bxr, bys, byn
477
478       CASE ( 'single_street_canyon' )
479          ch  = NINT( canyon_height / dz )
480          IF ( canyon_width_x /= 9999999.9 )  THEN
481!
482!--          Street canyon in y direction
483             cwx = NINT( canyon_width_x / dx )
484             IF ( canyon_wall_left == 9999999.9 )  THEN
485                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
486             ENDIF
487             cxl = NINT( canyon_wall_left / dx )
488             cxr = cxl + cwx
489             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
490
491          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
492!
493!--          Street canyon in x direction
494             cwy = NINT( canyon_width_y / dy )
495             IF ( canyon_wall_south == 9999999.9 )  THEN
496                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
497             ENDIF
498             cys = NINT( canyon_wall_south / dy )
499             cyn = cys + cwy
500             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
501          ENDIF
502
503    END SELECT
504
505    IF ( TRIM( topography ) /= 'flat' )  THEN
506       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
507          IF ( TRIM( topography ) == 'single_building' .OR.  &
508               TRIM( topography ) == 'single_street_canyon' )  THEN
509             WRITE ( io, 278 )
510          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
511             WRITE ( io, 279 )
512          ENDIF
513       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
514          WRITE ( io, 278 )
515       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
516          WRITE ( io, 279 )
517       ENDIF
518    ENDIF
519
520    IF ( plant_canopy ) THEN
521
522       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
523       IF ( passive_scalar ) THEN
524          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
525                            leaf_surface_concentration
526       ENDIF
527
528!
529!--    Heat flux at the top of vegetation
530       WRITE ( io, 282 ) cthf
531
532!
533!--    Leaf area density profile
534!--    Building output strings, starting with surface value
535       WRITE ( learde, '(F6.4)' )  lad_surface
536       gradients = '------'
537       slices = '     0'
538       coordinates = '   0.0'
539       i = 1
540       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
541
542          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
543          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
544
545          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
546          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
547
548          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
549          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
550
551          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
552          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
553
554          i = i + 1
555       ENDDO
556
557       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
558                          TRIM( gradients ), TRIM( slices )
559
560    ENDIF
561
562!
563!-- Boundary conditions
564    IF ( ibc_p_b == 0 )  THEN
565       runten = 'p(0)     = 0      |'
566    ELSEIF ( ibc_p_b == 1 )  THEN
567       runten = 'p(0)     = p(1)   |'
568    ELSE
569       runten = 'p(0)     = p(1) +R|'
570    ENDIF
571    IF ( ibc_p_t == 0 )  THEN
572       roben  = 'p(nzt+1) = 0      |'
573    ELSE
574       roben  = 'p(nzt+1) = p(nzt) |'
575    ENDIF
576
577    IF ( ibc_uv_b == 0 )  THEN
578       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
579    ELSE
580       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
581    ENDIF
582    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
583       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
584    ELSEIF ( ibc_uv_t == 0 )  THEN
585       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
586    ELSE
587       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
588    ENDIF
589
590    IF ( ibc_pt_b == 0 )  THEN
591       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
592    ELSEIF ( ibc_pt_b == 1 )  THEN
593       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
594    ELSEIF ( ibc_pt_b == 2 )  THEN
595       runten = TRIM( runten ) // ' pt(0) = from coupled model'
596    ENDIF
597    IF ( ibc_pt_t == 0 )  THEN
598       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
599    ELSEIF( ibc_pt_t == 1 )  THEN
600       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
601    ELSEIF( ibc_pt_t == 2 )  THEN
602       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
603
604    ENDIF
605
606    WRITE ( io, 300 )  runten, roben
607
608    IF ( .NOT. constant_diffusion )  THEN
609       IF ( ibc_e_b == 1 )  THEN
610          runten = 'e(0)     = e(1)'
611       ELSE
612          runten = 'e(0)     = e(1) = (u*/0.1)**2'
613       ENDIF
614       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
615
616       WRITE ( io, 301 )  'e', runten, roben       
617
618    ENDIF
619
620    IF ( ocean )  THEN
621       runten = 'sa(0)    = sa(1)'
622       IF ( ibc_sa_t == 0 )  THEN
623          roben =  'sa(nzt+1) = sa_surface'
624       ELSE
625          roben =  'sa(nzt+1) = sa(nzt)'
626       ENDIF
627       WRITE ( io, 301 ) 'sa', runten, roben
628    ENDIF
629
630    IF ( humidity )  THEN
631       IF ( ibc_q_b == 0 )  THEN
632          runten = 'q(0)     = q_surface'
633       ELSE
634          runten = 'q(0)     = q(1)'
635       ENDIF
636       IF ( ibc_q_t == 0 )  THEN
637          roben =  'q(nzt)   = q_top'
638       ELSE
639          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
640       ENDIF
641       WRITE ( io, 301 ) 'q', runten, roben
642    ENDIF
643
644    IF ( passive_scalar )  THEN
645       IF ( ibc_q_b == 0 )  THEN
646          runten = 's(0)     = s_surface'
647       ELSE
648          runten = 's(0)     = s(1)'
649       ENDIF
650       IF ( ibc_q_t == 0 )  THEN
651          roben =  's(nzt)   = s_top'
652       ELSE
653          roben =  's(nzt)   = s(nzt-1) + ds/dz'
654       ENDIF
655       WRITE ( io, 301 ) 's', runten, roben
656    ENDIF
657
658    IF ( use_surface_fluxes )  THEN
659       WRITE ( io, 303 )
660       IF ( constant_heatflux )  THEN
661          WRITE ( io, 306 )  surface_heatflux
662          IF ( random_heatflux )  WRITE ( io, 307 )
663       ENDIF
664       IF ( humidity  .AND.  constant_waterflux )  THEN
665          WRITE ( io, 311 ) surface_waterflux
666       ENDIF
667       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
668          WRITE ( io, 313 ) surface_waterflux
669       ENDIF
670    ENDIF
671
672    IF ( use_top_fluxes )  THEN
673       WRITE ( io, 304 )
674       IF ( coupling_mode == 'uncoupled' )  THEN
675          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
676          IF ( constant_top_heatflux )  THEN
677             WRITE ( io, 306 )  top_heatflux
678          ENDIF
679       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
680          WRITE ( io, 316 )
681       ENDIF
682       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
683          WRITE ( io, 309 )  top_salinityflux
684       ENDIF
685       IF ( humidity  .OR.  passive_scalar )  THEN
686          WRITE ( io, 315 )
687       ENDIF
688    ENDIF
689
690    IF ( prandtl_layer )  THEN
691       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, kappa, &
692                          rif_min, rif_max
693       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
694       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
695          WRITE ( io, 312 )
696       ENDIF
697       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
698          WRITE ( io, 314 )
699       ENDIF
700    ELSE
701       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
702          WRITE ( io, 310 )  rif_min, rif_max
703       ENDIF
704    ENDIF
705
706    WRITE ( io, 317 )  bc_lr, bc_ns
707    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
708       WRITE ( io, 318 )  outflow_damping_width, km_damp_max
709       IF ( turbulent_inflow )  THEN
710          WRITE ( io, 319 )  recycling_width, recycling_plane, &
711                             inflow_damping_height, inflow_damping_width
712       ENDIF
713    ENDIF
714
715!
716!-- Listing of 1D-profiles
717    WRITE ( io, 325 )  dt_dopr_listing
718    IF ( averaging_interval_pr /= 0.0 )  THEN
719       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
720    ENDIF
721
722!
723!-- DATA output
724    WRITE ( io, 330 )
725    IF ( averaging_interval_pr /= 0.0 )  THEN
726       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
727    ENDIF
728
729!
730!-- 1D-profiles
731    dopr_chr = 'Profile:'
732    IF ( dopr_n /= 0 )  THEN
733       WRITE ( io, 331 )
734
735       output_format = ''
736       IF ( netcdf_output )  THEN
737          IF ( netcdf_data_format == 1 )  THEN
738             output_format = 'NetCDF classic'
739          ELSE
740             output_format = 'NetCDF 64bit offset'
741          ENDIF
742       ENDIF
743       IF ( profil_output )  THEN
744          IF ( netcdf_output )  THEN
745             output_format = TRIM( output_format ) // ' and profil'
746          ELSE
747             output_format = 'profil'
748          ENDIF
749       ENDIF
750       WRITE ( io, 344 )  output_format
751
752       DO  i = 1, dopr_n
753          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
754          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
755             WRITE ( io, 332 )  dopr_chr
756             dopr_chr = '       :'
757          ENDIF
758       ENDDO
759
760       IF ( dopr_chr /= '' )  THEN
761          WRITE ( io, 332 )  dopr_chr
762       ENDIF
763       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
764       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
765    ENDIF
766
767!
768!-- 2D-arrays
769    DO  av = 0, 1
770
771       i = 1
772       do2d_xy = ''
773       do2d_xz = ''
774       do2d_yz = ''
775       DO  WHILE ( do2d(av,i) /= ' ' )
776
777          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
778          do2d_mode = do2d(av,i)(l-1:l)
779
780          SELECT CASE ( do2d_mode )
781             CASE ( 'xy' )
782                ll = LEN_TRIM( do2d_xy )
783                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
784             CASE ( 'xz' )
785                ll = LEN_TRIM( do2d_xz )
786                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
787             CASE ( 'yz' )
788                ll = LEN_TRIM( do2d_yz )
789                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
790          END SELECT
791
792          i = i + 1
793
794       ENDDO
795
796       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
797              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
798              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
799            ( netcdf_output  .OR.  iso2d_output ) )  THEN
800
801          IF (  av == 0 )  THEN
802             WRITE ( io, 334 )  ''
803          ELSE
804             WRITE ( io, 334 )  '(time-averaged)'
805          ENDIF
806
807          IF ( do2d_at_begin )  THEN
808             begin_chr = 'and at the start'
809          ELSE
810             begin_chr = ''
811          ENDIF
812
813          output_format = ''
814          IF ( netcdf_output )  THEN
815             IF ( netcdf_data_format == 1 )  THEN
816                output_format = 'NetCDF classic'
817             ELSEIF ( netcdf_data_format == 2 )  THEN
818                output_format = 'NetCDF 64bit offset'
819             ELSEIF ( netcdf_data_format == 3 )  THEN
820                output_format = 'NetCDF4/HDF5'
821             ELSEIF ( netcdf_data_format == 4 )  THEN
822                output_format = 'NetCDF4/HDF5 clasic'
823             ENDIF
824          ENDIF
825          IF ( iso2d_output )  THEN
826             IF ( netcdf_output )  THEN
827                output_format = TRIM( output_format ) // ' and iso2d'
828             ELSE
829                output_format = 'iso2d'
830             ENDIF
831          ENDIF
832          WRITE ( io, 344 )  output_format
833
834          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
835             i = 1
836             slices = '/'
837             coordinates = '/'
838!
839!--          Building strings with index and coordinate informations of the
840!--          slices
841             DO  WHILE ( section(i,1) /= -9999 )
842
843                WRITE (section_chr,'(I5)')  section(i,1)
844                section_chr = ADJUSTL( section_chr )
845                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
846
847                IF ( section(i,1) == -1 )  THEN
848                   WRITE (coor_chr,'(F10.1)')  -1.0
849                ELSE
850                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
851                ENDIF
852                coor_chr = ADJUSTL( coor_chr )
853                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
854
855                i = i + 1
856             ENDDO
857             IF ( av == 0 )  THEN
858                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
859                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
860                                   TRIM( coordinates )
861                IF ( skip_time_do2d_xy /= 0.0 )  THEN
862                   WRITE ( io, 339 )  skip_time_do2d_xy
863                ENDIF
864             ELSE
865                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
866                                   TRIM( begin_chr ), averaging_interval, &
867                                   dt_averaging_input, 'k', TRIM( slices ), &
868                                   TRIM( coordinates )
869                IF ( skip_time_data_output_av /= 0.0 )  THEN
870                   WRITE ( io, 339 )  skip_time_data_output_av
871                ENDIF
872             ENDIF
873
874          ENDIF
875
876          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
877             i = 1
878             slices = '/'
879             coordinates = '/'
880!
881!--          Building strings with index and coordinate informations of the
882!--          slices
883             DO  WHILE ( section(i,2) /= -9999 )
884
885                WRITE (section_chr,'(I5)')  section(i,2)
886                section_chr = ADJUSTL( section_chr )
887                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
888
889                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
890                coor_chr = ADJUSTL( coor_chr )
891                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
892
893                i = i + 1
894             ENDDO
895             IF ( av == 0 )  THEN
896                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
897                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
898                                   TRIM( coordinates )
899                IF ( skip_time_do2d_xz /= 0.0 )  THEN
900                   WRITE ( io, 339 )  skip_time_do2d_xz
901                ENDIF
902             ELSE
903                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
904                                   TRIM( begin_chr ), averaging_interval, &
905                                   dt_averaging_input, 'j', TRIM( slices ), &
906                                   TRIM( coordinates )
907                IF ( skip_time_data_output_av /= 0.0 )  THEN
908                   WRITE ( io, 339 )  skip_time_data_output_av
909                ENDIF
910             ENDIF
911          ENDIF
912
913          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
914             i = 1
915             slices = '/'
916             coordinates = '/'
917!
918!--          Building strings with index and coordinate informations of the
919!--          slices
920             DO  WHILE ( section(i,3) /= -9999 )
921
922                WRITE (section_chr,'(I5)')  section(i,3)
923                section_chr = ADJUSTL( section_chr )
924                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
925
926                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
927                coor_chr = ADJUSTL( coor_chr )
928                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
929
930                i = i + 1
931             ENDDO
932             IF ( av == 0 )  THEN
933                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
934                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
935                                   TRIM( coordinates )
936                IF ( skip_time_do2d_yz /= 0.0 )  THEN
937                   WRITE ( io, 339 )  skip_time_do2d_yz
938                ENDIF
939             ELSE
940                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
941                                   TRIM( begin_chr ), averaging_interval, &
942                                   dt_averaging_input, 'i', TRIM( slices ), &
943                                   TRIM( coordinates )
944                IF ( skip_time_data_output_av /= 0.0 )  THEN
945                   WRITE ( io, 339 )  skip_time_data_output_av
946                ENDIF
947             ENDIF
948          ENDIF
949
950       ENDIF
951
952    ENDDO
953
954!
955!-- 3d-arrays
956    DO  av = 0, 1
957
958       i = 1
959       do3d_chr = ''
960       DO  WHILE ( do3d(av,i) /= ' ' )
961
962          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
963          i = i + 1
964
965       ENDDO
966
967       IF ( do3d_chr /= '' )  THEN
968          IF ( av == 0 )  THEN
969             WRITE ( io, 336 )  ''
970          ELSE
971             WRITE ( io, 336 )  '(time-averaged)'
972          ENDIF
973
974          output_format = ''
975          IF ( netcdf_output )  THEN
976             IF ( netcdf_data_format == 1 )  THEN
977                output_format = 'NetCDF classic'
978             ELSEIF ( netcdf_data_format == 2 )  THEN
979                output_format = 'NetCDF 64bit offset'
980             ELSEIF ( netcdf_data_format == 3 )  THEN
981                output_format = 'NetCDF4/HDF5'
982             ELSEIF ( netcdf_data_format == 4 )  THEN
983                output_format = 'NetCDF4/HDF5 clasic'
984             ENDIF
985          ENDIF
986          IF ( avs_output )  THEN
987             IF ( netcdf_output )  THEN
988                output_format = TRIM( output_format ) // ' and avs'
989             ELSE
990                output_format = 'avs'
991             ENDIF
992          ENDIF
993          WRITE ( io, 344 )  output_format
994
995          IF ( do3d_at_begin )  THEN
996             begin_chr = 'and at the start'
997          ELSE
998             begin_chr = ''
999          ENDIF
1000          IF ( av == 0 )  THEN
1001             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1002                                zu(nz_do3d), nz_do3d
1003          ELSE
1004             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1005                                TRIM( begin_chr ), averaging_interval, &
1006                                dt_averaging_input, zu(nz_do3d), nz_do3d
1007          ENDIF
1008
1009          IF ( do3d_compress )  THEN
1010             do3d_chr = ''
1011             i = 1
1012             DO WHILE ( do3d(av,i) /= ' ' )
1013
1014                SELECT CASE ( do3d(av,i) )
1015                   CASE ( 'u' )
1016                      j = 1
1017                   CASE ( 'v' )
1018                      j = 2
1019                   CASE ( 'w' )
1020                      j = 3
1021                   CASE ( 'p' )
1022                      j = 4
1023                   CASE ( 'pt' )
1024                      j = 5
1025                END SELECT
1026                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1027                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1028                           ':' // prec // ','
1029                i = i + 1
1030
1031             ENDDO
1032             WRITE ( io, 338 )  do3d_chr
1033
1034          ENDIF
1035
1036          IF ( av == 0 )  THEN
1037             IF ( skip_time_do3d /= 0.0 )  THEN
1038                WRITE ( io, 339 )  skip_time_do3d
1039             ENDIF
1040          ELSE
1041             IF ( skip_time_data_output_av /= 0.0 )  THEN
1042                WRITE ( io, 339 )  skip_time_data_output_av
1043             ENDIF
1044          ENDIF
1045
1046       ENDIF
1047
1048    ENDDO
1049
1050!
1051!-- masked arrays
1052    IF ( masks > 0 )  WRITE ( io, 345 )  &
1053         mask_scale_x, mask_scale_y, mask_scale_z
1054    DO  mid = 1, masks
1055       DO  av = 0, 1
1056
1057          i = 1
1058          domask_chr = ''
1059          DO  WHILE ( domask(mid,av,i) /= ' ' )
1060             domask_chr = TRIM( domask_chr ) // ' ' //  &
1061                          TRIM( domask(mid,av,i) ) // ','
1062             i = i + 1
1063          ENDDO
1064
1065          IF ( domask_chr /= '' )  THEN
1066             IF ( av == 0 )  THEN
1067                WRITE ( io, 346 )  '', mid
1068             ELSE
1069                WRITE ( io, 346 )  ' (time-averaged)', mid
1070             ENDIF
1071
1072             output_format = ''
1073             IF ( netcdf_output )  THEN
1074                IF ( netcdf_data_format == 1 )  THEN
1075                   output_format = 'NetCDF classic'
1076                ELSEIF ( netcdf_data_format == 2 )  THEN
1077                   output_format = 'NetCDF 64bit offset'
1078                ELSEIF ( netcdf_data_format == 3 )  THEN
1079                   output_format = 'NetCDF4/HDF5'
1080                ELSEIF ( netcdf_data_format == 4 )  THEN
1081                   output_format = 'NetCDF4/HDF5 clasic'
1082                ENDIF
1083             ENDIF
1084             WRITE ( io, 344 )  output_format
1085
1086             IF ( av == 0 )  THEN
1087                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1088             ELSE
1089                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1090                                   averaging_interval, dt_averaging_input
1091             ENDIF
1092
1093             IF ( av == 0 )  THEN
1094                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1095                   WRITE ( io, 339 )  skip_time_domask(mid)
1096                ENDIF
1097             ELSE
1098                IF ( skip_time_data_output_av /= 0.0 )  THEN
1099                   WRITE ( io, 339 )  skip_time_data_output_av
1100                ENDIF
1101             ENDIF
1102!
1103!--          output locations
1104             DO  dim = 1, 3
1105                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1106                   count = 0
1107                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1108                      count = count + 1
1109                   ENDDO
1110                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1111                                      mask(mid,dim,:count)
1112                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1113                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1114                         mask_loop(mid,dim,3) == 0.0 )  THEN
1115                   WRITE ( io, 350 )  dir(dim), dir(dim)
1116                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1117                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1118                                      mask_loop(mid,dim,1:2)
1119                ELSE
1120                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1121                                      mask_loop(mid,dim,1:3)
1122                ENDIF
1123             ENDDO
1124          ENDIF
1125
1126       ENDDO
1127    ENDDO
1128
1129!
1130!-- Timeseries
1131    IF ( dt_dots /= 9999999.9 )  THEN
1132       WRITE ( io, 340 )
1133
1134       output_format = ''
1135       IF ( netcdf_output )  THEN
1136          IF ( netcdf_data_format == 1 )  THEN
1137             output_format = 'NetCDF classic'
1138          ELSE
1139             output_format = 'NetCDF 64bit offset'
1140          ENDIF
1141       ENDIF
1142       IF ( profil_output )  THEN
1143          IF ( netcdf_output )  THEN
1144             output_format = TRIM( output_format ) // ' and profil'
1145          ELSE
1146             output_format = 'profil'
1147          ENDIF
1148       ENDIF
1149       WRITE ( io, 344 )  output_format
1150       WRITE ( io, 341 )  dt_dots
1151    ENDIF
1152
1153#if defined( __dvrp_graphics )
1154!
1155!-- Dvrp-output
1156    IF ( dt_dvrp /= 9999999.9 )  THEN
1157       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1158                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1159       i = 1
1160       l = 0
1161       m = 0
1162       DO WHILE ( mode_dvrp(i) /= ' ' )
1163          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1164             READ ( mode_dvrp(i), '(10X,I2)' )  j
1165             l = l + 1
1166             IF ( do3d(0,j) /= ' ' )  THEN
1167                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1168                                   isosurface_color(:,l)
1169             ENDIF
1170          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1171             READ ( mode_dvrp(i), '(6X,I2)' )  j
1172             m = m + 1
1173             IF ( do2d(0,j) /= ' ' )  THEN
1174                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1175                                   slicer_range_limits_dvrp(:,m)
1176             ENDIF
1177          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1178             WRITE ( io, 363 )  dvrp_psize
1179             IF ( particle_dvrpsize /= 'none' )  THEN
1180                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1181                                   dvrpsize_interval
1182             ENDIF
1183             IF ( particle_color /= 'none' )  THEN
1184                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1185                                   color_interval
1186             ENDIF
1187          ENDIF
1188          i = i + 1
1189       ENDDO
1190
1191       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1192                          superelevation_y, superelevation, clip_dvrp_l, &
1193                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1194
1195       IF ( TRIM( topography ) /= 'flat' )  THEN
1196          WRITE ( io, 366 )  topography_color
1197          IF ( cluster_size > 1 )  THEN
1198             WRITE ( io, 367 )  cluster_size
1199          ENDIF
1200       ENDIF
1201
1202    ENDIF
1203#endif
1204
1205#if defined( __spectra )
1206!
1207!-- Spectra output
1208    IF ( dt_dosp /= 9999999.9 ) THEN
1209       WRITE ( io, 370 )
1210
1211       output_format = ''
1212       IF ( netcdf_output )  THEN
1213          IF ( netcdf_data_format == 1 )  THEN
1214             output_format = 'NetCDF classic'
1215          ELSE
1216             output_format = 'NetCDF 64bit offset'
1217          ENDIF
1218       ENDIF
1219       IF ( profil_output )  THEN
1220          IF ( netcdf_output )  THEN
1221             output_format = TRIM( output_format ) // ' and profil'
1222          ELSE
1223             output_format = 'profil'
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')
1677132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1678            '     effective emissivity scheme')
1679133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1680134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1681135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1682                  A,'-cycle)'/ &
1683            '     number of grid levels:                   ',I2/ &
1684            '     Gauss-Seidel red/black iterations:       ',I2)
1685136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1686                  I3,')')
1687137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1688            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1689                  I3,')'/ &
1690            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1691                  I3,')')
1692138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1693139 FORMAT (' --> Loop optimization method: ',A)
1694140 FORMAT ('     maximum residual allowed:                ',E10.3)
1695141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1696142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1697                  'step')
1698143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1699                  'kinetic energy')
1700150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1701                  'conserved'/ &
1702            '     using the ',A,' mode')
1703151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1704152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1705           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1706           /'     starting from dp_level_b =', F8.3, 'm', A /)
1707153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1708                  'prognostic equation for')
1709154 FORMAT ('     the potential temperature')
1710200 FORMAT (//' Run time and time step information:'/ &
1711             ' ----------------------------------'/)
1712201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1713             '    CFL-factor: ',F4.2)
1714202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1715203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1716             ' End time:         ',F9.3,' s')
1717204 FORMAT ( A,F9.3,' s')
1718205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1719206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1720             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1721               '  ',F9.3,' s'/                                                 &
1722             '                                   per second of simulated tim', &
1723               'e: ',F9.3,' s')
1724207 FORMAT ( A/' Coupling start time:',F9.3,' s')
1725250 FORMAT (//' Computational grid and domain size:'/ &
1726              ' ----------------------------------'// &
1727              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1728              ' m    dz =    ',F7.3,' m'/ &
1729              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1730              ' m  z(u) = ',F10.3,' m'/)
1731252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1732              ' factor: ',F5.3/ &
1733            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1734254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1735            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1736255 FORMAT (' Subdomains have equal size')
1737256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1738              'have smaller sizes'/                                          &
1739            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1740260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1741             ' degrees')
1742270 FORMAT (//' Topography informations:'/ &
1743              ' -----------------------'// &
1744              1X,'Topography: ',A)
1745271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1746              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1747                ' / ',I4)
1748272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1749              ' direction' / &
1750              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1751              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1752278 FORMAT (' Topography grid definition convention:'/ &
1753            ' cell edge (staggered grid points'/  &
1754            ' (u in x-direction, v in y-direction))' /)
1755279 FORMAT (' Topography grid definition convention:'/ &
1756            ' cell center (scalar grid points)' /)
1757280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1758              ' ------------------------------'// &
1759              ' Canopy mode: ', A / &
1760              ' Canopy top: ',I4 / &
1761              ' Leaf drag coefficient: ',F6.2 /)
1762281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1763              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1764282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1765283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1766              ' Height:              ',A,'  m'/ &
1767              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1768              ' Gradient:            ',A,'  m**2/m**4'/ &
1769              ' Gridpoint:           ',A)
1770               
1771300 FORMAT (//' Boundary conditions:'/ &
1772             ' -------------------'// &
1773             '                     p                    uv             ', &
1774             '                   pt'// &
1775             ' B. bound.: ',A/ &
1776             ' T. bound.: ',A)
1777301 FORMAT (/'                     ',A// &
1778             ' B. bound.: ',A/ &
1779             ' T. bound.: ',A)
1780303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1781304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1782305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1783               'computational u,v-level:'// &
1784             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1785             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1786306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1787307 FORMAT ('       Heatflux has a random normal distribution')
1788308 FORMAT ('       Predefined surface temperature')
1789309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1790310 FORMAT (//'    1D-Model:'// &
1791             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1792311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1793312 FORMAT ('       Predefined surface humidity')
1794313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1795314 FORMAT ('       Predefined scalar value at the surface')
1796315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1797316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1798                    'atmosphere model')
1799317 FORMAT (//' Lateral boundaries:'/ &
1800            '       left/right:  ',A/    &
1801            '       north/south: ',A)
1802318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1803                    'max =',F5.1,' m**2/s')
1804319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1805            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1806            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1807320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1808            '                                          v: ',F9.6,' m**2/s**2')
1809325 FORMAT (//' List output:'/ &
1810             ' -----------'//  &
1811            '    1D-Profiles:'/    &
1812            '       Output every             ',F8.2,' s')
1813326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1814            '       Averaging input every    ',F8.2,' s')
1815330 FORMAT (//' Data output:'/ &
1816             ' -----------'/)
1817331 FORMAT (/'    1D-Profiles:')
1818332 FORMAT (/'       ',A)
1819333 FORMAT ('       Output every             ',F8.2,' s',/ &
1820            '       Time averaged over       ',F8.2,' s'/ &
1821            '       Averaging input every    ',F8.2,' s')
1822334 FORMAT (/'    2D-Arrays',A,':')
1823335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1824            '       Output every             ',F8.2,' s  ',A/ &
1825            '       Cross sections at ',A1,' = ',A/ &
1826            '       scalar-coordinates:   ',A,' m'/)
1827336 FORMAT (/'    3D-Arrays',A,':')
1828337 FORMAT (/'       Arrays: ',A/ &
1829            '       Output every             ',F8.2,' s  ',A/ &
1830            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1831338 FORMAT ('       Compressed data output'/ &
1832            '       Decimal precision: ',A/)
1833339 FORMAT ('       No output during initial ',F8.2,' s')
1834340 FORMAT (/'    Time series:')
1835341 FORMAT ('       Output every             ',F8.2,' s'/)
1836342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1837            '       Output every             ',F8.2,' s  ',A/ &
1838            '       Time averaged over       ',F8.2,' s'/ &
1839            '       Averaging input every    ',F8.2,' s'/ &
1840            '       Cross sections at ',A1,' = ',A/ &
1841            '       scalar-coordinates:   ',A,' m'/)
1842343 FORMAT (/'       Arrays: ',A/ &
1843            '       Output every             ',F8.2,' s  ',A/ &
1844            '       Time averaged over       ',F8.2,' s'/ &
1845            '       Averaging input every    ',F8.2,' s'/ &
1846            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1847344 FORMAT ('       Output format: ',A/)
1848345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1849            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1850            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1851            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1852346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1853347 FORMAT ('       Variables: ',A/ &
1854            '       Output every             ',F8.2,' s')
1855348 FORMAT ('       Variables: ',A/ &
1856            '       Output every             ',F8.2,' s'/ &
1857            '       Time averaged over       ',F8.2,' s'/ &
1858            '       Averaging input every    ',F8.2,' s')
1859349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1860            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1861            13('       ',8(F8.2,',')/) )
1862350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1863            'all gridpoints along ',A,'-direction (default).' )
1864351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1865            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1866            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1867#if defined( __dvrp_graphics )
1868360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1869            '       Output every      ',F7.1,' s'/ &
1870            '       Output mode:      ',A/ &
1871            '       Host / User:      ',A,' / ',A/ &
1872            '       Directory:        ',A// &
1873            '       The sequence contains:')
1874361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1875            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1876362 FORMAT (/'       Slicer plane ',A/ &
1877            '       Slicer limits: [',F6.2,',',F6.2,']')
1878363 FORMAT (/'       Particles'/ &
1879            '          particle size:  ',F7.2,' m')
1880364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1881                       F6.2,',',F6.2,']')
1882365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1883            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1884                     ')'/ &
1885            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1886            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1887366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1888367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1889#endif
1890#if defined( __spectra )
1891370 FORMAT ('    Spectra:')
1892371 FORMAT ('       Output every ',F7.1,' s'/)
1893372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1894            '       Directions: ', 10(A5,',')/                         &
1895            '       height levels  k = ', 20(I3,',')/                  &
1896            '                          ', 20(I3,',')/                  &
1897            '                          ', 20(I3,',')/                  &
1898            '                          ', 20(I3,',')/                  &
1899            '                          ', 19(I3,','),I3,'.'/           &
1900            '       height levels selected for standard plot:'/        &
1901            '                      k = ', 20(I3,',')/                  &
1902            '                          ', 20(I3,',')/                  &
1903            '                          ', 20(I3,',')/                  &
1904            '                          ', 20(I3,',')/                  &
1905            '                          ', 19(I3,','),I3,'.'/           &
1906            '       Time averaged over ', F7.1, ' s,' /                &
1907            '       Profiles for the time averaging are taken every ', &
1908                    F6.1,' s')
1909#endif
1910400 FORMAT (//' Physical quantities:'/ &
1911              ' -------------------'/)
1912410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1913            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1914            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1915            '                            f*    = ',F9.6,' 1/s')
1916411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1917412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1918413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1919415 FORMAT (/'    Cloud physics parameters:'/ &
1920             '    ------------------------'/)
1921416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1922            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1923            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1924            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1925            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1926420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1927            '       Height:        ',A,'  m'/ &
1928            '       Temperature:   ',A,'  K'/ &
1929            '       Gradient:      ',A,'  K/100m'/ &
1930            '       Gridpoint:     ',A)
1931421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1932            '       Height:      ',A,'  m'/ &
1933            '       Humidity:    ',A,'  kg/kg'/ &
1934            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1935            '       Gridpoint:   ',A)
1936422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1937            '       Height:                  ',A,'  m'/ &
1938            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1939            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1940            '       Gridpoint:               ',A)
1941423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1942            '       Height:      ',A,'  m'/ &
1943            '       ug:          ',A,'  m/s'/ &
1944            '       Gradient:    ',A,'  1/100s'/ &
1945            '       Gridpoint:   ',A)
1946424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1947            '       Height:      ',A,'  m'/ &
1948            '       vg:          ',A,'  m/s'/ &
1949            '       Gradient:    ',A,'  1/100s'/ &
1950            '       Gridpoint:   ',A)
1951425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1952            '       Height:     ',A,'  m'/ &
1953            '       Salinity:   ',A,'  psu'/ &
1954            '       Gradient:   ',A,'  psu/100m'/ &
1955            '       Gridpoint:  ',A)
1956426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1957            '       Height:      ',A,'  m'/ &
1958            '       w_subs:      ',A,'  m/s'/ &
1959            '       Gradient:    ',A,'  (m/s)/100m'/ &
1960            '       Gridpoint:   ',A)
1961427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1962                  ' profiles')
1963430 FORMAT (//' Cloud physics quantities / methods:'/ &
1964              ' ----------------------------------'/)
1965431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1966                 'on)')
1967432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1968            '    total water content is used.'/ &
1969            '    Condensation is parameterized via 0% - or 100% scheme.')
1970433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1971                 'icle model')
1972434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1973                 ' droplets < 1.0E-6 m')
1974435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
1975436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1976                    'are used'/ &
1977            '          number of radius classes:       ',I3,'    interval ', &
1978                       '[1.0E-6,2.0E-4] m'/ &
1979            '          number of dissipation classes:   ',I2,'    interval ', &
1980                       '[0,1000] cm**2/s**3')
1981437 FORMAT ('    Droplet collision is switched off')
1982450 FORMAT (//' LES / Turbulence quantities:'/ &
1983              ' ---------------------------'/)
1984451 FORMAT ('    Diffusion coefficients are constant:'/ &
1985            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1986452 FORMAT ('    Mixing length is limited to the Prandtl mixing lenth.')
1987453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
1988454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1989455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
1990470 FORMAT (//' Actions during the simulation:'/ &
1991              ' -----------------------------'/)
1992471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1993            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1994            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1995            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1996472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1997                 ' to i/j =',I4)
1998473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1999                 1X,F5.3, ' m**2/s**2')
2000474 FORMAT ('    Random number generator used    : ',A/)
2001475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2002                 'respectively, if'/ &
2003            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2004                 ' 3D-simulation'/)
2005476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2006                 'respectively, if the'/ &
2007            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2008                 ' the 3D-simulation'/)
2009477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2010                 'respectively, if the'/ &
2011            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2012                 ' the 3D-simulation'/)
2013480 FORMAT ('    Particles:'/ &
2014            '    ---------'// &
2015            '       Particle advection is active (switched on at t = ', F7.1, &
2016                    ' s)'/ &
2017            '       Start of new particle generations every  ',F6.1,' s'/ &
2018            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2019            '                            bottom:     ', A, ' top:         ', A/&
2020            '       Maximum particle age:                 ',F9.1,' s'/ &
2021            '       Advection stopped at t = ',F9.1,' s'/ &
2022            '       Particles are sorted every ',F9.1,' s'/)
2023481 FORMAT ('       Particles have random start positions'/)
2024482 FORMAT ('          Particles are advected only horizontally'/)
2025483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2026484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2027            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2028            '            Maximum age of the end of the tail:  ',F8.2,' s')
2029485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2030486 FORMAT ('       Particle statistics are written on file'/)
2031487 FORMAT ('       Number of particle groups: ',I2/)
2032488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2033            '          minimum timestep for advection: ', F7.5/)
2034489 FORMAT ('       Number of particles simultaneously released at each ', &
2035                    'point: ', I5/)
2036490 FORMAT ('       Particle group ',I2,':'/ &
2037            '          Particle radius: ',E10.3, 'm')
2038491 FORMAT ('          Particle inertia is activated'/ &
2039            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2040492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2041493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2042            '                                         y:',F8.1,' - ',F8.1,' m'/&
2043            '                                         z:',F8.1,' - ',F8.1,' m'/&
2044            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2045                       ' m  dz = ',F8.1,' m'/)
2046494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2047                    F8.2,' s'/)
2048495 FORMAT ('       Number of particles in total domain: ',I10/)
2049500 FORMAT (//' 1D-Model parameters:'/                           &
2050              ' -------------------'//                           &
2051            '    Simulation time:                   ',F8.1,' s'/ &
2052            '    Run-controll output every:         ',F8.1,' s'/ &
2053            '    Vertical profile output every:     ',F8.1,' s'/ &
2054            '    Mixing length calculation:         ',A/         &
2055            '    Dissipation calculation:           ',A/)
2056502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2057503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2058504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2059
2060
2061 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.