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

Last change on this file since 1017 was 1017, checked in by raasch, 12 years ago

last commit documented

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