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

Last change on this file since 189 was 189, checked in by letzel, 16 years ago
  • changed: allow 100 spectra levels instead of 10 for consistency with define_netcdf_header
  • Property svn:keywords set to Id
File size: 62.7 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! allow 100 spectra levels instead of 10 for consistency with
7! define_netcdf_header
8! Bugfix in the output of the characteristic levels of potential temperature,
9! geostrophic wind, scalar concentration, humidity and leaf area density
10! Output of turbulence recycling informations
11!
12! Former revisions:
13! -----------------
14! $Id: header.f90 189 2008-08-13 17:09:26Z letzel $
15!
16! 138 2007-11-28 10:03:58Z letzel
17! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
18! Allow two instead of one digit to specify isosurface and slicer variables.
19! Output of sorting frequency of particles
20!
21! 108 2007-08-24 15:10:38Z letzel
22! Output of informations for coupled model runs (boundary conditions etc.)
23! + output of momentumfluxes at the top boundary
24! Rayleigh damping for ocean, e_init
25!
26! 97 2007-06-21 08:23:15Z raasch
27! Adjustments for the ocean version.
28! use_pt_reference renamed use_reference
29!
30! 87 2007-05-22 15:46:47Z raasch
31! Bugfix: output of use_upstream_for_tke
32!
33! 82 2007-04-16 15:40:52Z raasch
34! Preprocessor strings for different linux clusters changed to "lc",
35! routine local_flush is used for buffer flushing
36!
37! 76 2007-03-29 00:58:32Z raasch
38! Output of netcdf_64bit_3d, particles-package is now part of the default code,
39! output of the loop optimization method, moisture renamed humidity,
40! output of subversion revision number
41!
42! 19 2007-02-23 04:53:48Z raasch
43! Output of scalar flux applied at top boundary
44!
45! RCS Log replace by Id keyword, revision history cleaned up
46!
47! Revision 1.63  2006/08/22 13:53:13  raasch
48! Output of dz_max
49!
50! Revision 1.1  1997/08/11 06:17:20  raasch
51! Initial revision
52!
53!
54! Description:
55! ------------
56! Writing a header with all important informations about the actual run.
57! This subroutine is called three times, two times at the beginning
58! (writing information on files RUN_CONTROL and HEADER) and one time at the
59! end of the run, then writing additional information about CPU-usage on file
60! header.
61!------------------------------------------------------------------------------!
62
63    USE arrays_3d
64    USE control_parameters
65    USE cloud_parameters
66    USE cpulog
67    USE dvrp_variables
68    USE grid_variables
69    USE indices
70    USE model_1d
71    USE particle_attributes
72    USE pegrid
73    USE spectrum
74
75    IMPLICIT NONE
76
77    CHARACTER (LEN=1)  ::  prec
78    CHARACTER (LEN=2)  ::  do2d_mode
79    CHARACTER (LEN=5)  ::  section_chr
80    CHARACTER (LEN=9)  ::  time_to_string
81    CHARACTER (LEN=10) ::  coor_chr, host_chr
82    CHARACTER (LEN=16) ::  begin_chr
83    CHARACTER (LEN=21) ::  ver_rev
84    CHARACTER (LEN=40) ::  output_format
85    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
86                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
87                           run_classification
88    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
89                           temperatures, ugcomponent, vgcomponent
90    CHARACTER (LEN=85) ::  roben, runten
91
92    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, i, ihost, io, j, l, ll
93    REAL    ::  cpuseconds_per_simulated_second
94
95!
96!-- Open the output file. At the end of the simulation, output is directed
97!-- to unit 19.
98    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
99         .NOT. simulated_time_at_begin /= simulated_time )  THEN
100       io = 15   !  header output on file RUN_CONTROL
101    ELSE
102       io = 19   !  header output on file HEADER
103    ENDIF
104    CALL check_open( io )
105
106!
107!-- At the end of the run, output file (HEADER) will be rewritten with
108!-- new informations
109    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
110
111!
112!-- Determine kind of model run
113    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
114       run_classification = '3D - restart run'
115    ELSEIF ( TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
116       run_classification = '3D - run using 3D - prerun data'
117    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
118       run_classification = '3D - run without 1D - prerun'
119    ELSEIF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 ) THEN
120       run_classification = '3D - run with 1D - prerun'
121    ELSE
122       PRINT*,'+++ header:  unknown action(s): ',initializing_actions
123    ENDIF
124    IF ( ocean )  THEN
125       run_classification = 'ocean - ' // run_classification
126    ELSE
127       run_classification = 'atmosphere - ' // run_classification
128    ENDIF
129
130!
131!-- Run-identification, date, time, host
132    host_chr = host(1:10)
133    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
134    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
135    IF ( coupling_mode /= 'uncoupled' )  WRITE ( io, 101 )  coupling_mode
136    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
137                       ADJUSTR( host_chr )
138#if defined( __parallel )
139    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
140       char1 = 'calculated'
141    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
142               host(1:2) == 'lc' )  .AND.                          &
143             npex == -1  .AND.  pdims(2) == 1 )  THEN
144       char1 = 'forced'
145    ELSE
146       char1 = 'predefined'
147    ENDIF
148    IF ( threads_per_task == 1 )  THEN
149       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
150    ELSE
151       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
152                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
153    ENDIF
154    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
155           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
156         npex == -1  .AND.  pdims(2) == 1 )                      &
157    THEN
158       WRITE ( io, 106 )
159    ELSEIF ( pdims(2) == 1 )  THEN
160       WRITE ( io, 107 )  'x'
161    ELSEIF ( pdims(1) == 1 )  THEN
162       WRITE ( io, 107 )  'y'
163    ENDIF
164    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
165#endif
166    WRITE ( io, 99 )
167
168!
169!-- Numerical schemes
170    WRITE ( io, 110 )
171    IF ( psolver(1:7) == 'poisfft' )  THEN
172       WRITE ( io, 111 )  TRIM( fft_method )
173       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
174    ELSEIF ( psolver == 'sor' )  THEN
175       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
176    ELSEIF ( psolver == 'multigrid' )  THEN
177       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
178       IF ( mg_cycles == -1 )  THEN
179          WRITE ( io, 140 )  residual_limit
180       ELSE
181          WRITE ( io, 141 )  mg_cycles
182       ENDIF
183       IF ( mg_switch_to_pe0_level == 0 )  THEN
184          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
185                             nzt_mg(1)
186       ELSE
187          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
188                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
189                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
190                             nzt_mg(mg_switch_to_pe0_level),    &
191                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
192                             nzt_mg(1)
193       ENDIF
194    ENDIF
195    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
196    THEN
197       WRITE ( io, 142 )
198    ENDIF
199
200    IF ( momentum_advec == 'pw-scheme' )  THEN
201       WRITE ( io, 113 )
202    ELSE
203       WRITE ( io, 114 )
204       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
205       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
206            overshoot_limit_w /= 0.0 )  THEN
207          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
208                             overshoot_limit_w
209       ENDIF
210       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
211            ups_limit_w /= 0.0 )                               &
212       THEN
213          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
214       ENDIF
215       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
216    ENDIF
217    IF ( scalar_advec == 'pw-scheme' )  THEN
218       WRITE ( io, 116 )
219    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
220       WRITE ( io, 117 )
221       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
222       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
223          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
224       ENDIF
225       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
226          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
227       ENDIF
228    ELSE
229       WRITE ( io, 118 )
230    ENDIF
231
232    WRITE ( io, 139 )  TRIM( loop_optimization )
233
234    IF ( galilei_transformation )  THEN
235       IF ( use_ug_for_galilei_tr )  THEN
236          char1 = 'geostrophic wind'
237       ELSE
238          char1 = 'mean wind in model domain'
239       ENDIF
240       IF ( simulated_time_at_begin == simulated_time )  THEN
241          char2 = 'at the start of the run'
242       ELSE
243          char2 = 'at the end of the run'
244       ENDIF
245       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
246                          advected_distance_x/1000.0, advected_distance_y/1000.0
247    ENDIF
248    IF ( timestep_scheme == 'leapfrog' )  THEN
249       WRITE ( io, 120 )
250    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
251       WRITE ( io, 121 )
252    ELSE
253       WRITE ( io, 122 )  timestep_scheme
254    ENDIF
255    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
256    IF ( rayleigh_damping_factor /= 0.0 )  THEN
257       IF ( .NOT. ocean )  THEN
258          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
259               rayleigh_damping_factor
260       ELSE
261          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
262               rayleigh_damping_factor
263       ENDIF
264    ENDIF
265    IF ( humidity )  THEN
266       IF ( .NOT. cloud_physics )  THEN
267          WRITE ( io, 129 )
268       ELSE
269          WRITE ( io, 130 )
270          WRITE ( io, 131 )
271          IF ( radiation )      WRITE ( io, 132 )
272          IF ( precipitation )  WRITE ( io, 133 )
273       ENDIF
274    ENDIF
275    IF ( passive_scalar )  WRITE ( io, 134 )
276    IF ( conserve_volume_flow )  WRITE ( io, 150 )
277    WRITE ( io, 99 )
278
279!
280!-- Runtime and timestep informations
281    WRITE ( io, 200 )
282    IF ( .NOT. dt_fixed )  THEN
283       WRITE ( io, 201 )  dt_max, cfl_factor
284    ELSE
285       WRITE ( io, 202 )  dt
286    ENDIF
287    WRITE ( io, 203 )  simulated_time_at_begin, end_time
288
289    IF ( time_restart /= 9999999.9  .AND. &
290         simulated_time_at_begin == simulated_time )  THEN
291       IF ( dt_restart == 9999999.9 )  THEN
292          WRITE ( io, 204 )  ' Restart at:       ',time_restart
293       ELSE
294          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
295       ENDIF
296    ENDIF
297
298    IF ( simulated_time_at_begin /= simulated_time )  THEN
299       i = MAX ( log_point_s(10)%counts, 1 )
300       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
301          cpuseconds_per_simulated_second = 0.0
302       ELSE
303          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
304                                            ( simulated_time -    &
305                                              simulated_time_at_begin )
306       ENDIF
307       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
308                          log_point_s(10)%sum / REAL( i ),     &
309                          cpuseconds_per_simulated_second
310       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
311          IF ( dt_restart == 9999999.9 )  THEN
312             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
313          ELSE
314             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
315          ENDIF
316       ENDIF
317    ENDIF
318
319!
320!-- Computational grid
321    IF ( .NOT. ocean )  THEN
322       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
323       IF ( dz_stretch_level_index < nzt+1 )  THEN
324          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
325                             dz_stretch_factor, dz_max
326       ENDIF
327    ELSE
328       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
329       IF ( dz_stretch_level_index > 0 )  THEN
330          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
331                             dz_stretch_factor, dz_max
332       ENDIF
333    ENDIF
334    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
335                       MIN( nnz+2, nzt+2 )
336    IF ( numprocs > 1 )  THEN
337       IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
338          WRITE ( io, 255 )
339       ELSE
340          WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
341       ENDIF
342    ENDIF
343    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
344
345!
346!-- Topography
347    WRITE ( io, 270 )  topography
348    SELECT CASE ( TRIM( topography ) )
349
350       CASE ( 'flat' )
351          ! no actions necessary
352
353       CASE ( 'single_building' )
354          blx = INT( building_length_x / dx )
355          bly = INT( building_length_y / dy )
356          bh  = INT( building_height / dz )
357
358          IF ( building_wall_left == 9999999.9 )  THEN
359             building_wall_left = ( nx + 1 - blx ) / 2 * dx
360          ENDIF
361          bxl = INT ( building_wall_left / dx + 0.5 )
362          bxr = bxl + blx
363
364          IF ( building_wall_south == 9999999.9 )  THEN
365             building_wall_south = ( ny + 1 - bly ) / 2 * dy
366          ENDIF
367          bys = INT ( building_wall_south / dy + 0.5 )
368          byn = bys + bly
369
370          WRITE ( io, 271 )  building_length_x, building_length_y, &
371                             building_height, bxl, bxr, bys, byn
372
373    END SELECT
374
375    IF ( plant_canopy ) THEN
376
377       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
378       IF ( passive_scalar ) THEN
379          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
380                            leaf_surface_concentration
381       ENDIF
382
383!
384!--    Heat flux at the top of vegetation
385       WRITE ( io, 282 ) cthf
386
387!
388!--    Leaf area density profile
389!--    Building output strings, starting with surface value
390       WRITE ( learde, '(F6.2)' )  lad_surface
391       gradients = '------'
392       slices = '     0'
393       coordinates = '   0.0'
394       i = 1
395       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
396
397          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
398          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
399
400          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
401          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
402
403          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
404          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
405
406          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
407          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
408
409          i = i + 1
410       ENDDO
411
412       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
413                          TRIM( gradients ), TRIM( slices )
414
415    ENDIF
416
417!
418!-- Boundary conditions
419    IF ( ibc_p_b == 0 )  THEN
420       runten = 'p(0)     = 0      |'
421    ELSEIF ( ibc_p_b == 1 )  THEN
422       runten = 'p(0)     = p(1)   |'
423    ELSE
424       runten = 'p(0)     = p(1) +R|'
425    ENDIF
426    IF ( ibc_p_t == 0 )  THEN
427       roben  = 'p(nzt+1) = 0      |'
428    ELSE
429       roben  = 'p(nzt+1) = p(nzt) |'
430    ENDIF
431
432    IF ( ibc_uv_b == 0 )  THEN
433       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
434    ELSE
435       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
436    ENDIF
437    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
438       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
439    ELSEIF ( ibc_uv_t == 0 )  THEN
440       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
441    ELSE
442       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
443    ENDIF
444
445    IF ( ibc_pt_b == 0 )  THEN
446       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
447    ELSEIF ( ibc_pt_b == 1 )  THEN
448       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
449    ELSEIF ( ibc_pt_b == 2 )  THEN
450       runten = TRIM( runten ) // ' pt(0) = from coupled model'
451    ENDIF
452    IF ( ibc_pt_t == 0 )  THEN
453       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
454    ELSEIF( ibc_pt_t == 1 )  THEN
455       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
456    ELSEIF( ibc_pt_t == 2 )  THEN
457       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
458    ENDIF
459
460    WRITE ( io, 300 )  runten, roben
461
462    IF ( .NOT. constant_diffusion )  THEN
463       IF ( ibc_e_b == 1 )  THEN
464          runten = 'e(0)     = e(1)'
465       ELSE
466          runten = 'e(0)     = e(1) = (u*/0.1)**2'
467       ENDIF
468       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
469
470       WRITE ( io, 301 )  'e', runten, roben       
471
472    ENDIF
473
474    IF ( ocean )  THEN
475       runten = 'sa(0)    = sa(1)'
476       IF ( ibc_sa_t == 0 )  THEN
477          roben =  'sa(nzt+1) = sa_surface'
478       ELSE
479          roben =  'sa(nzt+1) = sa(nzt)'
480       ENDIF
481       WRITE ( io, 301 ) 'sa', runten, roben
482    ENDIF
483
484    IF ( humidity )  THEN
485       IF ( ibc_q_b == 0 )  THEN
486          runten = 'q(0)     = q_surface'
487       ELSE
488          runten = 'q(0)     = q(1)'
489       ENDIF
490       IF ( ibc_q_t == 0 )  THEN
491          roben =  'q(nzt)   = q_top'
492       ELSE
493          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
494       ENDIF
495       WRITE ( io, 301 ) 'q', runten, roben
496    ENDIF
497
498    IF ( passive_scalar )  THEN
499       IF ( ibc_q_b == 0 )  THEN
500          runten = 's(0)     = s_surface'
501       ELSE
502          runten = 's(0)     = s(1)'
503       ENDIF
504       IF ( ibc_q_t == 0 )  THEN
505          roben =  's(nzt)   = s_top'
506       ELSE
507          roben =  's(nzt)   = s(nzt-1) + ds/dz'
508       ENDIF
509       WRITE ( io, 301 ) 's', runten, roben
510    ENDIF
511
512    IF ( use_surface_fluxes )  THEN
513       WRITE ( io, 303 )
514       IF ( constant_heatflux )  THEN
515          WRITE ( io, 306 )  surface_heatflux
516          IF ( random_heatflux )  WRITE ( io, 307 )
517       ENDIF
518       IF ( humidity  .AND.  constant_waterflux )  THEN
519          WRITE ( io, 311 ) surface_waterflux
520       ENDIF
521       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
522          WRITE ( io, 313 ) surface_waterflux
523       ENDIF
524    ENDIF
525
526    IF ( use_top_fluxes )  THEN
527       WRITE ( io, 304 )
528       IF ( coupling_mode == 'uncoupled' )  THEN
529          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
530          IF ( constant_top_heatflux )  THEN
531             WRITE ( io, 306 )  top_heatflux
532          ENDIF
533       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
534          WRITE ( io, 316 )
535       ENDIF
536       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
537          WRITE ( io, 309 )  top_salinityflux
538       ENDIF
539       IF ( humidity  .OR.  passive_scalar )  THEN
540          WRITE ( io, 315 )
541       ENDIF
542    ENDIF
543
544    IF ( prandtl_layer )  THEN
545       WRITE ( io, 305 )  0.5 * (zu(1)-zu(0)), roughness_length, kappa, &
546                          rif_min, rif_max
547       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
548       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
549          WRITE ( io, 312 )
550       ENDIF
551       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
552          WRITE ( io, 314 )
553       ENDIF
554    ELSE
555       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
556          WRITE ( io, 310 )  rif_min, rif_max
557       ENDIF
558    ENDIF
559
560    WRITE ( io, 317 )  bc_lr, bc_ns
561    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
562       WRITE ( io, 318 )  outflow_damping_width, km_damp_max
563       IF ( turbulent_inflow )  THEN
564          WRITE ( io, 319 )  recycling_width, recycling_plane, &
565                             inflow_damping_height, inflow_damping_width
566       ENDIF
567    ENDIF
568
569!
570!-- Listing of 1D-profiles
571    WRITE ( io, 325 )  dt_dopr_listing
572    IF ( averaging_interval_pr /= 0.0 )  THEN
573       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
574    ENDIF
575
576!
577!-- DATA output
578    WRITE ( io, 330 )
579    IF ( averaging_interval_pr /= 0.0 )  THEN
580       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
581    ENDIF
582
583!
584!-- 1D-profiles
585    dopr_chr = 'Profile:'
586    IF ( dopr_n /= 0 )  THEN
587       WRITE ( io, 331 )
588
589       output_format = ''
590       IF ( netcdf_output )  THEN
591          IF ( netcdf_64bit )  THEN
592             output_format = 'netcdf (64 bit offset)'
593          ELSE
594             output_format = 'netcdf'
595          ENDIF
596       ENDIF
597       IF ( profil_output )  THEN
598          IF ( netcdf_output )  THEN
599             output_format = TRIM( output_format ) // ' and profil'
600          ELSE
601             output_format = 'profil'
602          ENDIF
603       ENDIF
604       WRITE ( io, 345 )  output_format
605
606       DO  i = 1, dopr_n
607          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
608          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
609             WRITE ( io, 332 )  dopr_chr
610             dopr_chr = '       :'
611          ENDIF
612       ENDDO
613
614       IF ( dopr_chr /= '' )  THEN
615          WRITE ( io, 332 )  dopr_chr
616       ENDIF
617       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
618       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
619    ENDIF
620
621!
622!-- 2D-arrays
623    DO  av = 0, 1
624
625       i = 1
626       do2d_xy = ''
627       do2d_xz = ''
628       do2d_yz = ''
629       DO  WHILE ( do2d(av,i) /= ' ' )
630
631          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
632          do2d_mode = do2d(av,i)(l-1:l)
633
634          SELECT CASE ( do2d_mode )
635             CASE ( 'xy' )
636                ll = LEN_TRIM( do2d_xy )
637                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
638             CASE ( 'xz' )
639                ll = LEN_TRIM( do2d_xz )
640                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
641             CASE ( 'yz' )
642                ll = LEN_TRIM( do2d_yz )
643                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
644          END SELECT
645
646          i = i + 1
647
648       ENDDO
649
650       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
651              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
652              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
653            ( netcdf_output  .OR.  iso2d_output ) )  THEN
654
655          IF (  av == 0 )  THEN
656             WRITE ( io, 334 )  ''
657          ELSE
658             WRITE ( io, 334 )  '(time-averaged)'
659          ENDIF
660
661          IF ( do2d_at_begin )  THEN
662             begin_chr = 'and at the start'
663          ELSE
664             begin_chr = ''
665          ENDIF
666
667          output_format = ''
668          IF ( netcdf_output )  THEN
669             IF ( netcdf_64bit )  THEN
670                output_format = 'netcdf (64 bit offset)'
671             ELSE
672                output_format = 'netcdf'
673             ENDIF
674          ENDIF
675          IF ( iso2d_output )  THEN
676             IF ( netcdf_output )  THEN
677                output_format = TRIM( output_format ) // ' and iso2d'
678             ELSE
679                output_format = 'iso2d'
680             ENDIF
681          ENDIF
682          WRITE ( io, 345 )  output_format
683
684          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
685             i = 1
686             slices = '/'
687             coordinates = '/'
688!
689!--          Building strings with index and coordinate informations of the
690!--          slices
691             DO  WHILE ( section(i,1) /= -9999 )
692
693                WRITE (section_chr,'(I5)')  section(i,1)
694                section_chr = ADJUSTL( section_chr )
695                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
696
697                WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
698                coor_chr = ADJUSTL( coor_chr )
699                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
700
701                i = i + 1
702             ENDDO
703             IF ( av == 0 )  THEN
704                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
705                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
706                                   TRIM( coordinates )
707                IF ( skip_time_do2d_xy /= 0.0 )  THEN
708                   WRITE ( io, 339 )  skip_time_do2d_xy
709                ENDIF
710             ELSE
711                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
712                                   TRIM( begin_chr ), averaging_interval, &
713                                   dt_averaging_input, 'k', TRIM( slices ), &
714                                   TRIM( coordinates )
715                IF ( skip_time_data_output_av /= 0.0 )  THEN
716                   WRITE ( io, 339 )  skip_time_data_output_av
717                ENDIF
718             ENDIF
719
720          ENDIF
721
722          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
723             i = 1
724             slices = '/'
725             coordinates = '/'
726!
727!--          Building strings with index and coordinate informations of the
728!--          slices
729             DO  WHILE ( section(i,2) /= -9999 )
730
731                WRITE (section_chr,'(I5)')  section(i,2)
732                section_chr = ADJUSTL( section_chr )
733                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
734
735                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
736                coor_chr = ADJUSTL( coor_chr )
737                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
738
739                i = i + 1
740             ENDDO
741             IF ( av == 0 )  THEN
742                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
743                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
744                                   TRIM( coordinates )
745                IF ( skip_time_do2d_xz /= 0.0 )  THEN
746                   WRITE ( io, 339 )  skip_time_do2d_xz
747                ENDIF
748             ELSE
749                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
750                                   TRIM( begin_chr ), averaging_interval, &
751                                   dt_averaging_input, 'j', TRIM( slices ), &
752                                   TRIM( coordinates )
753                IF ( skip_time_data_output_av /= 0.0 )  THEN
754                   WRITE ( io, 339 )  skip_time_data_output_av
755                ENDIF
756             ENDIF
757          ENDIF
758
759          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
760             i = 1
761             slices = '/'
762             coordinates = '/'
763!
764!--          Building strings with index and coordinate informations of the
765!--          slices
766             DO  WHILE ( section(i,3) /= -9999 )
767
768                WRITE (section_chr,'(I5)')  section(i,3)
769                section_chr = ADJUSTL( section_chr )
770                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
771
772                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
773                coor_chr = ADJUSTL( coor_chr )
774                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
775
776                i = i + 1
777             ENDDO
778             IF ( av == 0 )  THEN
779                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
780                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
781                                   TRIM( coordinates )
782                IF ( skip_time_do2d_yz /= 0.0 )  THEN
783                   WRITE ( io, 339 )  skip_time_do2d_yz
784                ENDIF
785             ELSE
786                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
787                                   TRIM( begin_chr ), averaging_interval, &
788                                   dt_averaging_input, 'i', TRIM( slices ), &
789                                   TRIM( coordinates )
790                IF ( skip_time_data_output_av /= 0.0 )  THEN
791                   WRITE ( io, 339 )  skip_time_data_output_av
792                ENDIF
793             ENDIF
794          ENDIF
795
796       ENDIF
797
798    ENDDO
799
800!
801!-- 3d-arrays
802    DO  av = 0, 1
803
804       i = 1
805       do3d_chr = ''
806       DO  WHILE ( do3d(av,i) /= ' ' )
807
808          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
809          i = i + 1
810
811       ENDDO
812
813       IF ( do3d_chr /= '' )  THEN
814          IF ( av == 0 )  THEN
815             WRITE ( io, 336 )  ''
816          ELSE
817             WRITE ( io, 336 )  '(time-averaged)'
818          ENDIF
819
820          output_format = ''
821          IF ( netcdf_output )  THEN
822             IF ( netcdf_64bit .AND. netcdf_64bit_3d )  THEN
823                output_format = 'netcdf (64 bit offset)'
824             ELSE
825                output_format = 'netcdf'
826             ENDIF
827          ENDIF
828          IF ( avs_output )  THEN
829             IF ( netcdf_output )  THEN
830                output_format = TRIM( output_format ) // ' and avs'
831             ELSE
832                output_format = 'avs'
833             ENDIF
834          ENDIF
835          WRITE ( io, 345 )  output_format
836
837          IF ( do3d_at_begin )  THEN
838             begin_chr = 'and at the start'
839          ELSE
840             begin_chr = ''
841          ENDIF
842          IF ( av == 0 )  THEN
843             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
844                                zu(nz_do3d), nz_do3d
845          ELSE
846             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
847                                TRIM( begin_chr ), averaging_interval, &
848                                dt_averaging_input, zu(nz_do3d), nz_do3d
849          ENDIF
850
851          IF ( do3d_compress )  THEN
852             do3d_chr = ''
853             i = 1
854             DO WHILE ( do3d(av,i) /= ' ' )
855
856                SELECT CASE ( do3d(av,i) )
857                   CASE ( 'u' )
858                      j = 1
859                   CASE ( 'v' )
860                      j = 2
861                   CASE ( 'w' )
862                      j = 3
863                   CASE ( 'p' )
864                      j = 4
865                   CASE ( 'pt' )
866                      j = 5
867                END SELECT
868                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
869                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
870                           ':' // prec // ','
871                i = i + 1
872
873             ENDDO
874             WRITE ( io, 338 )  do3d_chr
875
876          ENDIF
877
878          IF ( av == 0 )  THEN
879             IF ( skip_time_do3d /= 0.0 )  THEN
880                WRITE ( io, 339 )  skip_time_do3d
881             ENDIF
882          ELSE
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    ENDDO
891
892!
893!-- Timeseries
894    IF ( dt_dots /= 9999999.9 )  THEN
895       WRITE ( io, 340 )
896
897       output_format = ''
898       IF ( netcdf_output )  THEN
899          IF ( netcdf_64bit )  THEN
900             output_format = 'netcdf (64 bit offset)'
901          ELSE
902             output_format = 'netcdf'
903          ENDIF
904       ENDIF
905       IF ( profil_output )  THEN
906          IF ( netcdf_output )  THEN
907             output_format = TRIM( output_format ) // ' and profil'
908          ELSE
909             output_format = 'profil'
910          ENDIF
911       ENDIF
912       WRITE ( io, 345 )  output_format
913       WRITE ( io, 341 )  dt_dots
914    ENDIF
915
916#if defined( __dvrp_graphics )
917!
918!-- Dvrp-output
919    IF ( dt_dvrp /= 9999999.9 )  THEN
920       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
921                          TRIM( dvrp_username ), TRIM( dvrp_directory )
922       i = 1
923       l = 0
924       DO WHILE ( mode_dvrp(i) /= ' ' )
925          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
926             READ ( mode_dvrp(i), '(10X,I2)' )  j
927             l = l + 1
928             IF ( do3d(0,j) /= ' ' )  THEN
929                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l)
930             ENDIF
931          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
932             READ ( mode_dvrp(i), '(6X,I2)' )  j
933             IF ( do2d(0,j) /= ' ' )  WRITE ( io, 362 )  TRIM( do2d(0,j) )
934          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
935             WRITE ( io, 363 )
936          ENDIF
937          i = i + 1
938       ENDDO
939    ENDIF
940#endif
941
942#if defined( __spectra )
943!
944!-- Spectra output
945    IF ( dt_dosp /= 9999999.9 ) THEN
946       WRITE ( io, 370 )
947
948       output_format = ''
949       IF ( netcdf_output )  THEN
950          IF ( netcdf_64bit )  THEN
951             output_format = 'netcdf (64 bit offset)'
952          ELSE
953             output_format = 'netcdf'
954          ENDIF
955       ENDIF
956       IF ( profil_output )  THEN
957          IF ( netcdf_output )  THEN
958             output_format = TRIM( output_format ) // ' and profil'
959          ELSE
960             output_format = 'profil'
961          ENDIF
962       ENDIF
963       WRITE ( io, 345 )  output_format
964       WRITE ( io, 371 )  dt_dosp
965       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
966       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
967                          ( spectra_direction(i), i = 1,10 ),  &
968                          ( comp_spectra_level(i), i = 1,100 ), &
969                          ( plot_spectra_level(i), i = 1,100 ), &
970                          averaging_interval_sp, dt_averaging_input_pr
971    ENDIF
972#endif
973
974    WRITE ( io, 99 )
975
976!
977!-- Physical quantities
978    WRITE ( io, 400 )
979
980!
981!-- Geostrophic parameters
982    WRITE ( io, 410 )  omega, phi, f, fs
983
984!
985!-- Other quantities
986    WRITE ( io, 411 )  g
987    IF ( use_reference )  THEN
988       IF ( ocean )  THEN
989          WRITE ( io, 412 )  prho_reference
990       ELSE
991          WRITE ( io, 413 )  pt_reference
992       ENDIF
993    ENDIF
994
995!
996!-- Cloud physics parameters
997    IF ( cloud_physics ) THEN
998       WRITE ( io, 415 )
999       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1000    ENDIF
1001
1002!-- Profile of the geostrophic wind (component ug)
1003!-- Building output strings
1004    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1005    gradients = '------'
1006    slices = '     0'
1007    coordinates = '   0.0'
1008    i = 1
1009    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1010     
1011       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1012       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1013
1014       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1015       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1016
1017       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1018       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1019
1020       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1021       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1022
1023       i = i + 1
1024    ENDDO
1025
1026    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1027                       TRIM( gradients ), TRIM( slices )
1028
1029!-- Profile of the geostrophic wind (component vg)
1030!-- Building output strings
1031    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1032    gradients = '------'
1033    slices = '     0'
1034    coordinates = '   0.0'
1035    i = 1
1036    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1037
1038       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1039       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1040
1041       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1042       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1043
1044       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1045       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1046
1047       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1048       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1049
1050       i = i + 1 
1051    ENDDO
1052
1053    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1054                       TRIM( gradients ), TRIM( slices )
1055
1056!
1057!-- Initial temperature profile
1058!-- Building output strings, starting with surface temperature
1059    WRITE ( temperatures, '(F6.2)' )  pt_surface
1060    gradients = '------'
1061    slices = '     0'
1062    coordinates = '   0.0'
1063    i = 1
1064    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1065
1066       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1067       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1068
1069       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1070       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1071
1072       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1073       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1074
1075       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1076       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1077
1078       i = i + 1
1079    ENDDO
1080
1081    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1082                       TRIM( gradients ), TRIM( slices )
1083
1084!
1085!-- Initial humidity profile
1086!-- Building output strings, starting with surface humidity
1087    IF ( humidity  .OR.  passive_scalar )  THEN
1088       WRITE ( temperatures, '(E8.1)' )  q_surface
1089       gradients = '--------'
1090       slices = '       0'
1091       coordinates = '     0.0'
1092       i = 1
1093       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1094         
1095          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1096          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1097
1098          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1099          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1100         
1101          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1102          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1103         
1104          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1105          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1106
1107          i = i + 1
1108       ENDDO
1109
1110       IF ( humidity )  THEN
1111          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1112                             TRIM( gradients ), TRIM( slices )
1113       ELSE
1114          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1115                             TRIM( gradients ), TRIM( slices )
1116       ENDIF
1117    ENDIF
1118
1119!
1120!-- Initial salinity profile
1121!-- Building output strings, starting with surface salinity
1122    IF ( ocean )  THEN
1123       WRITE ( temperatures, '(F6.2)' )  sa_surface
1124       gradients = '------'
1125       slices = '     0'
1126       coordinates = '   0.0'
1127       i = 1
1128       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1129
1130          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1131          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1132
1133          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1134          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1135
1136          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1137          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1138
1139          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1140          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1141
1142          i = i + 1
1143       ENDDO
1144
1145       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1146                          TRIM( gradients ), TRIM( slices )
1147    ENDIF
1148
1149!
1150!-- LES / turbulence parameters
1151    WRITE ( io, 450 )
1152
1153!--
1154! ... LES-constants used must still be added here
1155!--
1156    IF ( constant_diffusion )  THEN
1157       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1158                          prandtl_number
1159    ENDIF
1160    IF ( .NOT. constant_diffusion)  THEN
1161       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1162       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1163       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1164       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1165    ENDIF
1166
1167!
1168!-- Special actions during the run
1169    WRITE ( io, 470 )
1170    IF ( create_disturbances )  THEN
1171       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1172                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1173                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1174       IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1175          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1176       ELSE
1177          WRITE ( io, 473 )  disturbance_energy_limit
1178       ENDIF
1179       WRITE ( io, 474 )  TRIM( random_generator )
1180    ENDIF
1181    IF ( pt_surface_initial_change /= 0.0 )  THEN
1182       WRITE ( io, 475 )  pt_surface_initial_change
1183    ENDIF
1184    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1185       WRITE ( io, 476 )  q_surface_initial_change       
1186    ENDIF
1187    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1188       WRITE ( io, 477 )  q_surface_initial_change       
1189    ENDIF
1190
1191    IF ( particle_advection )  THEN
1192!
1193!--    Particle attributes
1194       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1195                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1196                          end_time_prel, dt_sort_particles
1197       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1198       IF ( random_start_position )  WRITE ( io, 481 )
1199       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1200       WRITE ( io, 495 )  total_number_of_particles
1201       IF ( .NOT. vertical_particle_advection )  WRITE ( io, 482 )
1202       IF ( maximum_number_of_tailpoints /= 0 )  THEN
1203          WRITE ( io, 483 )  maximum_number_of_tailpoints
1204          IF ( minimum_tailpoint_distance /= 0 )  THEN
1205             WRITE ( io, 484 )  total_number_of_tails,      &
1206                                minimum_tailpoint_distance, &
1207                                maximum_tailpoint_age
1208          ENDIF
1209       ENDIF
1210       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1211          WRITE ( io, 485 )  dt_write_particle_data
1212          output_format = ''
1213          IF ( netcdf_output )  THEN
1214             IF ( netcdf_64bit )  THEN
1215                output_format = 'netcdf (64 bit offset) and binary'
1216             ELSE
1217                output_format = 'netcdf and binary'
1218             ENDIF
1219          ELSE
1220             output_format = 'binary'
1221          ENDIF
1222          WRITE ( io, 345 )  output_format
1223       ENDIF
1224       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1225       IF ( write_particle_statistics )  WRITE ( io, 486 )
1226
1227       WRITE ( io, 487 )  number_of_particle_groups
1228
1229       DO  i = 1, number_of_particle_groups
1230          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1231             WRITE ( io, 490 )  i, 0.0
1232             WRITE ( io, 492 )
1233          ELSE
1234             WRITE ( io, 490 )  i, radius(i)
1235             IF ( density_ratio(i) /= 0.0 )  THEN
1236                WRITE ( io, 491 )  density_ratio(i)
1237             ELSE
1238                WRITE ( io, 492 )
1239             ENDIF
1240          ENDIF
1241          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1242                             pdx(i), pdy(i), pdz(i)
1243       ENDDO
1244
1245    ENDIF
1246
1247
1248!
1249!-- Parameters of 1D-model
1250    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1251       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1252                          mixing_length_1d, dissipation_1d
1253       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1254          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1255       ENDIF
1256    ENDIF
1257
1258!
1259!-- User-defined informations
1260    CALL user_header( io )
1261
1262    WRITE ( io, 99 )
1263
1264!
1265!-- Write buffer contents to disc immediately
1266    CALL local_flush( io )
1267
1268!
1269!-- Here the FORMATs start
1270
1271 99 FORMAT (1X,78('-'))
1272100 FORMAT (/1X,'*************************',11X,42('-')/        &
1273            1X,'* ',A,' *',11X,A/                               &
1274            1X,'*************************',11X,42('-'))
1275101 FORMAT (37X,'coupled run: ',A/ &
1276            37X,42('-'))
1277102 FORMAT (/' Date:            ',A8,11X,'Run:       ',A20/      &
1278            ' Time:            ',A8,11X,'Run-No.:   ',I2.2/     &
1279            ' Run on host:   ',A10)
1280#if defined( __parallel )
1281103 FORMAT (' Number of PEs:',7X,I4,11X,'Processor grid (x,y): (',I3,',',I3, &
1282              ')',1X,A)
1283104 FORMAT (' Number of PEs:',7X,I4,11X,'Tasks:',I4,'   threads per task:',I4/ &
1284              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1285105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1286106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1287            37X,'because the job is running on an SMP-cluster')
1288107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1289#endif
1290110 FORMAT (/' Numerical Schemes:'/ &
1291             ' -----------------'/)
1292111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1293112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1294            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1295113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1296                  ' or Upstream')
1297114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1298115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1299116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1300                  ' or Upstream')
1301117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1302118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1303119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1304            '     Translation velocity = ',A/ &
1305            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1306120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1307                  ' of timestep changes)')
1308121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1309                  ' timestep changes')
1310122 FORMAT (' --> Time differencing scheme: ',A)
1311123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1312            '     maximum damping coefficient: ',F5.3, ' 1/s')
1313124 FORMAT ('     Spline-overshoots are being suppressed')
1314125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1315                  ' of'/                                                       &
1316            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1317126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1318                  ' of'/                                                       &
1319            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1320127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1321            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1322128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1323            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1324129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1325130 FORMAT (' --> Additional prognostic equation for the total water content')
1326131 FORMAT (' --> Parameterization of condensation processes via (0%-or100%)')
1327132 FORMAT (' --> Parameterization of long-wave radiation processes via'/ &
1328            '     effective emissivity scheme')
1329133 FORMAT (' --> Precipitation parameterization via Kessler-Scheme')
1330134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1331135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1332                  A,'-cycle)'/ &
1333            '     number of grid levels:                   ',I2/ &
1334            '     Gauss-Seidel red/black iterations:       ',I2)
1335136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1336                  I3,')')
1337137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1338            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1339                  I3,')'/ &
1340            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1341                  I3,')')
1342138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1343139 FORMAT (' --> Loop optimization method: ',A)
1344140 FORMAT ('     maximum residual allowed:                ',E10.3)
1345141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1346142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1347                  'step')
1348143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1349                  'kinetic energy')
1350150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1351                  'conserved')
1352200 FORMAT (//' Run time and time step information:'/ &
1353             ' ----------------------------------'/)
1354201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1355             '    CFL-factor: ',F4.2)
1356202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1357203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1358             ' End time:         ',F9.3,' s')
1359204 FORMAT ( A,F9.3,' s')
1360205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1361206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1362             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1363               '  ',F9.3,' s'/                                                 &
1364             '                                   per second of simulated tim', &
1365               'e: ',F9.3,' s')
1366250 FORMAT (//' Computational grid and domain size:'/ &
1367              ' ----------------------------------'// &
1368              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1369              ' m    dz =    ',F7.3,' m'/ &
1370              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1371              ' m  z(u) = ',F10.3,' m'/)
1372252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1373              ' factor: ',F5.3/ &
1374            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1375254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1376            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1377255 FORMAT (' Subdomains have equal size')
1378256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1379              'have smaller sizes'/                                          &
1380            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1381260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1382             ' degrees')
1383270 FORMAT (//' Topography informations:'/ &
1384              ' -----------------------'// &
1385              1X,'Topography: ',A)
1386271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1387              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1388                ' / ',I4)
1389280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1390              ' ------------------------------'// &
1391              ' Canopy mode: ', A / &
1392              ' Canopy top: ',I4 / &
1393              ' Leaf drag coefficient: ',F6.2 /)
1394281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1395              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1396282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1397283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1398              ' Height:              ',A,'  m'/ &
1399              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1400              ' Gradient:            ',A,'  m**2/m**4'/ &
1401              ' Gridpoint:           ',A)
1402               
1403300 FORMAT (//' Boundary conditions:'/ &
1404             ' -------------------'// &
1405             '                     p                    uv             ', &
1406             '                   pt'// &
1407             ' B. bound.: ',A/ &
1408             ' T. bound.: ',A)
1409301 FORMAT (/'                     ',A// &
1410             ' B. bound.: ',A/ &
1411             ' T. bound.: ',A)
1412303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1413304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1414305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1415               'computational u,v-level:'// &
1416             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1417             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1418306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1419307 FORMAT ('       Heatflux has a random normal distribution')
1420308 FORMAT ('       Predefined surface temperature')
1421309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1422310 FORMAT (//'    1D-Model:'// &
1423             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1424311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1425312 FORMAT ('       Predefined surface humidity')
1426313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1427314 FORMAT ('       Predefined scalar value at the surface')
1428315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1429316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1430                    'atmosphere model')
1431317 FORMAT (//' Lateral boundaries:'/ &
1432            '       left/right:  ',A/    &
1433            '       north/south: ',A)
1434318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1435                    'max =',F5.1,' m**2/s')
1436319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1437            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1438            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1439320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1440            '                                          v: ',F9.6,' m**2/s**2')
1441325 FORMAT (//' List output:'/ &
1442             ' -----------'//  &
1443            '    1D-Profiles:'/    &
1444            '       Output every             ',F8.2,' s')
1445326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1446            '       Averaging input every    ',F8.2,' s')
1447330 FORMAT (//' Data output:'/ &
1448             ' -----------'/)
1449331 FORMAT (/'    1D-Profiles:')
1450332 FORMAT (/'       ',A)
1451333 FORMAT ('       Output every             ',F8.2,' s',/ &
1452            '       Time averaged over       ',F8.2,' s'/ &
1453            '       Averaging input every    ',F8.2,' s')
1454334 FORMAT (/'    2D-Arrays',A,':')
1455335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1456            '       Output every             ',F8.2,' s  ',A/ &
1457            '       Cross sections at ',A1,' = ',A/ &
1458            '       scalar-coordinates:   ',A,' m'/)
1459336 FORMAT (/'    3D-Arrays',A,':')
1460337 FORMAT (/'       Arrays: ',A/ &
1461            '       Output every             ',F8.2,' s  ',A/ &
1462            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1463338 FORMAT ('       Compressed data output'/ &
1464            '       Decimal precision: ',A/)
1465339 FORMAT ('       No output during initial ',F8.2,' s')
1466340 FORMAT (/'    Time series:')
1467341 FORMAT ('       Output every             ',F8.2,' s'/)
1468342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1469            '       Output every             ',F8.2,' s  ',A/ &
1470            '       Time averaged over       ',F8.2,' s'/ &
1471            '       Averaging input every    ',F8.2,' s'/ &
1472            '       Cross sections at ',A1,' = ',A/ &
1473            '       scalar-coordinates:   ',A,' m'/)
1474343 FORMAT (/'       Arrays: ',A/ &
1475            '       Output every             ',F8.2,' s  ',A/ &
1476            '       Time averaged over       ',F8.2,' s'/ &
1477            '       Averaging input every    ',F8.2,' s'/ &
1478            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1479345 FORMAT ('       Output format: ',A/)
1480#if defined( __dvrp_graphics )
1481360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1482            '       Output every      ',F7.1,' s'/ &
1483            '       Output mode:      ',A/ &
1484            '       Host / User:      ',A,' / ',A/ &
1485            '       Directory:        ',A// &
1486            '       The sequence contains:')
1487361 FORMAT ('       Isosurface of ',A,'  Threshold value: ', E12.3)
1488362 FORMAT ('       Sectional plane ',A)
1489363 FORMAT ('       Particles')
1490#endif
1491#if defined( __spectra )
1492370 FORMAT ('    Spectra:')
1493371 FORMAT ('       Output every ',F7.1,' s'/)
1494372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1495            '       Directions: ', 10(A5,',')/                         &
1496            '       height levels  k = ', 20(I3,',')/                  &
1497            '                          ', 20(I3,',')/                  &
1498            '                          ', 20(I3,',')/                  &
1499            '                          ', 20(I3,',')/                  &
1500            '                          ', 19(I3,','),I3,'.'/           &
1501            '       height levels selected for standard plot:'/        &
1502            '                      k = ', 20(I3,',')/                  &
1503            '                          ', 20(I3,',')/                  &
1504            '                          ', 20(I3,',')/                  &
1505            '                          ', 20(I3,',')/                  &
1506            '                          ', 19(I3,','),I3,'.'/           &
1507            '       Time averaged over ', F7.1, ' s,' /                &
1508            '       Profiles for the time averaging are taken every ', &
1509                    F6.1,' s')
1510#endif
1511400 FORMAT (//' Physical quantities:'/ &
1512              ' -------------------'/)
1513410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1514            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1515            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1516            '                            f*    = ',F9.6,' 1/s')
1517411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1518412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1519413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1520415 FORMAT (/'    Cloud physics parameters:'/ &
1521             '    ------------------------'/)
1522416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1523            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1524            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1525            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1526            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1527420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1528            '       Height:        ',A,'  m'/ &
1529            '       Temperature:   ',A,'  K'/ &
1530            '       Gradient:      ',A,'  K/100m'/ &
1531            '       Gridpoint:     ',A)
1532421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1533            '       Height:      ',A,'  m'/ &
1534            '       Humidity:    ',A,'  kg/kg'/ &
1535            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1536            '       Gridpoint:   ',A)
1537422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1538            '       Height:                  ',A,'  m'/ &
1539            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1540            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1541            '       Gridpoint:               ',A)
1542423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1543            '       Height:      ',A,'  m'/ &
1544            '       ug:          ',A,'  m/s'/ &
1545            '       Gradient:    ',A,'  1/100s'/ &
1546            '       Gridpoint:   ',A)
1547424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1548            '       Height:      ',A,'  m'/ &
1549            '       vg:          ',A,'  m/s'/ &
1550            '       Gradient:    ',A,'  1/100s'/ &
1551            '       Gridpoint:   ',A)
1552425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1553            '       Height:     ',A,'  m'/ &
1554            '       Salinity:   ',A,'  psu'/ &
1555            '       Gradient:   ',A,'  psu/100m'/ &
1556            '       Gridpoint:  ',A)
1557450 FORMAT (//' LES / Turbulence quantities:'/ &
1558              ' ---------------------------'/)
1559451 FORMAT ('   Diffusion coefficients are constant:'/ &
1560            '   Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1561452 FORMAT ('   Mixing length is limited to the Prandtl mixing lenth.')
1562453 FORMAT ('   Mixing length is limited to ',F4.2,' * z')
1563454 FORMAT ('   TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1564455 FORMAT ('   initial TKE is prescribed as ',E9.2,' (m/s)**2')
1565470 FORMAT (//' Actions during the simulation:'/ &
1566              ' -----------------------------'/)
1567471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1568            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1569            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1570            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1571472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1572                 ' to i/j =',I4)
1573473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1574                 1X,F5.3, ' m**2/s**2')
1575474 FORMAT ('    Random number generator used    : ',A/)
1576475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1577                 'respectively, if'/ &
1578            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1579                 ' 3D-simulation'/)
1580476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1581                 'respectively, if the'/ &
1582            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1583                 ' the 3D-simulation'/)
1584477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1585                 'respectively, if the'/ &
1586            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1587                 ' the 3D-simulation'/)
1588480 FORMAT ('    Particles:'/ &
1589            '    ---------'// &
1590            '       Particle advection is active (switched on at t = ', F7.1, &
1591                    ' s)'/ &
1592            '       Start of new particle generations every  ',F6.1,' s'/ &
1593            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
1594            '                            bottom:     ', A, ' top:         ', A/&
1595            '       Maximum particle age:                 ',F9.1,' s'/ &
1596            '       Advection stopped at t = ',F9.1,' s'/ &
1597            '       Particles are sorted every ',F9.1,' s'/)
1598481 FORMAT ('       Particles have random start positions'/)
1599482 FORMAT ('       Particles are advected only horizontally'/)
1600483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
1601484 FORMAT ('            Number of tails of the total domain: ',I10/ &
1602            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
1603            '            Maximum age of the end of the tail:  ',F8.2,' s')
1604485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
1605486 FORMAT ('       Particle statistics are written on file'/)
1606487 FORMAT ('       Number of particle groups: ',I2/)
1607488 FORMAT ('       SGS velocity components are used for particle advection'/ &
1608            '          minimum timestep for advection: ', F7.5/)
1609489 FORMAT ('       Number of particles simultaneously released at each ', &
1610                    'point: ', I5/)
1611490 FORMAT ('       Particle group ',I2,':'/ &
1612            '          Particle radius: ',E10.3, 'm')
1613491 FORMAT ('          Particle inertia is activated'/ &
1614            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
1615492 FORMAT ('          Particles are advected only passively (no inertia)'/)
1616493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
1617            '                                         y:',F8.1,' - ',F8.1,' m'/&
1618            '                                         z:',F8.1,' - ',F8.1,' m'/&
1619            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
1620                       ' m  dz = ',F8.1,' m'/)
1621494 FORMAT ('       Output of particle time series in NetCDF format every ', &
1622                    F8.2,' s'/)
1623495 FORMAT ('       Number of particles in total domain: ',I10/)
1624500 FORMAT (//' 1D-Model parameters:'/                           &
1625              ' -------------------'//                           &
1626            '    Simulation time:                   ',F8.1,' s'/ &
1627            '    Run-controll output every:         ',F8.1,' s'/ &
1628            '    Vertical profile output every:     ',F8.1,' s'/ &
1629            '    Mixing length calculation:         ',A/         &
1630            '    Dissipation calculation:           ',A/)
1631502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
1632
1633
1634 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.