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

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

last commit documented

  • Property svn:keywords set to Id
File size: 80.1 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: header.f90 941 2012-07-09 14:50:21Z hoffmann $
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       IF ( profil_output )  THEN
756          IF ( netcdf_output )  THEN
757             output_format = TRIM( output_format ) // ' and profil'
758          ELSE
759             output_format = 'profil'
760          ENDIF
761       ENDIF
762       WRITE ( io, 344 )  output_format
763
764       DO  i = 1, dopr_n
765          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
766          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
767             WRITE ( io, 332 )  dopr_chr
768             dopr_chr = '       :'
769          ENDIF
770       ENDDO
771
772       IF ( dopr_chr /= '' )  THEN
773          WRITE ( io, 332 )  dopr_chr
774       ENDIF
775       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
776       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
777    ENDIF
778
779!
780!-- 2D-arrays
781    DO  av = 0, 1
782
783       i = 1
784       do2d_xy = ''
785       do2d_xz = ''
786       do2d_yz = ''
787       DO  WHILE ( do2d(av,i) /= ' ' )
788
789          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
790          do2d_mode = do2d(av,i)(l-1:l)
791
792          SELECT CASE ( do2d_mode )
793             CASE ( 'xy' )
794                ll = LEN_TRIM( do2d_xy )
795                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
796             CASE ( 'xz' )
797                ll = LEN_TRIM( do2d_xz )
798                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
799             CASE ( 'yz' )
800                ll = LEN_TRIM( do2d_yz )
801                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
802          END SELECT
803
804          i = i + 1
805
806       ENDDO
807
808       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
809              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
810              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
811            ( netcdf_output  .OR.  iso2d_output ) )  THEN
812
813          IF (  av == 0 )  THEN
814             WRITE ( io, 334 )  ''
815          ELSE
816             WRITE ( io, 334 )  '(time-averaged)'
817          ENDIF
818
819          IF ( do2d_at_begin )  THEN
820             begin_chr = 'and at the start'
821          ELSE
822             begin_chr = ''
823          ENDIF
824
825          output_format = ''
826          IF ( netcdf_output )  THEN
827             IF ( netcdf_data_format == 1 )  THEN
828                output_format = 'NetCDF classic'
829             ELSEIF ( netcdf_data_format == 2 )  THEN
830                output_format = 'NetCDF 64bit offset'
831             ELSEIF ( netcdf_data_format == 3 )  THEN
832                output_format = 'NetCDF4/HDF5'
833             ELSEIF ( netcdf_data_format == 4 )  THEN
834                output_format = 'NetCDF4/HDF5 clasic'
835             ENDIF
836          ENDIF
837          IF ( iso2d_output )  THEN
838             IF ( netcdf_output )  THEN
839                output_format = TRIM( output_format ) // ' and iso2d'
840             ELSE
841                output_format = 'iso2d'
842             ENDIF
843          ENDIF
844          WRITE ( io, 344 )  output_format
845
846          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
847             i = 1
848             slices = '/'
849             coordinates = '/'
850!
851!--          Building strings with index and coordinate informations of the
852!--          slices
853             DO  WHILE ( section(i,1) /= -9999 )
854
855                WRITE (section_chr,'(I5)')  section(i,1)
856                section_chr = ADJUSTL( section_chr )
857                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
858
859                IF ( section(i,1) == -1 )  THEN
860                   WRITE (coor_chr,'(F10.1)')  -1.0
861                ELSE
862                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
863                ENDIF
864                coor_chr = ADJUSTL( coor_chr )
865                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
866
867                i = i + 1
868             ENDDO
869             IF ( av == 0 )  THEN
870                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
871                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
872                                   TRIM( coordinates )
873                IF ( skip_time_do2d_xy /= 0.0 )  THEN
874                   WRITE ( io, 339 )  skip_time_do2d_xy
875                ENDIF
876             ELSE
877                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
878                                   TRIM( begin_chr ), averaging_interval, &
879                                   dt_averaging_input, 'k', TRIM( slices ), &
880                                   TRIM( coordinates )
881                IF ( skip_time_data_output_av /= 0.0 )  THEN
882                   WRITE ( io, 339 )  skip_time_data_output_av
883                ENDIF
884             ENDIF
885
886          ENDIF
887
888          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
889             i = 1
890             slices = '/'
891             coordinates = '/'
892!
893!--          Building strings with index and coordinate informations of the
894!--          slices
895             DO  WHILE ( section(i,2) /= -9999 )
896
897                WRITE (section_chr,'(I5)')  section(i,2)
898                section_chr = ADJUSTL( section_chr )
899                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
900
901                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
902                coor_chr = ADJUSTL( coor_chr )
903                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
904
905                i = i + 1
906             ENDDO
907             IF ( av == 0 )  THEN
908                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
909                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
910                                   TRIM( coordinates )
911                IF ( skip_time_do2d_xz /= 0.0 )  THEN
912                   WRITE ( io, 339 )  skip_time_do2d_xz
913                ENDIF
914             ELSE
915                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
916                                   TRIM( begin_chr ), averaging_interval, &
917                                   dt_averaging_input, 'j', TRIM( slices ), &
918                                   TRIM( coordinates )
919                IF ( skip_time_data_output_av /= 0.0 )  THEN
920                   WRITE ( io, 339 )  skip_time_data_output_av
921                ENDIF
922             ENDIF
923          ENDIF
924
925          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
926             i = 1
927             slices = '/'
928             coordinates = '/'
929!
930!--          Building strings with index and coordinate informations of the
931!--          slices
932             DO  WHILE ( section(i,3) /= -9999 )
933
934                WRITE (section_chr,'(I5)')  section(i,3)
935                section_chr = ADJUSTL( section_chr )
936                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
937
938                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
939                coor_chr = ADJUSTL( coor_chr )
940                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
941
942                i = i + 1
943             ENDDO
944             IF ( av == 0 )  THEN
945                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
946                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
947                                   TRIM( coordinates )
948                IF ( skip_time_do2d_yz /= 0.0 )  THEN
949                   WRITE ( io, 339 )  skip_time_do2d_yz
950                ENDIF
951             ELSE
952                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
953                                   TRIM( begin_chr ), averaging_interval, &
954                                   dt_averaging_input, 'i', TRIM( slices ), &
955                                   TRIM( coordinates )
956                IF ( skip_time_data_output_av /= 0.0 )  THEN
957                   WRITE ( io, 339 )  skip_time_data_output_av
958                ENDIF
959             ENDIF
960          ENDIF
961
962       ENDIF
963
964    ENDDO
965
966!
967!-- 3d-arrays
968    DO  av = 0, 1
969
970       i = 1
971       do3d_chr = ''
972       DO  WHILE ( do3d(av,i) /= ' ' )
973
974          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
975          i = i + 1
976
977       ENDDO
978
979       IF ( do3d_chr /= '' )  THEN
980          IF ( av == 0 )  THEN
981             WRITE ( io, 336 )  ''
982          ELSE
983             WRITE ( io, 336 )  '(time-averaged)'
984          ENDIF
985
986          output_format = ''
987          IF ( netcdf_output )  THEN
988             IF ( netcdf_data_format == 1 )  THEN
989                output_format = 'NetCDF classic'
990             ELSEIF ( netcdf_data_format == 2 )  THEN
991                output_format = 'NetCDF 64bit offset'
992             ELSEIF ( netcdf_data_format == 3 )  THEN
993                output_format = 'NetCDF4/HDF5'
994             ELSEIF ( netcdf_data_format == 4 )  THEN
995                output_format = 'NetCDF4/HDF5 clasic'
996             ENDIF
997          ENDIF
998          IF ( avs_output )  THEN
999             IF ( netcdf_output )  THEN
1000                output_format = TRIM( output_format ) // ' and avs'
1001             ELSE
1002                output_format = 'avs'
1003             ENDIF
1004          ENDIF
1005          WRITE ( io, 344 )  output_format
1006
1007          IF ( do3d_at_begin )  THEN
1008             begin_chr = 'and at the start'
1009          ELSE
1010             begin_chr = ''
1011          ENDIF
1012          IF ( av == 0 )  THEN
1013             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1014                                zu(nz_do3d), nz_do3d
1015          ELSE
1016             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1017                                TRIM( begin_chr ), averaging_interval, &
1018                                dt_averaging_input, zu(nz_do3d), nz_do3d
1019          ENDIF
1020
1021          IF ( do3d_compress )  THEN
1022             do3d_chr = ''
1023             i = 1
1024             DO WHILE ( do3d(av,i) /= ' ' )
1025
1026                SELECT CASE ( do3d(av,i) )
1027                   CASE ( 'u' )
1028                      j = 1
1029                   CASE ( 'v' )
1030                      j = 2
1031                   CASE ( 'w' )
1032                      j = 3
1033                   CASE ( 'p' )
1034                      j = 4
1035                   CASE ( 'pt' )
1036                      j = 5
1037                END SELECT
1038                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1039                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1040                           ':' // prec // ','
1041                i = i + 1
1042
1043             ENDDO
1044             WRITE ( io, 338 )  do3d_chr
1045
1046          ENDIF
1047
1048          IF ( av == 0 )  THEN
1049             IF ( skip_time_do3d /= 0.0 )  THEN
1050                WRITE ( io, 339 )  skip_time_do3d
1051             ENDIF
1052          ELSE
1053             IF ( skip_time_data_output_av /= 0.0 )  THEN
1054                WRITE ( io, 339 )  skip_time_data_output_av
1055             ENDIF
1056          ENDIF
1057
1058       ENDIF
1059
1060    ENDDO
1061
1062!
1063!-- masked arrays
1064    IF ( masks > 0 )  WRITE ( io, 345 )  &
1065         mask_scale_x, mask_scale_y, mask_scale_z
1066    DO  mid = 1, masks
1067       DO  av = 0, 1
1068
1069          i = 1
1070          domask_chr = ''
1071          DO  WHILE ( domask(mid,av,i) /= ' ' )
1072             domask_chr = TRIM( domask_chr ) // ' ' //  &
1073                          TRIM( domask(mid,av,i) ) // ','
1074             i = i + 1
1075          ENDDO
1076
1077          IF ( domask_chr /= '' )  THEN
1078             IF ( av == 0 )  THEN
1079                WRITE ( io, 346 )  '', mid
1080             ELSE
1081                WRITE ( io, 346 )  ' (time-averaged)', mid
1082             ENDIF
1083
1084             output_format = ''
1085             IF ( netcdf_output )  THEN
1086                IF ( netcdf_data_format == 1 )  THEN
1087                   output_format = 'NetCDF classic'
1088                ELSEIF ( netcdf_data_format == 2 )  THEN
1089                   output_format = 'NetCDF 64bit offset'
1090                ELSEIF ( netcdf_data_format == 3 )  THEN
1091                   output_format = 'NetCDF4/HDF5'
1092                ELSEIF ( netcdf_data_format == 4 )  THEN
1093                   output_format = 'NetCDF4/HDF5 clasic'
1094                ENDIF
1095             ENDIF
1096             WRITE ( io, 344 )  output_format
1097
1098             IF ( av == 0 )  THEN
1099                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1100             ELSE
1101                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1102                                   averaging_interval, dt_averaging_input
1103             ENDIF
1104
1105             IF ( av == 0 )  THEN
1106                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1107                   WRITE ( io, 339 )  skip_time_domask(mid)
1108                ENDIF
1109             ELSE
1110                IF ( skip_time_data_output_av /= 0.0 )  THEN
1111                   WRITE ( io, 339 )  skip_time_data_output_av
1112                ENDIF
1113             ENDIF
1114!
1115!--          output locations
1116             DO  dim = 1, 3
1117                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1118                   count = 0
1119                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1120                      count = count + 1
1121                   ENDDO
1122                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1123                                      mask(mid,dim,:count)
1124                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1125                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1126                         mask_loop(mid,dim,3) == 0.0 )  THEN
1127                   WRITE ( io, 350 )  dir(dim), dir(dim)
1128                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1129                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1130                                      mask_loop(mid,dim,1:2)
1131                ELSE
1132                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1133                                      mask_loop(mid,dim,1:3)
1134                ENDIF
1135             ENDDO
1136          ENDIF
1137
1138       ENDDO
1139    ENDDO
1140
1141!
1142!-- Timeseries
1143    IF ( dt_dots /= 9999999.9 )  THEN
1144       WRITE ( io, 340 )
1145
1146       output_format = ''
1147       IF ( netcdf_output )  THEN
1148          IF ( netcdf_data_format == 1 )  THEN
1149             output_format = 'NetCDF classic'
1150          ELSE
1151             output_format = 'NetCDF 64bit offset'
1152          ENDIF
1153       ENDIF
1154       IF ( profil_output )  THEN
1155          IF ( netcdf_output )  THEN
1156             output_format = TRIM( output_format ) // ' and profil'
1157          ELSE
1158             output_format = 'profil'
1159          ENDIF
1160       ENDIF
1161       WRITE ( io, 344 )  output_format
1162       WRITE ( io, 341 )  dt_dots
1163    ENDIF
1164
1165#if defined( __dvrp_graphics )
1166!
1167!-- Dvrp-output
1168    IF ( dt_dvrp /= 9999999.9 )  THEN
1169       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1170                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1171       i = 1
1172       l = 0
1173       m = 0
1174       DO WHILE ( mode_dvrp(i) /= ' ' )
1175          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1176             READ ( mode_dvrp(i), '(10X,I2)' )  j
1177             l = l + 1
1178             IF ( do3d(0,j) /= ' ' )  THEN
1179                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1180                                   isosurface_color(:,l)
1181             ENDIF
1182          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1183             READ ( mode_dvrp(i), '(6X,I2)' )  j
1184             m = m + 1
1185             IF ( do2d(0,j) /= ' ' )  THEN
1186                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1187                                   slicer_range_limits_dvrp(:,m)
1188             ENDIF
1189          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1190             WRITE ( io, 363 )  dvrp_psize
1191             IF ( particle_dvrpsize /= 'none' )  THEN
1192                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1193                                   dvrpsize_interval
1194             ENDIF
1195             IF ( particle_color /= 'none' )  THEN
1196                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1197                                   color_interval
1198             ENDIF
1199          ENDIF
1200          i = i + 1
1201       ENDDO
1202
1203       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1204                          superelevation_y, superelevation, clip_dvrp_l, &
1205                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1206
1207       IF ( TRIM( topography ) /= 'flat' )  THEN
1208          WRITE ( io, 366 )  topography_color
1209          IF ( cluster_size > 1 )  THEN
1210             WRITE ( io, 367 )  cluster_size
1211          ENDIF
1212       ENDIF
1213
1214    ENDIF
1215#endif
1216
1217#if defined( __spectra )
1218!
1219!-- Spectra output
1220    IF ( dt_dosp /= 9999999.9 ) THEN
1221       WRITE ( io, 370 )
1222
1223       output_format = ''
1224       IF ( netcdf_output )  THEN
1225          IF ( netcdf_data_format == 1 )  THEN
1226             output_format = 'NetCDF classic'
1227          ELSE
1228             output_format = 'NetCDF 64bit offset'
1229          ENDIF
1230       ENDIF
1231       IF ( profil_output )  THEN
1232          IF ( netcdf_output )  THEN
1233             output_format = TRIM( output_format ) // ' and profil'
1234          ELSE
1235             output_format = 'profil'
1236          ENDIF
1237       ENDIF
1238       WRITE ( io, 344 )  output_format
1239       WRITE ( io, 371 )  dt_dosp
1240       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1241       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1242                          ( spectra_direction(i), i = 1,10 ),  &
1243                          ( comp_spectra_level(i), i = 1,100 ), &
1244                          ( plot_spectra_level(i), i = 1,100 ), &
1245                          averaging_interval_sp, dt_averaging_input_pr
1246    ENDIF
1247#endif
1248
1249    WRITE ( io, 99 )
1250
1251!
1252!-- Physical quantities
1253    WRITE ( io, 400 )
1254
1255!
1256!-- Geostrophic parameters
1257    WRITE ( io, 410 )  omega, phi, f, fs
1258
1259!
1260!-- Other quantities
1261    WRITE ( io, 411 )  g
1262    IF ( use_reference )  THEN
1263       IF ( ocean )  THEN
1264          WRITE ( io, 412 )  prho_reference
1265       ELSE
1266          WRITE ( io, 413 )  pt_reference
1267       ENDIF
1268    ENDIF
1269
1270!
1271!-- Cloud physics parameters
1272    IF ( cloud_physics ) THEN
1273       WRITE ( io, 415 )
1274       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1275    ENDIF
1276
1277!-- Profile of the geostrophic wind (component ug)
1278!-- Building output strings
1279    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1280    gradients = '------'
1281    slices = '     0'
1282    coordinates = '   0.0'
1283    i = 1
1284    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1285     
1286       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1287       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1288
1289       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1290       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1291
1292       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1293       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1294
1295       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1296       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1297
1298       IF ( i == 10 )  THEN
1299          EXIT
1300       ELSE
1301          i = i + 1
1302       ENDIF
1303
1304    ENDDO
1305
1306    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1307                       TRIM( gradients ), TRIM( slices )
1308
1309!-- Profile of the geostrophic wind (component vg)
1310!-- Building output strings
1311    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1312    gradients = '------'
1313    slices = '     0'
1314    coordinates = '   0.0'
1315    i = 1
1316    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1317
1318       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1319       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1320
1321       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1322       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1323
1324       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1325       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1326
1327       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1328       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1329
1330       IF ( i == 10 )  THEN
1331          EXIT
1332       ELSE
1333          i = i + 1
1334       ENDIF
1335 
1336    ENDDO
1337
1338    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1339                       TRIM( gradients ), TRIM( slices )
1340
1341!
1342!-- Initial wind profiles
1343    IF ( u_profile(1) /= 9999999.9 )  WRITE ( io, 427 )
1344
1345!
1346!-- Initial temperature profile
1347!-- Building output strings, starting with surface temperature
1348    WRITE ( temperatures, '(F6.2)' )  pt_surface
1349    gradients = '------'
1350    slices = '     0'
1351    coordinates = '   0.0'
1352    i = 1
1353    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1354
1355       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1356       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1357
1358       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1359       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1360
1361       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1362       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1363
1364       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1365       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1366
1367       IF ( i == 10 )  THEN
1368          EXIT
1369       ELSE
1370          i = i + 1
1371       ENDIF
1372
1373    ENDDO
1374
1375    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1376                       TRIM( gradients ), TRIM( slices )
1377
1378!
1379!-- Initial humidity profile
1380!-- Building output strings, starting with surface humidity
1381    IF ( humidity  .OR.  passive_scalar )  THEN
1382       WRITE ( temperatures, '(E8.1)' )  q_surface
1383       gradients = '--------'
1384       slices = '       0'
1385       coordinates = '     0.0'
1386       i = 1
1387       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1388         
1389          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1390          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1391
1392          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1393          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1394         
1395          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1396          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1397         
1398          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1399          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1400
1401          IF ( i == 10 )  THEN
1402             EXIT
1403          ELSE
1404             i = i + 1
1405          ENDIF
1406
1407       ENDDO
1408
1409       IF ( humidity )  THEN
1410          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1411                             TRIM( gradients ), TRIM( slices )
1412       ELSE
1413          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1414                             TRIM( gradients ), TRIM( slices )
1415       ENDIF
1416    ENDIF
1417
1418!
1419!-- Initial salinity profile
1420!-- Building output strings, starting with surface salinity
1421    IF ( ocean )  THEN
1422       WRITE ( temperatures, '(F6.2)' )  sa_surface
1423       gradients = '------'
1424       slices = '     0'
1425       coordinates = '   0.0'
1426       i = 1
1427       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1428
1429          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1430          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1431
1432          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1433          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1434
1435          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1436          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1437
1438          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1439          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1440
1441          IF ( i == 10 )  THEN
1442             EXIT
1443          ELSE
1444             i = i + 1
1445          ENDIF
1446
1447       ENDDO
1448
1449       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1450                          TRIM( gradients ), TRIM( slices )
1451    ENDIF
1452
1453!
1454!-- Profile for the large scale vertial velocity
1455!-- Building output strings, starting with surface value
1456    IF ( large_scale_subsidence )  THEN
1457       temperatures = '   0.0'
1458       gradients = '------'
1459       slices = '     0'
1460       coordinates = '   0.0'
1461       i = 1
1462       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
1463
1464          WRITE (coor_chr,'(E10.2,7X)')  &
1465                                w_subs(subs_vertical_gradient_level_i(i))
1466          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1467
1468          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
1469          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1470
1471          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
1472          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1473
1474          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
1475          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1476
1477          IF ( i == 10 )  THEN
1478             EXIT
1479          ELSE
1480             i = i + 1
1481          ENDIF
1482
1483       ENDDO
1484
1485       WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1486                          TRIM( gradients ), TRIM( slices )
1487    ENDIF
1488
1489!
1490!-- Cloud physcis parameters / quantities / numerical methods
1491    WRITE ( io, 430 )
1492    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1493       WRITE ( io, 431 )
1494    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1495       WRITE ( io, 432 )
1496       IF ( radiation )      WRITE ( io, 132 )
1497       IF ( precipitation )  WRITE ( io, 133 )
1498    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1499       WRITE ( io, 433 )
1500       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1501       IF ( collision_kernel /= 'none' )  THEN
1502          WRITE ( io, 435 )  TRIM( collision_kernel )
1503          IF ( collision_kernel(6:9) == 'fast' )  THEN
1504             WRITE ( io, 436 )  radius_classes, dissipation_classes
1505          ENDIF
1506       ELSE
1507          WRITE ( io, 437 )
1508       ENDIF
1509    ENDIF
1510
1511!
1512!-- LES / turbulence parameters
1513    WRITE ( io, 450 )
1514
1515!--
1516! ... LES-constants used must still be added here
1517!--
1518    IF ( constant_diffusion )  THEN
1519       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1520                          prandtl_number
1521    ENDIF
1522    IF ( .NOT. constant_diffusion)  THEN
1523       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1524       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1525       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1526       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1527    ENDIF
1528
1529!
1530!-- Special actions during the run
1531    WRITE ( io, 470 )
1532    IF ( create_disturbances )  THEN
1533       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1534                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1535                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1536       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1537          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1538       ELSE
1539          WRITE ( io, 473 )  disturbance_energy_limit
1540       ENDIF
1541       WRITE ( io, 474 )  TRIM( random_generator )
1542    ENDIF
1543    IF ( pt_surface_initial_change /= 0.0 )  THEN
1544       WRITE ( io, 475 )  pt_surface_initial_change
1545    ENDIF
1546    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1547       WRITE ( io, 476 )  q_surface_initial_change       
1548    ENDIF
1549    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1550       WRITE ( io, 477 )  q_surface_initial_change       
1551    ENDIF
1552
1553    IF ( particle_advection )  THEN
1554!
1555!--    Particle attributes
1556       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1557                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1558                          end_time_prel, dt_sort_particles
1559       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1560       IF ( random_start_position )  WRITE ( io, 481 )
1561       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1562       WRITE ( io, 495 )  total_number_of_particles
1563       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1564          WRITE ( io, 483 )  maximum_number_of_tailpoints
1565          IF ( minimum_tailpoint_distance /= 0 )  THEN
1566             WRITE ( io, 484 )  total_number_of_tails,      &
1567                                minimum_tailpoint_distance, &
1568                                maximum_tailpoint_age
1569          ENDIF
1570       ENDIF
1571       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1572          WRITE ( io, 485 )  dt_write_particle_data
1573          output_format = ''
1574          IF ( netcdf_output )  THEN
1575             IF ( netcdf_data_format > 1 )  THEN
1576                output_format = 'netcdf (64 bit offset) and binary'
1577             ELSE
1578                output_format = 'netcdf and binary'
1579             ENDIF
1580          ELSE
1581             output_format = 'binary'
1582          ENDIF
1583          WRITE ( io, 344 )  output_format
1584       ENDIF
1585       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1586       IF ( write_particle_statistics )  WRITE ( io, 486 )
1587
1588       WRITE ( io, 487 )  number_of_particle_groups
1589
1590       DO  i = 1, number_of_particle_groups
1591          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1592             WRITE ( io, 490 )  i, 0.0
1593             WRITE ( io, 492 )
1594          ELSE
1595             WRITE ( io, 490 )  i, radius(i)
1596             IF ( density_ratio(i) /= 0.0 )  THEN
1597                WRITE ( io, 491 )  density_ratio(i)
1598             ELSE
1599                WRITE ( io, 492 )
1600             ENDIF
1601          ENDIF
1602          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1603                             pdx(i), pdy(i), pdz(i)
1604          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1605       ENDDO
1606
1607    ENDIF
1608
1609
1610!
1611!-- Parameters of 1D-model
1612    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1613       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1614                          mixing_length_1d, dissipation_1d
1615       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1616          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1617       ENDIF
1618    ENDIF
1619
1620!
1621!-- User-defined informations
1622    CALL user_header( io )
1623
1624    WRITE ( io, 99 )
1625
1626!
1627!-- Write buffer contents to disc immediately
1628    CALL local_flush( io )
1629
1630!
1631!-- Here the FORMATs start
1632
1633 99 FORMAT (1X,78('-'))
1634100 FORMAT (/1X,'***************************',9X,42('-')/        &
1635            1X,'* ',A,' *',9X,A/                               &
1636            1X,'***************************',9X,42('-'))
1637101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1638            37X,42('-'))
1639102 FORMAT (/' Date:              ',A8,9X,'Run:       ',A20/      &
1640            ' Time:              ',A8,9X,'Run-No.:   ',I2.2/     &
1641            ' Run on host:     ',A10)
1642#if defined( __parallel )
1643103 FORMAT (' Number of PEs:',8X,I5,9X,'Processor grid (x,y): (',I3,',',I3, &
1644              ')',1X,A)
1645104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1646              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1647105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1648106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1649            37X,'because the job is running on an SMP-cluster')
1650107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1651108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
1652#endif
1653110 FORMAT (/' Numerical Schemes:'/ &
1654             ' -----------------'/)
1655111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1656112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1657            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1658113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1659                  ' or Upstream')
1660114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1661115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1662116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1663                  ' or Upstream')
1664117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1665118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1666119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1667            '     Translation velocity = ',A/ &
1668            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1669120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1670                  ' of timestep changes)')
1671121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1672                  ' timestep changes')
1673122 FORMAT (' --> Time differencing scheme: ',A)
1674123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1675            '     maximum damping coefficient: ',F5.3, ' 1/s')
1676124 FORMAT ('     Spline-overshoots are being suppressed')
1677125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1678                  ' of'/                                                       &
1679            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1680126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1681                  ' of'/                                                       &
1682            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1683127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1684            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1685128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1686            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1687129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1688130 FORMAT (' --> Additional prognostic equation for the total water content')
1689131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1690                  F6.2, ' K assumed')
1691132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1692            '     effective emissivity scheme')
1693133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1694134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1695135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1696                  A,'-cycle)'/ &
1697            '     number of grid levels:                   ',I2/ &
1698            '     Gauss-Seidel red/black iterations:       ',I2)
1699136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1700                  I3,')')
1701137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1702            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1703                  I3,')'/ &
1704            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1705                  I3,')')
1706138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1707139 FORMAT (' --> Loop optimization method: ',A)
1708140 FORMAT ('     maximum residual allowed:                ',E10.3)
1709141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1710142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1711                  'step')
1712143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1713                  'kinetic energy')
1714144 FORMAT ('     masking method is used')
1715150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1716                  'conserved'/ &
1717            '     using the ',A,' mode')
1718151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1719152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1720           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1721           /'     starting from dp_level_b =', F8.3, 'm', A /)
1722153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1723                  'prognostic equation for')
1724154 FORMAT ('     the potential temperature')
1725200 FORMAT (//' Run time and time step information:'/ &
1726             ' ----------------------------------'/)
1727201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1728             '    CFL-factor: ',F4.2)
1729202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1730203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1731             ' End time:         ',F9.3,' s')
1732204 FORMAT ( A,F9.3,' s')
1733205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1734206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1735             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1736               '  ',F9.3,' s'/                                                 &
1737             '                                   per second of simulated tim', &
1738               'e: ',F9.3,' s')
1739207 FORMAT ( A/' Coupling start time:',F9.3,' s')
1740250 FORMAT (//' Computational grid and domain size:'/ &
1741              ' ----------------------------------'// &
1742              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1743              ' m    dz =    ',F7.3,' m'/ &
1744              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1745              ' m  z(u) = ',F10.3,' m'/)
1746252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1747              ' factor: ',F5.3/ &
1748            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1749254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1750            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1751255 FORMAT (' Subdomains have equal size')
1752256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1753              'have smaller sizes'/                                          &
1754            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1755260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1756             ' degrees')
1757270 FORMAT (//' Topography informations:'/ &
1758              ' -----------------------'// &
1759              1X,'Topography: ',A)
1760271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1761              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1762                ' / ',I4)
1763272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1764              ' direction' / &
1765              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1766              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1767278 FORMAT (' Topography grid definition convention:'/ &
1768            ' cell edge (staggered grid points'/  &
1769            ' (u in x-direction, v in y-direction))' /)
1770279 FORMAT (' Topography grid definition convention:'/ &
1771            ' cell center (scalar grid points)' /)
1772280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1773              ' ------------------------------'// &
1774              ' Canopy mode: ', A / &
1775              ' Canopy top: ',I4 / &
1776              ' Leaf drag coefficient: ',F6.2 /)
1777281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1778              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1779282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1780283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1781              ' Height:              ',A,'  m'/ &
1782              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1783              ' Gradient:            ',A,'  m**2/m**4'/ &
1784              ' Gridpoint:           ',A)
1785               
1786300 FORMAT (//' Boundary conditions:'/ &
1787             ' -------------------'// &
1788             '                     p                    uv             ', &
1789             '                   pt'// &
1790             ' B. bound.: ',A/ &
1791             ' T. bound.: ',A)
1792301 FORMAT (/'                     ',A// &
1793             ' B. bound.: ',A/ &
1794             ' T. bound.: ',A)
1795303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1796304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1797305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1798               'computational u,v-level:'// &
1799             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1800             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1801306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1802307 FORMAT ('       Heatflux has a random normal distribution')
1803308 FORMAT ('       Predefined surface temperature')
1804309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1805310 FORMAT (//'    1D-Model:'// &
1806             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1807311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1808312 FORMAT ('       Predefined surface humidity')
1809313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1810314 FORMAT ('       Predefined scalar value at the surface')
1811315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1812316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1813                    'atmosphere model')
1814317 FORMAT (//' Lateral boundaries:'/ &
1815            '       left/right:  ',A/    &
1816            '       north/south: ',A)
1817318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1818                    'max =',F5.1,' m**2/s')
1819319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1820            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1821            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1822320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1823            '                                          v: ',F9.6,' m**2/s**2')
1824325 FORMAT (//' List output:'/ &
1825             ' -----------'//  &
1826            '    1D-Profiles:'/    &
1827            '       Output every             ',F8.2,' s')
1828326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1829            '       Averaging input every    ',F8.2,' s')
1830330 FORMAT (//' Data output:'/ &
1831             ' -----------'/)
1832331 FORMAT (/'    1D-Profiles:')
1833332 FORMAT (/'       ',A)
1834333 FORMAT ('       Output every             ',F8.2,' s',/ &
1835            '       Time averaged over       ',F8.2,' s'/ &
1836            '       Averaging input every    ',F8.2,' s')
1837334 FORMAT (/'    2D-Arrays',A,':')
1838335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1839            '       Output every             ',F8.2,' s  ',A/ &
1840            '       Cross sections at ',A1,' = ',A/ &
1841            '       scalar-coordinates:   ',A,' m'/)
1842336 FORMAT (/'    3D-Arrays',A,':')
1843337 FORMAT (/'       Arrays: ',A/ &
1844            '       Output every             ',F8.2,' s  ',A/ &
1845            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1846338 FORMAT ('       Compressed data output'/ &
1847            '       Decimal precision: ',A/)
1848339 FORMAT ('       No output during initial ',F8.2,' s')
1849340 FORMAT (/'    Time series:')
1850341 FORMAT ('       Output every             ',F8.2,' s'/)
1851342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1852            '       Output every             ',F8.2,' s  ',A/ &
1853            '       Time averaged over       ',F8.2,' s'/ &
1854            '       Averaging input every    ',F8.2,' s'/ &
1855            '       Cross sections at ',A1,' = ',A/ &
1856            '       scalar-coordinates:   ',A,' m'/)
1857343 FORMAT (/'       Arrays: ',A/ &
1858            '       Output every             ',F8.2,' s  ',A/ &
1859            '       Time averaged over       ',F8.2,' s'/ &
1860            '       Averaging input every    ',F8.2,' s'/ &
1861            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1862344 FORMAT ('       Output format: ',A/)
1863345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1864            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1865            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1866            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1867346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1868347 FORMAT ('       Variables: ',A/ &
1869            '       Output every             ',F8.2,' s')
1870348 FORMAT ('       Variables: ',A/ &
1871            '       Output every             ',F8.2,' s'/ &
1872            '       Time averaged over       ',F8.2,' s'/ &
1873            '       Averaging input every    ',F8.2,' s')
1874349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1875            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1876            13('       ',8(F8.2,',')/) )
1877350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1878            'all gridpoints along ',A,'-direction (default).' )
1879351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1880            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1881            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1882#if defined( __dvrp_graphics )
1883360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1884            '       Output every      ',F7.1,' s'/ &
1885            '       Output mode:      ',A/ &
1886            '       Host / User:      ',A,' / ',A/ &
1887            '       Directory:        ',A// &
1888            '       The sequence contains:')
1889361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1890            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1891362 FORMAT (/'       Slicer plane ',A/ &
1892            '       Slicer limits: [',F6.2,',',F6.2,']')
1893363 FORMAT (/'       Particles'/ &
1894            '          particle size:  ',F7.2,' m')
1895364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1896                       F6.2,',',F6.2,']')
1897365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1898            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1899                     ')'/ &
1900            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1901            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1902366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1903367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1904#endif
1905#if defined( __spectra )
1906370 FORMAT ('    Spectra:')
1907371 FORMAT ('       Output every ',F7.1,' s'/)
1908372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1909            '       Directions: ', 10(A5,',')/                         &
1910            '       height levels  k = ', 20(I3,',')/                  &
1911            '                          ', 20(I3,',')/                  &
1912            '                          ', 20(I3,',')/                  &
1913            '                          ', 20(I3,',')/                  &
1914            '                          ', 19(I3,','),I3,'.'/           &
1915            '       height levels selected for standard plot:'/        &
1916            '                      k = ', 20(I3,',')/                  &
1917            '                          ', 20(I3,',')/                  &
1918            '                          ', 20(I3,',')/                  &
1919            '                          ', 20(I3,',')/                  &
1920            '                          ', 19(I3,','),I3,'.'/           &
1921            '       Time averaged over ', F7.1, ' s,' /                &
1922            '       Profiles for the time averaging are taken every ', &
1923                    F6.1,' s')
1924#endif
1925400 FORMAT (//' Physical quantities:'/ &
1926              ' -------------------'/)
1927410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1928            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1929            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1930            '                            f*    = ',F9.6,' 1/s')
1931411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1932412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1933413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1934415 FORMAT (/'    Cloud physics parameters:'/ &
1935             '    ------------------------'/)
1936416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1937            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1938            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1939            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1940            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1941420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1942            '       Height:        ',A,'  m'/ &
1943            '       Temperature:   ',A,'  K'/ &
1944            '       Gradient:      ',A,'  K/100m'/ &
1945            '       Gridpoint:     ',A)
1946421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1947            '       Height:      ',A,'  m'/ &
1948            '       Humidity:    ',A,'  kg/kg'/ &
1949            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1950            '       Gridpoint:   ',A)
1951422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1952            '       Height:                  ',A,'  m'/ &
1953            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1954            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1955            '       Gridpoint:               ',A)
1956423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1957            '       Height:      ',A,'  m'/ &
1958            '       ug:          ',A,'  m/s'/ &
1959            '       Gradient:    ',A,'  1/100s'/ &
1960            '       Gridpoint:   ',A)
1961424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1962            '       Height:      ',A,'  m'/ &
1963            '       vg:          ',A,'  m/s'/ &
1964            '       Gradient:    ',A,'  1/100s'/ &
1965            '       Gridpoint:   ',A)
1966425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1967            '       Height:     ',A,'  m'/ &
1968            '       Salinity:   ',A,'  psu'/ &
1969            '       Gradient:   ',A,'  psu/100m'/ &
1970            '       Gridpoint:  ',A)
1971426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1972            '       Height:      ',A,'  m'/ &
1973            '       w_subs:      ',A,'  m/s'/ &
1974            '       Gradient:    ',A,'  (m/s)/100m'/ &
1975            '       Gridpoint:   ',A)
1976427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1977                  ' profiles')
1978430 FORMAT (//' Cloud physics quantities / methods:'/ &
1979              ' ----------------------------------'/)
1980431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1981                 'on)')
1982432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1983            '    total water content is used.'/ &
1984            '    Condensation is parameterized via 0% - or 100% scheme.')
1985433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1986                 'icle model')
1987434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1988                 ' droplets < 1.0E-6 m')
1989435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
1990436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1991                    'are used'/ &
1992            '          number of radius classes:       ',I3,'    interval ', &
1993                       '[1.0E-6,2.0E-4] m'/ &
1994            '          number of dissipation classes:   ',I2,'    interval ', &
1995                       '[0,1000] cm**2/s**3')
1996437 FORMAT ('    Droplet collision is switched off')
1997450 FORMAT (//' LES / Turbulence quantities:'/ &
1998              ' ---------------------------'/)
1999451 FORMAT ('    Diffusion coefficients are constant:'/ &
2000            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2001452 FORMAT ('    Mixing length is limited to the Prandtl mixing lenth.')
2002453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2003454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2004455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2005470 FORMAT (//' Actions during the simulation:'/ &
2006              ' -----------------------------'/)
2007471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2008            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2009            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2010            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2011472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2012                 ' to i/j =',I4)
2013473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2014                 1X,F5.3, ' m**2/s**2')
2015474 FORMAT ('    Random number generator used    : ',A/)
2016475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2017                 'respectively, if'/ &
2018            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2019                 ' 3D-simulation'/)
2020476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2021                 'respectively, if the'/ &
2022            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2023                 ' the 3D-simulation'/)
2024477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2025                 'respectively, if the'/ &
2026            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2027                 ' the 3D-simulation'/)
2028480 FORMAT ('    Particles:'/ &
2029            '    ---------'// &
2030            '       Particle advection is active (switched on at t = ', F7.1, &
2031                    ' s)'/ &
2032            '       Start of new particle generations every  ',F6.1,' s'/ &
2033            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2034            '                            bottom:     ', A, ' top:         ', A/&
2035            '       Maximum particle age:                 ',F9.1,' s'/ &
2036            '       Advection stopped at t = ',F9.1,' s'/ &
2037            '       Particles are sorted every ',F9.1,' s'/)
2038481 FORMAT ('       Particles have random start positions'/)
2039482 FORMAT ('          Particles are advected only horizontally'/)
2040483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2041484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2042            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2043            '            Maximum age of the end of the tail:  ',F8.2,' s')
2044485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2045486 FORMAT ('       Particle statistics are written on file'/)
2046487 FORMAT ('       Number of particle groups: ',I2/)
2047488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2048            '          minimum timestep for advection: ', F7.5/)
2049489 FORMAT ('       Number of particles simultaneously released at each ', &
2050                    'point: ', I5/)
2051490 FORMAT ('       Particle group ',I2,':'/ &
2052            '          Particle radius: ',E10.3, 'm')
2053491 FORMAT ('          Particle inertia is activated'/ &
2054            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2055492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2056493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2057            '                                         y:',F8.1,' - ',F8.1,' m'/&
2058            '                                         z:',F8.1,' - ',F8.1,' m'/&
2059            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2060                       ' m  dz = ',F8.1,' m'/)
2061494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2062                    F8.2,' s'/)
2063495 FORMAT ('       Number of particles in total domain: ',I10/)
2064500 FORMAT (//' 1D-Model parameters:'/                           &
2065              ' -------------------'//                           &
2066            '    Simulation time:                   ',F8.1,' s'/ &
2067            '    Run-controll output every:         ',F8.1,' s'/ &
2068            '    Vertical profile output every:     ',F8.1,' s'/ &
2069            '    Mixing length calculation:         ',A/         &
2070            '    Dissipation calculation:           ',A/)
2071502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2072503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2073504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2074
2075
2076 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.