source: palm/tags/release-3.6/SOURCE/header.f90 @ 2238

Last change on this file since 2238 was 226, checked in by raasch, 15 years ago

preparations for the next release

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