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

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

old profil-parameters (cross_xtext, cross_normalized_x, etc. ) and respective code removed
(check_open, check_parameters, close_file, data_output_profiles, data_output_spectra, header, modules, parin)

reformatting (netcdf)

append feature removed from unit 14 (check_open)

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