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

Last change on this file since 1 was 1, checked in by raasch, 18 years ago

Initial repository layout and content

File size: 58.4 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: header.f90,v $
11! Revision 1.63  2006/08/22 13:53:13  raasch
12! Output of dz_max
13!
14! Revision 1.62  2006/08/04 14:38:41  raasch
15! Generation of the run description header as well as run date and run time
16! moved to routine check_parameters,
17! output for additional particle quantities
18!
19! Revision 1.61  2006/04/26 12:19:51  raasch
20! Output of threads per task
21!
22! Revision 1.60  2006/04/11 14:57:01  raasch
23! pl_spectra renamed data_output_sp
24!
25! Revision 1.59  2006/03/14 12:44:10  raasch
26! Output of the initial geostrophic wind profile corrected
27!
28! Revision 1.58  2006/02/23 12:24:22  raasch
29! Output of psl, psr, pdx, etc. for each particle group, output of e_min,
30! information about volume flow conservation and usage of NetCDF 64 bit offset
31! format, pl.. renamed do.., skip_time control parameters for do..,
32! ebene renamed section, .._anz renamed .._no, dt_average renamed
33! dt_averaging_input_pr
34! output of 2d/3d data averaging informations, buffer is forced to be written
35! on file at the end of the routine
36!
37! Revision 1.57  2005/10/20 14:06:44  raasch
38! Error in output of yz-slice information removed
39!
40! Revision 1.56  2005/07/01 07:48:14  steinfeld
41! Information on the initial profiles of ug and vg added;
42! dependency of ug and vg on height considered in the output of
43! the boundary conditions for u and v
44!
45! Revision 1.55  2005/06/26 19:53:15  raasch
46! gas_constant renamed r_d, latent_heat renamed l_v, radius is used instead
47! of diameter, output formats 335+337 changed
48!
49! Revision 1.54  2005/05/19 08:32:27  raasch
50! Error in output of particle inertia information removed
51!
52! Revision 1.53  2005/05/18 15:31:59  raasch
53! Informations about data output format (netcdf, iso2d, etc.) are given
54!
55! Revision 1.52  2005/04/23 09:16:10  raasch
56! fcl_factor renamed cfl_factor
57!
58! Revision 1.51  2005/03/26 20:23:14  raasch
59! Output of horizontal boundary conditions, output of additional call of
60! pressure solver in case of Runge-Kutta schemes,
61! calculate the number of particle groups (formerly unknown = 0 )
62!
63! Revision 1.50  2004/04/30 11:48:02  raasch
64! Forcing a 1d-decomposition is output on linux-cluster and decalpha,
65! output of subdomain sizes, impulse_advec renamed momentum_advec
66!
67! Revision 1.49  2004/01/28 15:09:15  raasch
68! Output of timestep schemes modified
69!
70! Revision 1.48  2003/10/29 08:52:04  raasch
71! Additional output for multigrid method (lowest levels gathered on PE0),
72! particle output modified for particle groups
73!
74! Revision 1.47  2003/04/16 12:58:18  raasch
75! Output for mixing length limitations revised
76!
77! Revision 1.46  2003/03/16 09:39:31  raasch
78! Two underscores (_) are placed in front of all define-strings
79!
80! Revision 1.45  2003/03/14 13:43:21  raasch
81! Informations about random generator
82!
83! Revision 1.44  2003/03/12 16:31:45  raasch
84! Small change for NEC system
85!
86! Revision 1.43  2002/12/19 14:53:47  raasch
87! Informations about user defined restart times added
88!
89! Revision 1.42  2002/09/12 13:03:24  raasch
90! Informations about particle inertia added
91!
92! Revision 1.41  2002/06/11 13:09:11  raasch
93! Information about hybrid solver, usage of 1d-decomposition and fast version
94! of prognostic_equations included,
95! no output of mixing length adjustments in case of constant diffusion
96!
97! Revision 1.40  2002/04/16  08:06:13  08:06:13  raasch (Siegfried Raasch)
98! Informations about particle boundary conditions and output of particle
99! data added, direct output of informations about scalar transport (instead
100! of using humidity)
101!
102! Revision 1.39  2001/08/21 08:50:54  raasch
103! Informations about mixing length adjustment, particle tails and dvrp PE usage
104! included
105!
106! Revision 1.38  2001/07/20 13:05:39  raasch
107! Information about multigrid method included
108!
109! Revision 1.37  2001/07/12 12:08:14  raasch
110! Additional informations about dvrp-output (host and filenames) and
111! particles (maximum age, random start positions), + module particle_attributes
112!
113! Revision 1.36  2001/03/30 07:23:53  raasch
114! Translation of remaining German identifiers (variables, subroutines, etc.)
115!
116! Revision 1.35  2001/01/29 12:25:55  raasch
117! Informations about using passive scalar
118!
119! Revision 1.34  2001/01/25 07:00:48  raasch
120! Information about using surface fluxes and fft-method added
121!
122! Revision 1.33  2001/01/05 15:11:41  raasch
123! Spectra informations added. Old revision remarks deleted.
124!
125! Revision 1.32  2001/01/03 13:08:47  letzel
126! File output translated into English.
127!
128! Revision 1.31  2000/12/28 13:04:54  raasch
129! Slicer information added to dvrp-output.
130! Informations about optionally used packages are put in cpp-define-brackets.
131!
132! Revision 1.30  2000/04/27 07:08:14  raasch
133! notice if processor topology is predefined by user,
134! general notice about dvrp-output (including isosurface and particles),
135! all comments translated into English
136!
137! Revision 1.1  1997/08/11 06:17:20  raasch
138! Initial revision
139!
140!
141! Description:
142! ------------
143! Writing a header with all important informations about the actual run.
144! This subroutine is called three times, two times at the beginning
145! (writing information on files RUN_CONTROL and HEADER) and one time at the
146! end of the run, then writing additional information about CPU-usage on file
147! header.
148!------------------------------------------------------------------------------!
149
150    USE arrays_3d
151    USE control_parameters
152    USE cloud_parameters
153    USE cpulog
154    USE dvrp_variables
155    USE grid_variables
156    USE indices
157    USE model_1d
158    USE particle_attributes
159    USE pegrid
160    USE spectrum
161
162    IMPLICIT NONE
163
164    CHARACTER (LEN=1)  ::  prec
165    CHARACTER (LEN=2)  ::  do2d_mode
166    CHARACTER (LEN=5)  ::  section_chr
167    CHARACTER (LEN=9)  ::  time_to_string
168    CHARACTER (LEN=10) ::  coor_chr, host_chr
169    CHARACTER (LEN=16) ::  begin_chr
170    CHARACTER (LEN=40) ::  output_format
171    CHARACTER (LEN=70) ::  char1, char2, coordinates, gradients, dopr_chr, &
172                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
173                           run_classification, slices, temperatures, &
174                           ugcomponent, vgcomponent
175    CHARACTER (LEN=85) ::  roben, runten
176
177    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, i, ihost, io, j, l, ll
178    REAL    ::  cpuseconds_per_simulated_second
179
180!
181!-- Open the output file. At the end of the simulation, output is directed
182!-- to unit 19.
183    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
184         .NOT. simulated_time_at_begin /= simulated_time )  THEN
185       io = 15   !  header output on file RUN_CONTROL
186    ELSE
187       io = 19   !  header output on file HEADER
188    ENDIF
189    CALL check_open( io )
190
191!
192!-- At the end of the run, output file (HEADER) will be rewritten with
193!-- new informations
194    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
195
196!
197!-- Determine kind of model run
198    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
199       run_classification = '3D - restart run'
200    ELSE
201       IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
202          run_classification = '3D - run without 1D - prerun'
203       ELSEIF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 ) THEN
204          run_classification = '3D - run with 1D - prerun'
205       ELSE
206          PRINT*,'+++ header:  unknown action(s): ',initializing_actions
207       ENDIF
208    ENDIF
209
210!
211!-- Run-identification, date, time, host
212    host_chr = host(1:10)
213    WRITE ( io, 100 )  version, TRIM( run_classification ), run_date, &
214                       run_identifier, run_time, runnr, ADJUSTR( host_chr )
215#if defined( __parallel )
216    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
217       char1 = 'calculated'
218    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
219               host(1:2) == 'lc' )  .AND.                          &
220             npex == -1  .AND.  pdims(2) == 1 )  THEN
221       char1 = 'forced'
222    ELSE
223       char1 = 'predefined'
224    ENDIF
225    IF ( threads_per_task == 1 )  THEN
226       WRITE ( io, 101 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
227    ELSE
228       WRITE ( io, 102 )  numprocs*threads_per_task, numprocs, &
229                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
230    ENDIF
231    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
232           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
233         npex == -1  .AND.  pdims(2) == 1 )                      &
234    THEN
235       WRITE ( io, 104 )
236    ELSEIF ( pdims(2) == 1 )  THEN
237       WRITE ( io, 105 )  'x'
238    ELSEIF ( pdims(1) == 1 )  THEN
239       WRITE ( io, 105 )  'y'
240    ENDIF
241    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 103 )
242#endif
243    WRITE ( io, 99 )
244
245!
246!-- Numerical schemes
247    WRITE ( io, 110 )
248    IF ( psolver(1:7) == 'poisfft' )  THEN
249       WRITE ( io, 111 )  TRIM( fft_method )
250       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
251    ELSEIF ( psolver == 'sor' )  THEN
252       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
253    ELSEIF ( psolver == 'multigrid' )  THEN
254       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
255       IF ( mg_cycles == -1 )  THEN
256          WRITE ( io, 140 )  residual_limit
257       ELSE
258          WRITE ( io, 141 )  mg_cycles
259       ENDIF
260       IF ( mg_switch_to_pe0_level == 0 )  THEN
261          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
262                             nzt_mg(1)
263       ELSE
264          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
265                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
266                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
267                             nzt_mg(mg_switch_to_pe0_level),    &
268                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
269                             nzt_mg(1)
270       ENDIF
271    ENDIF
272    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
273    THEN
274       WRITE ( io, 142 )
275    ENDIF
276
277    IF ( momentum_advec == 'pw-scheme' )  THEN
278       WRITE ( io, 113 )
279    ELSE
280       WRITE ( io, 114 )
281       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
282       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
283            overshoot_limit_w /= 0.0 )  THEN
284          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
285                             overshoot_limit_w
286       ENDIF
287       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
288            ups_limit_w /= 0.0 )                               &
289       THEN
290          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
291       ENDIF
292       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
293    ENDIF
294    IF ( scalar_advec == 'pw-scheme' )  THEN
295       WRITE ( io, 116 )
296    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
297       WRITE ( io, 117 )
298       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
299       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
300          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
301       ENDIF
302       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
303          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
304       ENDIF
305    ELSE
306       WRITE ( io, 118 )
307    ENDIF
308    IF ( momentum_advec /= 'ups-scheme' .AND. scalar_advec /= 'ups-scheme' &
309         .AND. scalar_advec /= 'bc-scheme'  .AND.  host(1:3) /= 'nec' )  THEN
310       WRITE ( io, 139 )
311    ENDIF
312    IF ( galilei_transformation )  THEN
313       IF ( use_ug_for_galilei_tr )  THEN
314          char1 = 'geostrophic wind'
315       ELSE
316          char1 = 'mean wind in model domain'
317       ENDIF
318       IF ( simulated_time_at_begin == simulated_time )  THEN
319          char2 = 'at the start of the run'
320       ELSE
321          char2 = 'at the end of the run'
322       ENDIF
323       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
324                          advected_distance_x/1000.0, advected_distance_y/1000.0
325    ENDIF
326    IF ( timestep_scheme == 'leapfrog' )  THEN
327       WRITE ( io, 120 )
328    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
329       WRITE ( io, 121 )
330    ELSE
331       WRITE ( io, 122 )  timestep_scheme
332    ENDIF
333    IF ( rayleigh_damping_factor /= 0.0 )  THEN
334       WRITE ( io, 123 )  rayleigh_damping_height, rayleigh_damping_factor
335    ENDIF
336    IF ( moisture )  THEN
337       IF ( .NOT. cloud_physics )  THEN
338          WRITE ( io, 129 )
339       ELSE
340          WRITE ( io, 130 )
341          WRITE ( io, 131 )
342          IF ( radiation )      WRITE ( io, 132 )
343          IF ( precipitation )  WRITE ( io, 133 )
344       ENDIF
345    ENDIF
346    IF ( passive_scalar )  WRITE ( io, 134 )
347    IF ( conserve_volume_flow )  WRITE ( io, 150 )
348    WRITE ( io, 99 )
349
350!
351!-- Runtime and timestep informations
352    WRITE ( io, 200 )
353    IF ( .NOT. dt_fixed )  THEN
354       WRITE ( io, 201 )  dt_max, cfl_factor
355    ELSE
356       WRITE ( io, 202 )  dt
357    ENDIF
358    WRITE ( io, 203 )  simulated_time_at_begin, end_time
359
360    IF ( time_restart /= 9999999.9  .AND. &
361         simulated_time_at_begin == simulated_time )  THEN
362       IF ( dt_restart == 9999999.9 )  THEN
363          WRITE ( io, 204 )  ' Restart at:       ',time_restart
364       ELSE
365          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
366       ENDIF
367    ENDIF
368
369    IF ( simulated_time_at_begin /= simulated_time )  THEN
370       i = MAX ( log_point_s(10)%counts, 1 )
371       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
372          cpuseconds_per_simulated_second = 0.0
373       ELSE
374          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
375                                            ( simulated_time -    &
376                                              simulated_time_at_begin )
377       ENDIF
378       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
379                          log_point_s(10)%sum / REAL( i ),     &
380                          cpuseconds_per_simulated_second
381       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
382          IF ( dt_restart == 9999999.9 )  THEN
383             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
384          ELSE
385             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
386          ENDIF
387       ENDIF
388    ENDIF
389
390!
391!-- Computational grid
392    WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
393    IF ( dz_stretch_level_index < nzt+1 )  THEN
394       WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
395                          dz_stretch_factor, dz_max
396    ENDIF
397    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
398                       MIN( nnz+2, nzt+2 )
399    IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
400       WRITE ( io, 255 )
401    ELSE
402       WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
403    ENDIF
404    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
405
406!
407!-- Topography
408    WRITE ( io, 270 )  topography
409    SELECT CASE ( TRIM( topography ) )
410
411       CASE ( 'flat' )
412          ! no actions necessary
413
414       CASE ( 'single_building' )
415          blx = INT( building_length_x / dx )
416          bly = INT( building_length_y / dy )
417          bh  = INT( building_height / dz )
418
419          IF ( building_wall_left == 9999999.9 )  THEN
420             building_wall_left = ( nx + 1 - blx ) / 2 * dx
421          ENDIF
422          bxl = INT ( building_wall_left / dx + 0.5 )
423          bxr = bxl + blx
424
425          IF ( building_wall_south == 9999999.9 )  THEN
426             building_wall_south = ( ny + 1 - bly ) / 2 * dy
427          ENDIF
428          bys = INT ( building_wall_south / dy + 0.5 )
429          byn = bys + bly
430
431          WRITE ( io, 271 )  building_length_x, building_length_y, &
432                             building_height, bxl, bxr, bys, byn
433
434    END SELECT
435
436!
437!-- Boundary conditions
438    IF ( ibc_p_b == 0 )  THEN
439       runten = 'p(0)     = 0      |'
440    ELSEIF ( ibc_p_b == 1 )  THEN
441       runten = 'p(0)     = p(1)   |'
442    ELSE
443       runten = 'p(0)     = p(1) +R|'
444    ENDIF
445    IF ( ibc_p_t == 0 )  THEN
446       roben  = 'p(nzt+1) = 0      |'
447    ELSE
448       roben  = 'p(nzt+1) = p(nzt) |'
449    ENDIF
450
451    IF ( ibc_uv_b == 0 )  THEN
452       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
453    ELSE
454       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
455    ENDIF
456    IF ( ibc_uv_t == 0 )  THEN
457       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
458    ELSE
459       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
460    ENDIF
461
462    IF ( ibc_pt_b == 0 )  THEN
463       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
464    ELSE
465       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
466    ENDIF
467    IF ( ibc_pt_t == 0 )  THEN
468       roben  = TRIM( roben  ) // ' pt(nzt) = pt_top'
469    ELSE
470       roben  = TRIM( roben  ) // ' pt(nzt) = pt(nzt-1) + dpt/dz'
471    ENDIF
472
473    WRITE ( io, 300 )  runten, roben
474
475    IF ( .NOT. constant_diffusion )  THEN
476       IF ( ibc_e_b == 1 )  THEN
477          runten = 'e(0)     = e(1)'
478       ELSE
479          runten = 'e(0)     = e(1) = (u*/0.1)**2'
480       ENDIF
481       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
482
483       WRITE ( io, 301 )  runten, roben       
484
485    ENDIF
486
487    IF ( moisture  .OR.  passive_scalar )  THEN
488       IF ( moisture )  THEN
489          IF ( ibc_q_b == 0 )  THEN
490             runten = 'q(0)     = q_surface'
491          ELSE
492             runten = 'q(0)     = q(1)'
493          ENDIF
494          IF ( ibc_q_t == 0 )  THEN
495             roben =  'q(nzt)   = q_top'
496          ELSE
497             roben =  'q(nzt)   = q(nzt-1) + dq/dz'
498          ENDIF
499       ELSE
500          IF ( ibc_q_b == 0 )  THEN
501             runten = 's(0)     = s_surface'
502          ELSE
503             runten = 's(0)     = s(1)'
504          ENDIF
505          IF ( ibc_q_t == 0 )  THEN
506             roben =  's(nzt)   = s_top'
507          ELSE
508             roben =  's(nzt)   = s(nzt-1) + ds/dz'
509          ENDIF
510       ENDIF
511
512       WRITE ( io, 302 ) runten, roben
513
514    ENDIF
515
516    IF ( use_surface_fluxes )  THEN
517       WRITE ( io, 303 )
518       IF ( constant_heatflux )  THEN
519          WRITE ( io, 306 )  surface_heatflux
520          IF ( random_heatflux )  WRITE ( io, 307 )
521       ENDIF
522       IF ( moisture  .AND.  constant_waterflux )  THEN
523          WRITE ( io, 311 ) surface_waterflux
524       ENDIF
525       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
526          WRITE ( io, 313 ) surface_waterflux
527       ENDIF
528    ENDIF
529
530    IF ( prandtl_layer )  THEN
531       WRITE ( io, 305 )  zu(1), roughness_length, kappa, rif_min, rif_max
532       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
533       IF ( moisture  .AND.  .NOT. constant_waterflux )  THEN
534          WRITE ( io, 312 )
535       ENDIF
536       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
537          WRITE ( io, 314 )
538       ENDIF
539    ELSE
540       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
541          WRITE ( io, 310 )  rif_min, rif_max
542       ENDIF
543    ENDIF
544
545    WRITE ( io, 317 )  bc_lr, bc_ns
546    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
547       WRITE ( io, 318 )  outflow_damping_width, km_damp_max
548    ENDIF
549
550!
551!-- Listing of 1D-profiles
552    WRITE ( io, 320 )  dt_dopr_listing
553    IF ( averaging_interval_pr /= 0.0 )  THEN
554       WRITE ( io, 321 )  averaging_interval_pr, dt_averaging_input_pr
555    ENDIF
556
557!
558!-- DATA output
559    WRITE ( io, 330 )
560    IF ( averaging_interval_pr /= 0.0 )  THEN
561       WRITE ( io, 321 )  averaging_interval_pr, dt_averaging_input_pr
562    ENDIF
563
564!
565!-- 1D-profiles
566    dopr_chr = 'Profile:'
567    IF ( dopr_n /= 0 )  THEN
568       WRITE ( io, 331 )
569
570       output_format = ''
571       IF ( netcdf_output )  THEN
572          IF ( netcdf_64bit )  THEN
573             output_format = 'netcdf (64 bit offset)'
574          ELSE
575             output_format = 'netcdf'
576          ENDIF
577       ENDIF
578       IF ( profil_output )  THEN
579          IF ( netcdf_output )  THEN
580             output_format = TRIM( output_format ) // ' and profil'
581          ELSE
582             output_format = 'profil'
583          ENDIF
584       ENDIF
585       WRITE ( io, 345 )  output_format
586
587       DO  i = 1, dopr_n
588          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
589          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
590             WRITE ( io, 332 )  dopr_chr
591             dopr_chr = '       :'
592          ENDIF
593       ENDDO
594
595       IF ( dopr_chr /= '' )  THEN
596          WRITE ( io, 332 )  dopr_chr
597       ENDIF
598       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
599       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
600    ENDIF
601
602!
603!-- 2D-arrays
604    DO  av = 0, 1
605
606       i = 1
607       do2d_xy = ''
608       do2d_xz = ''
609       do2d_yz = ''
610       DO  WHILE ( do2d(av,i) /= ' ' )
611
612          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
613          do2d_mode = do2d(av,i)(l-1:l)
614
615          SELECT CASE ( do2d_mode )
616             CASE ( 'xy' )
617                ll = LEN_TRIM( do2d_xy )
618                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
619             CASE ( 'xz' )
620                ll = LEN_TRIM( do2d_xz )
621                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
622             CASE ( 'yz' )
623                ll = LEN_TRIM( do2d_yz )
624                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
625          END SELECT
626
627          i = i + 1
628
629       ENDDO
630
631       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
632              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
633              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
634            ( netcdf_output  .OR.  iso2d_output ) )  THEN
635
636          IF (  av == 0 )  THEN
637             WRITE ( io, 334 )  ''
638          ELSE
639             WRITE ( io, 334 )  '(time-averaged)'
640          ENDIF
641
642          IF ( do2d_at_begin )  THEN
643             begin_chr = 'and at the start'
644          ELSE
645             begin_chr = ''
646          ENDIF
647
648          output_format = ''
649          IF ( netcdf_output )  THEN
650             IF ( netcdf_64bit )  THEN
651                output_format = 'netcdf (64 bit offset)'
652             ELSE
653                output_format = 'netcdf'
654             ENDIF
655          ENDIF
656          IF ( iso2d_output )  THEN
657             IF ( netcdf_output )  THEN
658                output_format = TRIM( output_format ) // ' and iso2d'
659             ELSE
660                output_format = 'iso2d'
661             ENDIF
662          ENDIF
663          WRITE ( io, 345 )  output_format
664
665          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
666             i = 1
667             slices = '/'
668             coordinates = '/'
669!
670!--          Building strings with index and coordinate informations of the
671!--          slices
672             DO  WHILE ( section(i,1) /= -9999 )
673
674                WRITE (section_chr,'(I5)')  section(i,1)
675                section_chr = ADJUSTL( section_chr )
676                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
677
678                WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
679                coor_chr = ADJUSTL( coor_chr )
680                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
681
682                i = i + 1
683             ENDDO
684             IF ( av == 0 )  THEN
685                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
686                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
687                                   TRIM( coordinates )
688                IF ( skip_time_do2d_xy /= 0.0 )  THEN
689                   WRITE ( io, 339 )  skip_time_do2d_xy
690                ENDIF
691             ELSE
692                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
693                                   TRIM( begin_chr ), averaging_interval, &
694                                   dt_averaging_input, 'k', TRIM( slices ), &
695                                   TRIM( coordinates )
696                IF ( skip_time_data_output_av /= 0.0 )  THEN
697                   WRITE ( io, 339 )  skip_time_data_output_av
698                ENDIF
699             ENDIF
700
701          ENDIF
702
703          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
704             i = 1
705             slices = '/'
706             coordinates = '/'
707!
708!--          Building strings with index and coordinate informations of the
709!--          slices
710             DO  WHILE ( section(i,2) /= -9999 )
711
712                WRITE (section_chr,'(I5)')  section(i,2)
713                section_chr = ADJUSTL( section_chr )
714                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
715
716                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
717                coor_chr = ADJUSTL( coor_chr )
718                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
719
720                i = i + 1
721             ENDDO
722             IF ( av == 0 )  THEN
723                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
724                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
725                                   TRIM( coordinates )
726                IF ( skip_time_do2d_xz /= 0.0 )  THEN
727                   WRITE ( io, 339 )  skip_time_do2d_xz
728                ENDIF
729             ELSE
730                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
731                                   TRIM( begin_chr ), averaging_interval, &
732                                   dt_averaging_input, 'j', TRIM( slices ), &
733                                   TRIM( coordinates )
734                IF ( skip_time_data_output_av /= 0.0 )  THEN
735                   WRITE ( io, 339 )  skip_time_data_output_av
736                ENDIF
737             ENDIF
738          ENDIF
739
740          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
741             i = 1
742             slices = '/'
743             coordinates = '/'
744!
745!--          Building strings with index and coordinate informations of the
746!--          slices
747             DO  WHILE ( section(i,3) /= -9999 )
748
749                WRITE (section_chr,'(I5)')  section(i,3)
750                section_chr = ADJUSTL( section_chr )
751                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
752
753                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
754                coor_chr = ADJUSTL( coor_chr )
755                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
756
757                i = i + 1
758             ENDDO
759             IF ( av == 0 )  THEN
760                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
761                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
762                                   TRIM( coordinates )
763                IF ( skip_time_do2d_yz /= 0.0 )  THEN
764                   WRITE ( io, 339 )  skip_time_do2d_yz
765                ENDIF
766             ELSE
767                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
768                                   TRIM( begin_chr ), averaging_interval, &
769                                   dt_averaging_input, 'i', TRIM( slices ), &
770                                   TRIM( coordinates )
771                IF ( skip_time_data_output_av /= 0.0 )  THEN
772                   WRITE ( io, 339 )  skip_time_data_output_av
773                ENDIF
774             ENDIF
775          ENDIF
776
777       ENDIF
778
779    ENDDO
780
781!
782!-- 3d-arrays
783    DO  av = 0, 1
784
785       i = 1
786       do3d_chr = ''
787       DO  WHILE ( do3d(av,i) /= ' ' )
788
789          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
790          i = i + 1
791
792       ENDDO
793
794       IF ( do3d_chr /= '' )  THEN
795          IF ( av == 0 )  THEN
796             WRITE ( io, 336 )  ''
797          ELSE
798             WRITE ( io, 336 )  '(time-averaged)'
799          ENDIF
800
801          output_format = ''
802          IF ( netcdf_output )  THEN
803             IF ( netcdf_64bit )  THEN
804                output_format = 'netcdf (64 bit offset)'
805             ELSE
806                output_format = 'netcdf'
807             ENDIF
808          ENDIF
809          IF ( avs_output )  THEN
810             IF ( netcdf_output )  THEN
811                output_format = TRIM( output_format ) // ' and avs'
812             ELSE
813                output_format = 'avs'
814             ENDIF
815          ENDIF
816          WRITE ( io, 345 )  output_format
817
818          IF ( do3d_at_begin )  THEN
819             begin_chr = 'and at the start'
820          ELSE
821             begin_chr = ''
822          ENDIF
823          IF ( av == 0 )  THEN
824             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
825                                zu(nz_do3d), nz_do3d
826          ELSE
827             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
828                                TRIM( begin_chr ), averaging_interval, &
829                                dt_averaging_input, zu(nz_do3d), nz_do3d
830          ENDIF
831
832          IF ( do3d_compress )  THEN
833             do3d_chr = ''
834             i = 1
835             DO WHILE ( do3d(av,i) /= ' ' )
836
837                SELECT CASE ( do3d(av,i) )
838                   CASE ( 'u' )
839                      j = 1
840                   CASE ( 'v' )
841                      j = 2
842                   CASE ( 'w' )
843                      j = 3
844                   CASE ( 'p' )
845                      j = 4
846                   CASE ( 'pt' )
847                      j = 5
848                END SELECT
849                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
850                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
851                           ':' // prec // ','
852                i = i + 1
853
854             ENDDO
855             WRITE ( io, 338 )  do3d_chr
856
857          ENDIF
858
859          IF ( av == 0 )  THEN
860             IF ( skip_time_do3d /= 0.0 )  THEN
861                WRITE ( io, 339 )  skip_time_do3d
862             ENDIF
863          ELSE
864             IF ( skip_time_data_output_av /= 0.0 )  THEN
865                WRITE ( io, 339 )  skip_time_data_output_av
866             ENDIF
867          ENDIF
868
869       ENDIF
870
871    ENDDO
872
873!
874!-- Timeseries
875    IF ( dt_dots /= 9999999.9 )  THEN
876       WRITE ( io, 340 )
877
878       output_format = ''
879       IF ( netcdf_output )  THEN
880          IF ( netcdf_64bit )  THEN
881             output_format = 'netcdf (64 bit offset)'
882          ELSE
883             output_format = 'netcdf'
884          ENDIF
885       ENDIF
886       IF ( profil_output )  THEN
887          IF ( netcdf_output )  THEN
888             output_format = TRIM( output_format ) // ' and profil'
889          ELSE
890             output_format = 'profil'
891          ENDIF
892       ENDIF
893       WRITE ( io, 345 )  output_format
894       WRITE ( io, 341 )  dt_dots
895    ENDIF
896
897#if defined( __dvrp_graphics )
898!
899!-- Dvrp-output
900    IF ( dt_dvrp /= 9999999.9 )  THEN
901       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
902                          TRIM( dvrp_username ), TRIM( dvrp_directory )
903       i = 1
904       l = 0
905       DO WHILE ( mode_dvrp(i) /= ' ' )
906          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
907             READ ( mode_dvrp(i), '(10X,I1)' )  j
908             l = l + 1
909             IF ( do3d(0,j) /= ' ' )  THEN
910                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l)
911             ENDIF
912          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
913             READ ( mode_dvrp(i), '(6X,I1)' )  j
914             IF ( do2d(0,j) /= ' ' )  WRITE ( io, 362 )  TRIM( do2d(0,j) )
915          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
916             WRITE ( io, 363 )
917          ENDIF
918          i = i + 1
919       ENDDO
920    ENDIF
921#endif
922
923#if defined( __spectra )
924!
925!-- Spectra output
926    IF ( dt_dosp /= 9999999.9 ) THEN
927       WRITE ( io, 370 )
928
929       output_format = ''
930       IF ( netcdf_output )  THEN
931          IF ( netcdf_64bit )  THEN
932             output_format = 'netcdf (64 bit offset)'
933          ELSE
934             output_format = 'netcdf'
935          ENDIF
936       ENDIF
937       IF ( profil_output )  THEN
938          IF ( netcdf_output )  THEN
939             output_format = TRIM( output_format ) // ' and profil'
940          ELSE
941             output_format = 'profil'
942          ENDIF
943       ENDIF
944       WRITE ( io, 345 )  output_format
945       WRITE ( io, 371 )  dt_dosp
946       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
947       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
948                          ( spectra_direction(i), i = 1,10 ),  &
949                          ( comp_spectra_level(i), i = 1,10 ), &
950                          ( plot_spectra_level(i), i = 1,10 ), &
951                          averaging_interval_sp, dt_averaging_input_pr
952    ENDIF
953#endif
954
955    WRITE ( io, 99 )
956
957!
958!-- Physical quantities
959    WRITE ( io, 400 )
960
961!
962!-- Geostrophic parameters
963    WRITE ( io, 410 )  omega, phi, f, fs
964
965!
966!-- Other quantities
967    WRITE ( io, 411 )  g
968
969!
970!-- Cloud physics parameters
971    IF ( cloud_physics ) THEN
972       WRITE ( io, 412 )
973       WRITE ( io, 413 ) surface_pressure, r_d, rho_surface, cp, l_v
974    ENDIF
975
976!-- Profile of the geostrophic wind (component ug)
977!-- Building output strings
978    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
979    gradients = '------'
980    slices = '     0'
981    coordinates = '   0.0'
982    i = 1
983    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
984     
985       WRITE (coor_chr,'(F6.2,4X)')  ug(ug_vertical_gradient_level_ind(i))
986       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
987
988       WRITE (coor_chr,'(F6.2,4X)')  ug_vertical_gradient(i)
989       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
990
991       WRITE (coor_chr,'(I6,4X)')  ug_vertical_gradient_level_ind(i)
992       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
993
994       WRITE (coor_chr,'(F6.1,4X)')  ug_vertical_gradient_level(i)
995       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
996
997       i = i + 1
998    ENDDO
999
1000    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1001                       TRIM( gradients ), TRIM( slices )
1002
1003!-- Profile of the geostrophic wind (component vg)
1004!-- Building output strings
1005    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1006    gradients = '------'
1007    slices = '     0'
1008    coordinates = '   0.0'
1009    i = 1
1010    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1011
1012       WRITE (coor_chr,'(F6.2,4X)')  vg(vg_vertical_gradient_level_ind(i))
1013       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1014
1015       WRITE (coor_chr,'(F6.2,4X)')  vg_vertical_gradient(i)
1016       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1017
1018       WRITE (coor_chr,'(I6,4X)')  vg_vertical_gradient_level_ind(i)
1019       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1020
1021       WRITE (coor_chr,'(F6.1,4X)')  vg_vertical_gradient_level(i)
1022       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1023
1024       i = i + 1 
1025    ENDDO
1026
1027    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1028                       TRIM( gradients ), TRIM( slices )
1029
1030!
1031!-- Initial temperature profile
1032!-- Building output strings, starting with surface temperature
1033    WRITE ( temperatures, '(F6.2)' )  pt_surface
1034    gradients = '------'
1035    slices = '     0'
1036    coordinates = '   0.0'
1037    i = 1
1038    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1039
1040       WRITE (coor_chr,'(F6.2,4X)')  pt_init(pt_vertical_gradient_level_ind(i))
1041       temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1042
1043       WRITE (coor_chr,'(F6.2,4X)')  pt_vertical_gradient(i)
1044       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1045
1046       WRITE (coor_chr,'(I6,4X)')  pt_vertical_gradient_level_ind(i)
1047       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1048
1049       WRITE (coor_chr,'(F6.1,4X)')  pt_vertical_gradient_level(i)
1050       coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1051
1052       i = i + 1
1053    ENDDO
1054
1055    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1056                       TRIM( gradients ), TRIM( slices )
1057
1058!
1059!-- Initial humidity profile
1060!-- Building output strings, starting with surface humidity
1061    IF ( moisture  .OR.  passive_scalar )  THEN
1062       WRITE ( temperatures, '(E8.1)' )  q_surface
1063       gradients = '--------'
1064       slices = '       0'
1065       coordinates = '     0.0'
1066       i = 1
1067       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1068         
1069          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1070          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1071
1072          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1073          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1074         
1075          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1076          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1077         
1078          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1079          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1080
1081          i = i + 1
1082       ENDDO
1083
1084       IF ( moisture )  THEN
1085          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1086                             TRIM( gradients ), TRIM( slices )
1087       ELSE
1088          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1089                             TRIM( gradients ), TRIM( slices )
1090       ENDIF
1091    ENDIF
1092
1093!
1094!-- LES / turbulence parameters
1095    WRITE ( io, 450 )
1096
1097!--
1098! ... LES-constants used must still be added here
1099!--
1100    IF ( constant_diffusion )  THEN
1101       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1102                          prandtl_number
1103    ENDIF
1104    IF ( .NOT. constant_diffusion)  THEN
1105       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1106       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1107       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1108    ENDIF
1109
1110!
1111!-- Special actions during the run
1112    WRITE ( io, 470 )
1113    IF ( create_disturbances )  THEN
1114       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1115                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1116                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1117       IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1118          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1119       ELSE
1120          WRITE ( io, 473 )  disturbance_energy_limit
1121       ENDIF
1122       WRITE ( io, 474 )  TRIM( random_generator )
1123    ENDIF
1124    IF ( pt_surface_initial_change /= 0.0 )  THEN
1125       WRITE ( io, 475 )  pt_surface_initial_change
1126    ENDIF
1127    IF ( moisture  .AND.  q_surface_initial_change /= 0.0 )  THEN
1128       WRITE ( io, 476 )  q_surface_initial_change       
1129    ENDIF
1130    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1131       WRITE ( io, 477 )  q_surface_initial_change       
1132    ENDIF
1133
1134#if defined( __particles )
1135!
1136!-- Particle attributes
1137    WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1138                       bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1139                       end_time_prel
1140    IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1141    IF ( random_start_position )  WRITE ( io, 481 )
1142    IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1143    WRITE ( io, 495 )  total_number_of_particles
1144    IF ( .NOT. vertical_particle_advection )  WRITE ( io, 482 )
1145    IF ( maximum_number_of_tailpoints /= 0 )  THEN
1146       WRITE ( io, 483 )  maximum_number_of_tailpoints
1147       IF ( minimum_tailpoint_distance /= 0 )  THEN
1148          WRITE ( io, 484 )  total_number_of_tails, minimum_tailpoint_distance,&
1149                             maximum_tailpoint_age
1150       ENDIF
1151    ENDIF
1152    IF ( dt_write_particle_data /= 9999999.9 )  THEN
1153       WRITE ( io, 485 )  dt_write_particle_data
1154       output_format = ''
1155       IF ( netcdf_output )  THEN
1156          IF ( netcdf_64bit )  THEN
1157             output_format = 'netcdf (64 bit offset) and binary'
1158          ELSE
1159             output_format = 'netcdf and binary'
1160          ENDIF
1161       ELSE
1162          output_format = 'binary'
1163       ENDIF
1164       WRITE ( io, 345 )  output_format
1165    ENDIF
1166    IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1167    IF ( write_particle_statistics )  WRITE ( io, 486 )
1168
1169    WRITE ( io, 487 )  number_of_particle_groups
1170
1171    DO  i = 1, number_of_particle_groups
1172       IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1173          WRITE ( io, 490 )  i, 0.0
1174          WRITE ( io, 492 )
1175       ELSE
1176          WRITE ( io, 490 )  i, radius(i)
1177          IF ( density_ratio(i) /= 0.0 )  THEN
1178             WRITE ( io, 491 )  density_ratio(i)
1179          ELSE
1180             WRITE ( io, 492 )
1181          ENDIF
1182       ENDIF
1183       WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1184                          pdx(i), pdy(i), pdz(i)
1185    ENDDO
1186
1187#endif
1188
1189!
1190!-- Parameters of 1D-model
1191    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1192       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1193                          mixing_length_1d, dissipation_1d
1194       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1195          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1196       ENDIF
1197    ENDIF
1198
1199!
1200!-- User-defined informations
1201    CALL user_header( io )
1202
1203    WRITE ( io, 99 )
1204
1205#if defined( __ibm )
1206!
1207!-- Write buffer contents to disc immediately
1208    CALL FLUSH_( io )
1209#elif defined( __lcmuk )  ||  defined( __nec )
1210    CALL FLUSH( io )
1211#endif
1212
1213!
1214!-- Here the FORMATs start
1215
1216 99 FORMAT (1X,78('-'))
1217100 FORMAT (/10X,'****************',11X,28('-')/                &
1218            10X,'*  ',A12,'*',11X,A/                            &
1219            10X,'****************',11X,28('-')//                &
1220            ' Date:            ',A8,11X,'Run:       ',A20/      &
1221            ' Time:            ',A8,11X,'Run-No.:   ',I2.2/     &
1222            ' Run on host:   ',A10)
1223#if defined( __parallel )
1224101 FORMAT (' Number of PEs:',7X,I4,11X,'Processor grid (x,y): (',I3,',',I3, &
1225              ')',1X,A)
1226102 FORMAT (' Number of PEs:',7X,I4,11X,'Tasks:',I4,'   threads per task:',I4/ &
1227              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1228103 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1229104 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1230            37X,'because the job is running on an SMP-cluster')
1231105 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1232#endif
1233110 FORMAT (/' Numerical Schemes:'/ &
1234             ' -----------------'/)
1235111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1236112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1237            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1238113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1239                  ' or Upstream')
1240114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1241115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1242116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1243                  ' or Upstream')
1244117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1245118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1246119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1247            '     Translation velocity = ',A/ &
1248            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1249120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1250                  ' of timestep changes)')
1251121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1252                  ' timestep changes')
1253122 FORMAT (' --> Time differencing scheme: ',A)
1254123 FORMAT (' --> Rayleigh-Damping active, starts above z = ',F8.2,' m'/ &
1255            '     maximum damping coefficient: ',F5.3, ' 1/s')
1256124 FORMAT ('     Spline-overshoots are being suppressed')
1257125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1258                  ' of'/                                                       &
1259            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1260126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1261                  ' of'/                                                       &
1262            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1263127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1264            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1265128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1266            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1267129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1268130 FORMAT (' --> Additional prognostic equation for the total water content')
1269131 FORMAT (' --> Parameterization of condensation processes via (0%-or100%)')
1270132 FORMAT (' --> Parameterization of long-wave radiation processes via'/ &
1271            '     effective emissivity scheme')
1272133 FORMAT (' --> Precipitation parameterization via Kessler-Scheme')
1273134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1274135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1275                  A,'-cycle)'/ &
1276            '     number of grid levels:                   ',I2/ &
1277            '     Gauss-Seidel red/black iterations:       ',I2)
1278136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1279                  I3,')')
1280137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1281            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1282                  I3,')'/ &
1283            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1284                  I3,')')
1285138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1286139 FORMAT (' --> Prognostic equations are solved in one single loop (fast', &
1287                  ' method)')
1288140 FORMAT ('     maximum residual allowed:                ',E10.3)
1289141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1290142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1291                  'step')
1292150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1293                  'conserved')
1294200 FORMAT (//' Run time and time step information:'/ &
1295             ' ----------------------------------'/)
1296201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1297             '    CFL-factor: ',F4.2)
1298202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1299203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1300             ' End time:         ',F9.3,' s')
1301204 FORMAT ( A,F9.3,' s')
1302205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1303206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1304             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1305               '  ',F9.3,' s'/                                                 &
1306             '                                   per second of simulated tim', &
1307               'e: ',F9.3,' s')
1308250 FORMAT (//' Computational grid and domain size:'/ &
1309              ' ----------------------------------'// &
1310              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1311              ' m    dz =    ',F7.3,' m'/ &
1312              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1313              ' m  z(u) = ',F10.3,' m'/)
1314252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1315              ' factor: ',F5.3/ &
1316            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1317254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1318            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1319255 FORMAT (' Subdomains have equal size')
1320256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1321              'have smaller sizes'/                                          &
1322            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1323260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1324             ' degrees')
1325270 FORMAT (//' Topography informations:'/ &
1326              ' -----------------------'// &
1327              1X,'Topography: ',A)
1328271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1329              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1330                ' / ',I4)
1331300 FORMAT (//' Boundary conditions:'/ &
1332             ' -------------------'// &
1333             '                     p                    uv             ', &
1334             '                   pt'// &
1335             ' B. bound.: ',A/ &
1336             ' T. bound.: ',A)
1337301 FORMAT (/'                     e'// &
1338             ' B. bound.: ',A/ &
1339             ' T. bound.: ',A)
1340302 FORMAT (/'                     q'// &
1341             ' B. bound.: ',A/ &
1342             ' T. bound.: ',A)
1343303 FORMAT (/' Surface fluxes are used in diffusion terms at k=1')
1344305 FORMAT (//'    Prandtl-Layer between surface and first computational ', &
1345               'u,v-level:'// &
1346             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1347             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1348306 FORMAT ('       Predefined constant heatflux:   ',F6.3,' K m/s')
1349307 FORMAT ('       Heatflux has a random normal distribution')
1350308 FORMAT ('       Predefined surface temperature')
1351310 FORMAT (//'    1D-Model:'// &
1352             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1353311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1354312 FORMAT ('       Predefined surface humidity')
1355313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1356314 FORMAT ('       Predefined scalar value at the surface')
1357317 FORMAT (//' Lateral boundaries:'/ &
1358            '       left/right:  ',A/    &
1359            '       north/south: ',A)
1360318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1361                    'max =',F5.1,' m**2/s')
1362320 FORMAT (//' List output:'/ &
1363             ' -----------'//  &
1364            '    1D-Profiles:'/    &
1365            '       Output every             ',F8.2,' s')
1366321 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1367            '       Averaging input every    ',F8.2,' s')
1368330 FORMAT (//' Data output:'/ &
1369             ' -----------'/)
1370331 FORMAT (/'    1D-Profiles:')
1371332 FORMAT (/'       ',A)
1372333 FORMAT ('       Output every             ',F8.2,' s',/ &
1373            '       Time averaged over       ',F8.2,' s'/ &
1374            '       Averaging input every    ',F8.2,' s')
1375334 FORMAT (/'    2D-Arrays',A,':')
1376335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1377            '       Output every             ',F8.2,' s  ',A/ &
1378            '       Cross sections at ',A1,' = ',A/ &
1379            '       scalar-coordinates:   ',A,' m'/)
1380336 FORMAT (/'    3D-Arrays',A,':')
1381337 FORMAT (/'       Arrays: ',A/ &
1382            '       Output every             ',F8.2,' s  ',A/ &
1383            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1384338 FORMAT ('       Compressed data output'/ &
1385            '       Decimal precision: ',A/)
1386339 FORMAT ('       No output during initial ',F8.2,' s')
1387340 FORMAT (/'    Time series:')
1388341 FORMAT ('       Output every             ',F8.2,' s'/)
1389342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1390            '       Output every             ',F8.2,' s  ',A/ &
1391            '       Time averaged over       ',F8.2,' s'/ &
1392            '       Averaging input every    ',F8.2,' s'/ &
1393            '       Cross sections at ',A1,' = ',A/ &
1394            '       scalar-coordinates:   ',A,' m'/)
1395343 FORMAT (/'       Arrays: ',A/ &
1396            '       Output every             ',F8.2,' s  ',A/ &
1397            '       Time averaged over       ',F8.2,' s'/ &
1398            '       Averaging input every    ',F8.2,' s'/ &
1399            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1400345 FORMAT ('       Output format: ',A/)
1401#if defined( __dvrp_graphics )
1402360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1403            '       Output every      ',F7.1,' s'/ &
1404            '       Output mode:      ',A/ &
1405            '       Host / User:      ',A,' / ',A/ &
1406            '       Directory:        ',A// &
1407            '       The sequence contains:')
1408361 FORMAT ('       Isosurface of ',A,'  Threshold value: ', E12.3)
1409362 FORMAT ('       Sectional plane ',A)
1410363 FORMAT ('       Particles')
1411#endif
1412#if defined( __spectra )
1413370 FORMAT ('    Spectra:')
1414371 FORMAT ('       Output every ',F7.1,' s'/)
1415372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1416            '       Directions: ', 10(A5,',')/                         &
1417            '       height levels  k = ', 9(I3,','),I3,'.'/            &
1418            '       height levels selected for standard plot:'/        &
1419            '                      k = ', 9(I3,','),I3,'.'/            &
1420            '       Time averaged over ', F7.1, ' s,' /                &
1421            '       Profiles for the time averaging are taken every ', &
1422                    F6.1,' s')
1423#endif
1424400 FORMAT (//' Physical quantities:'/ &
1425              ' -------------------'/)
1426410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1427            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1428            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1429            '                            f*    = ',F9.6,' 1/s')
1430411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1431412 FORMAT (/'    Cloud physics parameters:'/ &
1432             '    ------------------------'/)
1433413 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1434            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1435            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1436            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1437            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1438420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1439            '       Height:        ',A,'  m'/ &
1440            '       Temperature:   ',A,'  K'/ &
1441            '       Gradient:      ',A,'  K/100m'/ &
1442            '       Gridpoint:     ',A)
1443421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1444            '       Height:      ',A,'  m'/ &
1445            '       Humidity:    ',A,'  kg/kg'/ &
1446            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1447            '       Gridpoint:   ',A)
1448422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1449            '       Height:                  ',A,'  m'/ &
1450            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1451            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1452            '       Gridpoint:               ',A)
1453423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1454            '       Height:      ',A,'  m'/ &
1455            '       ug:          ',A,'  m/s'/ &
1456            '       Gradient:    ',A,'  1/100s'/ &
1457            '       Gridpoint:   ',A)
1458424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1459            '       Height:      ',A,'  m'/ &
1460            '       vg:          ',A,'  m/S'/ &
1461            '       Gradient:    ',A,'  1/100s'/ &
1462            '       Gridpoint:   ',A)
1463450 FORMAT (//' LES / Turbulence quantities:'/ &
1464              ' ---------------------------'/)
1465451 FORMAT ('   Diffusion coefficients are constant:'/ &
1466            '   Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1467452 FORMAT ('   Mixing length is limited to the Prandtl mixing lenth.')
1468453 FORMAT ('   Mixing length is limited to ',F4.2,' * z')
1469454 FORMAT ('   TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1470470 FORMAT (//' Actions during the simulation:'/ &
1471              ' -----------------------------'/)
1472471 FORMAT ('    Disturbance impulse (u,v) every :  ',F6.2,' s'/             &
1473            '    Disturbance amplitude           :    ',F4.2, ' m/s'/        &
1474            '    Lower disturbance level         : ',F7.2,' m (GP ',I4,')'/  &
1475            '    Upper disturbance level         : ',F7.2,' m (GP ',I4,')')
1476472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1477                 ' to i/j =',I4)
1478473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1479                 1X,F5.3, ' m**2/s**2')
1480474 FORMAT ('    Random number generator used    : ',A/)
1481475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1482                 'respectively, if'/ &
1483            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1484                 ' 3D-simulation'/)
1485476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1486                 'respectively, if the'/ &
1487            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1488                 ' the 3D-simulation'/)
1489477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1490                 'respectively, if the'/ &
1491            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1492                 ' the 3D-simulation'/)
1493#if defined( __particles )
1494480 FORMAT ('    Particles:'/ &
1495            '    ---------'// &
1496            '       Particle advection is active (switched on at t = ', F7.1, &
1497                    ' s)'/ &
1498            '       Start of new particle generations every  ',F6.1,' s'/ &
1499            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
1500            '                            bottom:     ', A, ' top:         ', A/&
1501            '       Maximum particle age:                 ',F9.1,' s'/ &
1502            '       Advection stopped at t = ',F9.1,' s'/)
1503481 FORMAT ('       Particles have random start positions'/)
1504482 FORMAT ('       Particles are advected only horizontally'/)
1505483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
1506484 FORMAT ('            Number of tails of the total domain: ',I10/ &
1507            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
1508            '            Maximum age of the end of the tail:  ',F8.2,' s')
1509485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
1510486 FORMAT ('       Particle statistics are written on file'/)
1511487 FORMAT ('       Number of particle groups: ',I2/)
1512488 FORMAT ('       SGS velocity components are used for particle advection'/ &
1513            '          minimum timestep for advection: ', F7.5/)
1514489 FORMAT ('       Number of particles simultaneously released at each ', &
1515                    'point: ', I5/)
1516490 FORMAT ('       Particle group ',I2,':'/ &
1517            '          Particle radius: ',E10.3, 'm')
1518491 FORMAT ('          Particle inertia is activated'/ &
1519            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
1520492 FORMAT ('          Particles are advected only passively (no inertia)'/)
1521493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
1522            '                                         y:',F8.1,' - ',F8.1,' m'/&
1523            '                                         z:',F8.1,' - ',F8.1,' m'/&
1524            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
1525                       ' m  dz = ',F8.1,' m'/)
1526494 FORMAT ('       Output of particle time series in NetCDF format every ', &
1527                    F8.2,' s'/)
1528495 FORMAT ('       Number of particles in total domain: ',I10/)
1529#endif
1530500 FORMAT (//' 1D-Model parameters:'/                           &
1531              ' -------------------'//                           &
1532            '    Simulation time:                   ',F8.1,' s'/ &
1533            '    Run-controll output every:         ',F8.1,' s'/ &
1534            '    Vertical profile output every:     ',F8.1,' s'/ &
1535            '    Mixing length calculation:         ',A/         &
1536            '    Dissipation calculation:           ',A/)
1537502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
1538
1539
1540 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.