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

Last change on this file since 1321 was 1321, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 82.1 KB
Line 
1 SUBROUTINE header
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 1321 2014-03-20 09:40:40Z raasch $
27!
28! 1320 2014-03-20 08:40:49Z raasch
29! ONLY-attribute added to USE-statements,
30! kind-parameters added to all INTEGER and REAL declaration statements,
31! kinds are defined in new module kinds,
32! revision history before 2012 removed,
33! comment fields (!:) to be used for variable explanations added to
34! all variable declaration statements
35!
36! 1308 2014-03-13 14:58:42Z fricke
37! output of the fixed number of output time levels
38! output_format adjusted for masked data if netcdf_data_format > 5
39!
40! 1299 2014-03-06 13:15:21Z heinze
41! output for using large_scale subsidence in combination
42! with large_scale_forcing
43! reformatting, more detailed explanations
44!
45! 1241 2013-10-30 11:36:58Z heinze
46! output for nudging + large scale forcing from external file
47!
48! 1216 2013-08-26 09:31:42Z raasch
49! output for transpose_compute_overlap
50!
51! 1212 2013-08-15 08:46:27Z raasch
52! output for poisfft_hybrid removed
53!
54! 1179 2013-06-14 05:57:58Z raasch
55! output of reference_state, use_reference renamed use_single_reference_value
56!
57! 1159 2013-05-21 11:58:22Z fricke
58! +use_cmax
59!
60! 1115 2013-03-26 18:16:16Z hoffmann
61! descriptions for Seifert-Beheng-cloud-physics-scheme added
62!
63! 1111 2013-03-08 23:54:10Z raasch
64! output of accelerator board information
65! ibc_p_b = 2 removed
66!
67! 1108 2013-03-05 07:03:32Z raasch
68! bugfix for r1106
69!
70! 1106 2013-03-04 05:31:38Z raasch
71! some format changes for coupled runs
72!
73! 1092 2013-02-02 11:24:22Z raasch
74! unused variables removed
75!
76! 1036 2012-10-22 13:43:42Z raasch
77! code put under GPL (PALM 3.9)
78!
79! 1031 2012-10-19 14:35:30Z raasch
80! output of netCDF data format modified
81!
82! 1015 2012-09-27 09:23:24Z raasch
83! output of Aajustment of mixing length to the Prandtl mixing length at first
84! grid point above ground removed
85!
86! 1003 2012-09-14 14:35:53Z raasch
87! output of information about equal/unequal subdomain size removed
88!
89! 1001 2012-09-13 14:08:46Z raasch
90! all actions concerning leapfrog- and upstream-spline-scheme removed
91!
92! 978 2012-08-09 08:28:32Z fricke
93! -km_damp_max, outflow_damping_width
94! +pt_damping_factor, pt_damping_width
95! +z0h
96!
97! 964 2012-07-26 09:14:24Z raasch
98! output of profil-related quantities removed
99!
100! 940 2012-07-09 14:31:00Z raasch
101! Output in case of simulations for pure neutral stratification (no pt-equation
102! solved)
103!
104! 927 2012-06-06 19:15:04Z raasch
105! output of masking_method for mg-solver
106!
107! 868 2012-03-28 12:21:07Z raasch
108! translation velocity in Galilean transformation changed to 0.6 * ug
109!
110! 833 2012-02-22 08:55:55Z maronga
111! Adjusted format for leaf area density
112!
113! 828 2012-02-21 12:00:36Z raasch
114! output of dissipation_classes + radius_classes
115!
116! 825 2012-02-19 03:03:44Z raasch
117! Output of cloud physics parameters/quantities complemented and restructured
118!
119! Revision 1.1  1997/08/11 06:17:20  raasch
120! Initial revision
121!
122!
123! Description:
124! ------------
125! Writing a header with all important informations about the actual run.
126! This subroutine is called three times, two times at the beginning
127! (writing information on files RUN_CONTROL and HEADER) and one time at the
128! end of the run, then writing additional information about CPU-usage on file
129! header.
130!-----------------------------------------------------------------------------!
131
132    USE arrays_3d,                                                             &
133        ONLY:  lad, pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
134       
135    USE control_parameters
136       
137    USE cloud_parameters,                                                      &
138        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
139               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
140       
141    USE cpulog,                                                                &
142        ONLY:  log_point_s
143       
144    USE dvrp_variables,                                                        &
145        ONLY:  use_seperate_pe_for_dvrp_output
146       
147    USE grid_variables,                                                        &
148        ONLY:  dx, dy
149       
150    USE indices,                                                               &
151        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
152               nys_mg, nzt, nzt_mg
153       
154    USE kinds
155   
156    USE model_1d,                                                              &
157        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
158       
159    USE particle_attributes,                                                   &
160        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
161               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
162               dt_sort_particles, dt_write_particle_data, end_time_prel,       &
163               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
164               minimum_tailpoint_distance, number_of_particle_groups,          &
165               particle_advection, particle_advection_start,                   &
166               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
167               pst, radius, radius_classes, random_start_position,             &
168               total_number_of_particles, use_particle_tails,                  &
169               use_sgs_for_particles, total_number_of_tails,                   &
170               vertical_particle_advection, write_particle_statistics
171       
172    USE pegrid
173
174    IMPLICIT NONE
175
176    CHARACTER (LEN=1)  ::  prec                !:
177   
178    CHARACTER (LEN=2)  ::  do2d_mode           !:
179   
180    CHARACTER (LEN=5)  ::  section_chr         !:
181   
182    CHARACTER (LEN=10) ::  coor_chr            !:
183    CHARACTER (LEN=10) ::  host_chr            !:
184   
185    CHARACTER (LEN=16) ::  begin_chr           !:
186   
187    CHARACTER (LEN=26) ::  ver_rev             !:
188   
189    CHARACTER (LEN=40) ::  output_format       !:
190   
191    CHARACTER (LEN=70) ::  char1               !:
192    CHARACTER (LEN=70) ::  char2               !:
193    CHARACTER (LEN=70) ::  dopr_chr            !:
194    CHARACTER (LEN=70) ::  do2d_xy             !:
195    CHARACTER (LEN=70) ::  do2d_xz             !:
196    CHARACTER (LEN=70) ::  do2d_yz             !:
197    CHARACTER (LEN=70) ::  do3d_chr            !:
198    CHARACTER (LEN=70) ::  domask_chr          !:
199    CHARACTER (LEN=70) ::  run_classification  !:
200   
201    CHARACTER (LEN=85) ::  roben               !:
202    CHARACTER (LEN=85) ::  runten              !:
203   
204    CHARACTER (LEN=86) ::  coordinates         !:
205    CHARACTER (LEN=86) ::  gradients           !:
206    CHARACTER (LEN=86) ::  learde              !:
207    CHARACTER (LEN=86) ::  slices              !:
208    CHARACTER (LEN=86) ::  temperatures        !:
209    CHARACTER (LEN=86) ::  ugcomponent         !:
210    CHARACTER (LEN=86) ::  vgcomponent         !:
211
212    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
213
214    INTEGER(iwp) ::  av        !:
215    INTEGER(iwp) ::  bh        !:
216    INTEGER(iwp) ::  blx       !:
217    INTEGER(iwp) ::  bly       !:
218    INTEGER(iwp) ::  bxl       !:
219    INTEGER(iwp) ::  bxr       !:
220    INTEGER(iwp) ::  byn       !:
221    INTEGER(iwp) ::  bys       !:
222    INTEGER(iwp) ::  ch        !:
223    INTEGER(iwp) ::  count     !:
224    INTEGER(iwp) ::  cwx       !:
225    INTEGER(iwp) ::  cwy       !:
226    INTEGER(iwp) ::  cxl       !:
227    INTEGER(iwp) ::  cxr       !:
228    INTEGER(iwp) ::  cyn       !:
229    INTEGER(iwp) ::  cys       !:
230    INTEGER(iwp) ::  dim       !:
231    INTEGER(iwp) ::  i         !:
232    INTEGER(iwp) ::  io        !:
233    INTEGER(iwp) ::  j         !:
234    INTEGER(iwp) ::  l         !:
235    INTEGER(iwp) ::  ll        !:
236    INTEGER(iwp) ::  mpi_type  !:
237   
238    REAL(wp) ::  cpuseconds_per_simulated_second  !:
239
240!
241!-- Open the output file. At the end of the simulation, output is directed
242!-- to unit 19.
243    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
244         .NOT. simulated_time_at_begin /= simulated_time )  THEN
245       io = 15   !  header output on file RUN_CONTROL
246    ELSE
247       io = 19   !  header output on file HEADER
248    ENDIF
249    CALL check_open( io )
250
251!
252!-- At the end of the run, output file (HEADER) will be rewritten with
253!-- new informations
254    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
255
256!
257!-- Determine kind of model run
258    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
259       run_classification = '3D - restart run'
260    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
261       run_classification = '3D - run with cyclic fill of 3D - prerun data'
262    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
263       run_classification = '3D - run without 1D - prerun'
264    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
265       run_classification = '3D - run with 1D - prerun'
266    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
267       run_classification = '3D - run initialized by user'
268    ELSE
269       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
270       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
271    ENDIF
272    IF ( ocean )  THEN
273       run_classification = 'ocean - ' // run_classification
274    ELSE
275       run_classification = 'atmosphere - ' // run_classification
276    ENDIF
277
278!
279!-- Run-identification, date, time, host
280    host_chr = host(1:10)
281    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
282    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
283    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
284#if defined( __mpi2 )
285       mpi_type = 2
286#else
287       mpi_type = 1
288#endif
289       WRITE ( io, 101 )  mpi_type, coupling_mode
290    ENDIF
291#if defined( __parallel )
292    IF ( coupling_start_time /= 0.0 )  THEN
293       IF ( coupling_start_time > simulated_time_at_begin )  THEN
294          WRITE ( io, 109 )
295       ELSE
296          WRITE ( io, 114 )
297       ENDIF
298    ENDIF
299#endif
300    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
301                       ADJUSTR( host_chr )
302#if defined( __parallel )
303    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
304       char1 = 'calculated'
305    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
306               host(1:2) == 'lc' )  .AND.                          &
307             npex == -1  .AND.  pdims(2) == 1 )  THEN
308       char1 = 'forced'
309    ELSE
310       char1 = 'predefined'
311    ENDIF
312    IF ( threads_per_task == 1 )  THEN
313       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
314    ELSE
315       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
316                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
317    ENDIF
318    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
319    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
320           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
321         npex == -1  .AND.  pdims(2) == 1 )                      &
322    THEN
323       WRITE ( io, 106 )
324    ELSEIF ( pdims(2) == 1 )  THEN
325       WRITE ( io, 107 )  'x'
326    ELSEIF ( pdims(1) == 1 )  THEN
327       WRITE ( io, 107 )  'y'
328    ENDIF
329    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
330    IF ( numprocs /= maximum_parallel_io_streams )  THEN
331       WRITE ( io, 108 )  maximum_parallel_io_streams
332    ENDIF
333#else
334    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
335#endif
336    WRITE ( io, 99 )
337
338!
339!-- Numerical schemes
340    WRITE ( io, 110 )
341    IF ( psolver(1:7) == 'poisfft' )  THEN
342       WRITE ( io, 111 )  TRIM( fft_method )
343       IF ( transpose_compute_overlap )  WRITE( io, 115 )
344    ELSEIF ( psolver == 'sor' )  THEN
345       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
346    ELSEIF ( psolver == 'multigrid' )  THEN
347       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
348       IF ( mg_cycles == -1 )  THEN
349          WRITE ( io, 140 )  residual_limit
350       ELSE
351          WRITE ( io, 141 )  mg_cycles
352       ENDIF
353       IF ( mg_switch_to_pe0_level == 0 )  THEN
354          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
355                             nzt_mg(1)
356       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
357          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
358                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
359                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
360                             nzt_mg(mg_switch_to_pe0_level),    &
361                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
362                             nzt_mg(1)
363       ENDIF
364       IF ( masking_method )  WRITE ( io, 144 )
365    ENDIF
366    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
367    THEN
368       WRITE ( io, 142 )
369    ENDIF
370
371    IF ( momentum_advec == 'pw-scheme' )  THEN
372       WRITE ( io, 113 )
373    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
374       WRITE ( io, 503 )
375    ENDIF
376    IF ( scalar_advec == 'pw-scheme' )  THEN
377       WRITE ( io, 116 )
378    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
379       WRITE ( io, 504 )
380    ELSE
381       WRITE ( io, 118 )
382    ENDIF
383
384    WRITE ( io, 139 )  TRIM( loop_optimization )
385
386    IF ( galilei_transformation )  THEN
387       IF ( use_ug_for_galilei_tr )  THEN
388          char1 = '0.6 * geostrophic wind'
389       ELSE
390          char1 = 'mean wind in model domain'
391       ENDIF
392       IF ( simulated_time_at_begin == simulated_time )  THEN
393          char2 = 'at the start of the run'
394       ELSE
395          char2 = 'at the end of the run'
396       ENDIF
397       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
398                          advected_distance_x/1000.0, advected_distance_y/1000.0
399    ENDIF
400    WRITE ( io, 122 )  timestep_scheme
401    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
402    IF ( rayleigh_damping_factor /= 0.0 )  THEN
403       IF ( .NOT. ocean )  THEN
404          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
405               rayleigh_damping_factor
406       ELSE
407          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
408               rayleigh_damping_factor
409       ENDIF
410    ENDIF
411    IF ( neutral )  WRITE ( io, 131 )  pt_surface
412    IF ( humidity )  THEN
413       IF ( .NOT. cloud_physics )  THEN
414          WRITE ( io, 129 )
415       ELSE
416          WRITE ( io, 130 )
417       ENDIF
418    ENDIF
419    IF ( passive_scalar )  WRITE ( io, 134 )
420    IF ( conserve_volume_flow )  THEN
421       WRITE ( io, 150 )  conserve_volume_flow_mode
422       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
423          WRITE ( io, 151 )  u_bulk, v_bulk
424       ENDIF
425    ELSEIF ( dp_external )  THEN
426       IF ( dp_smooth )  THEN
427          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
428       ELSE
429          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
430       ENDIF
431    ENDIF
432    IF ( large_scale_subsidence )  THEN
433        WRITE ( io, 153 )
434        WRITE ( io, 154 )
435    ENDIF
436    IF ( nudging )  THEN
437        WRITE ( io, 155 )
438        WRITE ( io, 156 )
439    ENDIF
440    IF ( large_scale_forcing )  THEN
441        WRITE ( io, 157 )
442        WRITE ( io, 158 )
443    ENDIF
444    WRITE ( io, 99 )
445
446!
447!-- Runtime and timestep informations
448    WRITE ( io, 200 )
449    IF ( .NOT. dt_fixed )  THEN
450       WRITE ( io, 201 )  dt_max, cfl_factor
451    ELSE
452       WRITE ( io, 202 )  dt
453    ENDIF
454    WRITE ( io, 203 )  simulated_time_at_begin, end_time
455
456    IF ( time_restart /= 9999999.9  .AND. &
457         simulated_time_at_begin == simulated_time )  THEN
458       IF ( dt_restart == 9999999.9 )  THEN
459          WRITE ( io, 204 )  ' Restart at:       ',time_restart
460       ELSE
461          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
462       ENDIF
463    ENDIF
464
465    IF ( simulated_time_at_begin /= simulated_time )  THEN
466       i = MAX ( log_point_s(10)%counts, 1 )
467       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
468          cpuseconds_per_simulated_second = 0.0
469       ELSE
470          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
471                                            ( simulated_time -    &
472                                              simulated_time_at_begin )
473       ENDIF
474       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
475                          log_point_s(10)%sum / REAL( i ),     &
476                          cpuseconds_per_simulated_second
477       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
478          IF ( dt_restart == 9999999.9 )  THEN
479             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
480          ELSE
481             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
482          ENDIF
483       ENDIF
484    ENDIF
485
486!
487!-- Start time for coupled runs, if independent precursor runs for atmosphere
488!-- and ocean are used or have been used. In this case, coupling_start_time
489!-- defines the time when the coupling is switched on.
490    IF ( coupling_start_time /= 0.0 )  THEN
491       WRITE ( io, 207 )  coupling_start_time
492    ENDIF
493
494!
495!-- Computational grid
496    IF ( .NOT. ocean )  THEN
497       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
498       IF ( dz_stretch_level_index < nzt+1 )  THEN
499          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
500                             dz_stretch_factor, dz_max
501       ENDIF
502    ELSE
503       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
504       IF ( dz_stretch_level_index > 0 )  THEN
505          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
506                             dz_stretch_factor, dz_max
507       ENDIF
508    ENDIF
509    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
510                       MIN( nnz+2, nzt+2 )
511    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
512
513!
514!-- Topography
515    WRITE ( io, 270 )  topography
516    SELECT CASE ( TRIM( topography ) )
517
518       CASE ( 'flat' )
519          ! no actions necessary
520
521       CASE ( 'single_building' )
522          blx = INT( building_length_x / dx )
523          bly = INT( building_length_y / dy )
524          bh  = INT( building_height / dz )
525
526          IF ( building_wall_left == 9999999.9 )  THEN
527             building_wall_left = ( nx + 1 - blx ) / 2 * dx
528          ENDIF
529          bxl = INT ( building_wall_left / dx + 0.5 )
530          bxr = bxl + blx
531
532          IF ( building_wall_south == 9999999.9 )  THEN
533             building_wall_south = ( ny + 1 - bly ) / 2 * dy
534          ENDIF
535          bys = INT ( building_wall_south / dy + 0.5 )
536          byn = bys + bly
537
538          WRITE ( io, 271 )  building_length_x, building_length_y, &
539                             building_height, bxl, bxr, bys, byn
540
541       CASE ( 'single_street_canyon' )
542          ch  = NINT( canyon_height / dz )
543          IF ( canyon_width_x /= 9999999.9 )  THEN
544!
545!--          Street canyon in y direction
546             cwx = NINT( canyon_width_x / dx )
547             IF ( canyon_wall_left == 9999999.9 )  THEN
548                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
549             ENDIF
550             cxl = NINT( canyon_wall_left / dx )
551             cxr = cxl + cwx
552             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
553
554          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
555!
556!--          Street canyon in x direction
557             cwy = NINT( canyon_width_y / dy )
558             IF ( canyon_wall_south == 9999999.9 )  THEN
559                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
560             ENDIF
561             cys = NINT( canyon_wall_south / dy )
562             cyn = cys + cwy
563             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
564          ENDIF
565
566    END SELECT
567
568    IF ( TRIM( topography ) /= 'flat' )  THEN
569       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
570          IF ( TRIM( topography ) == 'single_building' .OR.  &
571               TRIM( topography ) == 'single_street_canyon' )  THEN
572             WRITE ( io, 278 )
573          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
574             WRITE ( io, 279 )
575          ENDIF
576       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
577          WRITE ( io, 278 )
578       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
579          WRITE ( io, 279 )
580       ENDIF
581    ENDIF
582
583    IF ( plant_canopy )  THEN
584
585       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
586       IF ( passive_scalar )  THEN
587          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
588                            leaf_surface_concentration
589       ENDIF
590
591!
592!--    Heat flux at the top of vegetation
593       WRITE ( io, 282 ) cthf
594
595!
596!--    Leaf area density profile
597!--    Building output strings, starting with surface value
598       WRITE ( learde, '(F6.4)' )  lad_surface
599       gradients = '------'
600       slices = '     0'
601       coordinates = '   0.0'
602       i = 1
603       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
604
605          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
606          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
607
608          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
609          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
610
611          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
612          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
613
614          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
615          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
616
617          i = i + 1
618       ENDDO
619
620       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
621                          TRIM( gradients ), TRIM( slices )
622
623    ENDIF
624
625!
626!-- Boundary conditions
627    IF ( ibc_p_b == 0 )  THEN
628       runten = 'p(0)     = 0      |'
629    ELSEIF ( ibc_p_b == 1 )  THEN
630       runten = 'p(0)     = p(1)   |'
631    ENDIF
632    IF ( ibc_p_t == 0 )  THEN
633       roben  = 'p(nzt+1) = 0      |'
634    ELSE
635       roben  = 'p(nzt+1) = p(nzt) |'
636    ENDIF
637
638    IF ( ibc_uv_b == 0 )  THEN
639       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
640    ELSE
641       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
642    ENDIF
643    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
644       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
645    ELSEIF ( ibc_uv_t == 0 )  THEN
646       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
647    ELSE
648       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
649    ENDIF
650
651    IF ( ibc_pt_b == 0 )  THEN
652       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
653    ELSEIF ( ibc_pt_b == 1 )  THEN
654       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
655    ELSEIF ( ibc_pt_b == 2 )  THEN
656       runten = TRIM( runten ) // ' pt(0) = from coupled model'
657    ENDIF
658    IF ( ibc_pt_t == 0 )  THEN
659       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
660    ELSEIF( ibc_pt_t == 1 )  THEN
661       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
662    ELSEIF( ibc_pt_t == 2 )  THEN
663       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
664
665    ENDIF
666
667    WRITE ( io, 300 )  runten, roben
668
669    IF ( .NOT. constant_diffusion )  THEN
670       IF ( ibc_e_b == 1 )  THEN
671          runten = 'e(0)     = e(1)'
672       ELSE
673          runten = 'e(0)     = e(1) = (u*/0.1)**2'
674       ENDIF
675       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
676
677       WRITE ( io, 301 )  'e', runten, roben       
678
679    ENDIF
680
681    IF ( ocean )  THEN
682       runten = 'sa(0)    = sa(1)'
683       IF ( ibc_sa_t == 0 )  THEN
684          roben =  'sa(nzt+1) = sa_surface'
685       ELSE
686          roben =  'sa(nzt+1) = sa(nzt)'
687       ENDIF
688       WRITE ( io, 301 ) 'sa', runten, roben
689    ENDIF
690
691    IF ( humidity )  THEN
692       IF ( ibc_q_b == 0 )  THEN
693          runten = 'q(0)     = q_surface'
694       ELSE
695          runten = 'q(0)     = q(1)'
696       ENDIF
697       IF ( ibc_q_t == 0 )  THEN
698          roben =  'q(nzt)   = q_top'
699       ELSE
700          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
701       ENDIF
702       WRITE ( io, 301 ) 'q', runten, roben
703    ENDIF
704
705    IF ( passive_scalar )  THEN
706       IF ( ibc_q_b == 0 )  THEN
707          runten = 's(0)     = s_surface'
708       ELSE
709          runten = 's(0)     = s(1)'
710       ENDIF
711       IF ( ibc_q_t == 0 )  THEN
712          roben =  's(nzt)   = s_top'
713       ELSE
714          roben =  's(nzt)   = s(nzt-1) + ds/dz'
715       ENDIF
716       WRITE ( io, 301 ) 's', runten, roben
717    ENDIF
718
719    IF ( use_surface_fluxes )  THEN
720       WRITE ( io, 303 )
721       IF ( constant_heatflux )  THEN
722          IF ( large_scale_forcing .AND. lsf_surf )  THEN
723             WRITE ( io, 306 )  shf(0,0)
724          ELSE
725             WRITE ( io, 306 )  surface_heatflux
726          ENDIF
727          IF ( random_heatflux )  WRITE ( io, 307 )
728       ENDIF
729       IF ( humidity  .AND.  constant_waterflux )  THEN
730          IF ( large_scale_forcing .AND. lsf_surf )  THEN
731             WRITE ( io, 311 ) qsws(0,0)
732          ELSE
733             WRITE ( io, 311 ) surface_waterflux
734          ENDIF
735       ENDIF
736       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
737          WRITE ( io, 313 ) surface_waterflux
738       ENDIF
739    ENDIF
740
741    IF ( use_top_fluxes )  THEN
742       WRITE ( io, 304 )
743       IF ( coupling_mode == 'uncoupled' )  THEN
744          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
745          IF ( constant_top_heatflux )  THEN
746             WRITE ( io, 306 )  top_heatflux
747          ENDIF
748       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
749          WRITE ( io, 316 )
750       ENDIF
751       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
752          WRITE ( io, 309 )  top_salinityflux
753       ENDIF
754       IF ( humidity  .OR.  passive_scalar )  THEN
755          WRITE ( io, 315 )
756       ENDIF
757    ENDIF
758
759    IF ( prandtl_layer )  THEN
760       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
761                          z0h_factor*roughness_length, kappa, &
762                          rif_min, rif_max
763       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
764       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
765          WRITE ( io, 312 )
766       ENDIF
767       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
768          WRITE ( io, 314 )
769       ENDIF
770    ELSE
771       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
772          WRITE ( io, 310 )  rif_min, rif_max
773       ENDIF
774    ENDIF
775
776    WRITE ( io, 317 )  bc_lr, bc_ns
777    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
778       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
779       IF ( turbulent_inflow )  THEN
780          WRITE ( io, 319 )  recycling_width, recycling_plane, &
781                             inflow_damping_height, inflow_damping_width
782       ENDIF
783    ENDIF
784
785!
786!-- Listing of 1D-profiles
787    WRITE ( io, 325 )  dt_dopr_listing
788    IF ( averaging_interval_pr /= 0.0 )  THEN
789       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
790    ENDIF
791
792!
793!-- DATA output
794    WRITE ( io, 330 )
795    IF ( averaging_interval_pr /= 0.0 )  THEN
796       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
797    ENDIF
798
799!
800!-- 1D-profiles
801    dopr_chr = 'Profile:'
802    IF ( dopr_n /= 0 )  THEN
803       WRITE ( io, 331 )
804
805       output_format = ''
806       IF ( netcdf_output )  THEN
807          output_format = output_format_netcdf
808       ENDIF
809       WRITE ( io, 344 )  output_format
810
811       DO  i = 1, dopr_n
812          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
813          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
814             WRITE ( io, 332 )  dopr_chr
815             dopr_chr = '       :'
816          ENDIF
817       ENDDO
818
819       IF ( dopr_chr /= '' )  THEN
820          WRITE ( io, 332 )  dopr_chr
821       ENDIF
822       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
823       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
824    ENDIF
825
826!
827!-- 2D-arrays
828    DO  av = 0, 1
829
830       i = 1
831       do2d_xy = ''
832       do2d_xz = ''
833       do2d_yz = ''
834       DO  WHILE ( do2d(av,i) /= ' ' )
835
836          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
837          do2d_mode = do2d(av,i)(l-1:l)
838
839          SELECT CASE ( do2d_mode )
840             CASE ( 'xy' )
841                ll = LEN_TRIM( do2d_xy )
842                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
843             CASE ( 'xz' )
844                ll = LEN_TRIM( do2d_xz )
845                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
846             CASE ( 'yz' )
847                ll = LEN_TRIM( do2d_yz )
848                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
849          END SELECT
850
851          i = i + 1
852
853       ENDDO
854
855       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
856              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
857              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
858            ( netcdf_output  .OR.  iso2d_output ) )  THEN
859
860          IF (  av == 0 )  THEN
861             WRITE ( io, 334 )  ''
862          ELSE
863             WRITE ( io, 334 )  '(time-averaged)'
864          ENDIF
865
866          IF ( do2d_at_begin )  THEN
867             begin_chr = 'and at the start'
868          ELSE
869             begin_chr = ''
870          ENDIF
871
872          output_format = ''
873          IF ( netcdf_output )  THEN
874             output_format = output_format_netcdf
875          ENDIF
876          IF ( iso2d_output )  THEN
877             IF ( netcdf_output )  THEN
878                output_format = TRIM( output_format_netcdf ) // ' and iso2d'
879             ELSE
880                output_format = 'iso2d'
881             ENDIF
882          ENDIF
883          WRITE ( io, 344 )  output_format
884
885          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
886             i = 1
887             slices = '/'
888             coordinates = '/'
889!
890!--          Building strings with index and coordinate informations of the
891!--          slices
892             DO  WHILE ( section(i,1) /= -9999 )
893
894                WRITE (section_chr,'(I5)')  section(i,1)
895                section_chr = ADJUSTL( section_chr )
896                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
897
898                IF ( section(i,1) == -1 )  THEN
899                   WRITE (coor_chr,'(F10.1)')  -1.0
900                ELSE
901                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
902                ENDIF
903                coor_chr = ADJUSTL( coor_chr )
904                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
905
906                i = i + 1
907             ENDDO
908             IF ( av == 0 )  THEN
909                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
910                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
911                                   TRIM( coordinates )
912                IF ( skip_time_do2d_xy /= 0.0 )  THEN
913                   WRITE ( io, 339 )  skip_time_do2d_xy
914                ENDIF
915             ELSE
916                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
917                                   TRIM( begin_chr ), averaging_interval, &
918                                   dt_averaging_input, 'k', TRIM( slices ), &
919                                   TRIM( coordinates )
920                IF ( skip_time_data_output_av /= 0.0 )  THEN
921                   WRITE ( io, 339 )  skip_time_data_output_av
922                ENDIF
923             ENDIF
924             IF ( netcdf_data_format > 4 )  THEN
925                WRITE ( io, 352 )  ntdim_2d_xy(av)
926             ELSE
927                WRITE ( io, 353 )
928             ENDIF
929          ENDIF
930
931          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
932             i = 1
933             slices = '/'
934             coordinates = '/'
935!
936!--          Building strings with index and coordinate informations of the
937!--          slices
938             DO  WHILE ( section(i,2) /= -9999 )
939
940                WRITE (section_chr,'(I5)')  section(i,2)
941                section_chr = ADJUSTL( section_chr )
942                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
943
944                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
945                coor_chr = ADJUSTL( coor_chr )
946                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
947
948                i = i + 1
949             ENDDO
950             IF ( av == 0 )  THEN
951                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
952                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
953                                   TRIM( coordinates )
954                IF ( skip_time_do2d_xz /= 0.0 )  THEN
955                   WRITE ( io, 339 )  skip_time_do2d_xz
956                ENDIF
957             ELSE
958                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
959                                   TRIM( begin_chr ), averaging_interval, &
960                                   dt_averaging_input, 'j', TRIM( slices ), &
961                                   TRIM( coordinates )
962                IF ( skip_time_data_output_av /= 0.0 )  THEN
963                   WRITE ( io, 339 )  skip_time_data_output_av
964                ENDIF
965             ENDIF
966             IF ( netcdf_data_format > 4 )  THEN
967                WRITE ( io, 352 )  ntdim_2d_xz(av)
968             ELSE
969                WRITE ( io, 353 )
970             ENDIF
971          ENDIF
972
973          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
974             i = 1
975             slices = '/'
976             coordinates = '/'
977!
978!--          Building strings with index and coordinate informations of the
979!--          slices
980             DO  WHILE ( section(i,3) /= -9999 )
981
982                WRITE (section_chr,'(I5)')  section(i,3)
983                section_chr = ADJUSTL( section_chr )
984                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
985
986                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
987                coor_chr = ADJUSTL( coor_chr )
988                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
989
990                i = i + 1
991             ENDDO
992             IF ( av == 0 )  THEN
993                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
994                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
995                                   TRIM( coordinates )
996                IF ( skip_time_do2d_yz /= 0.0 )  THEN
997                   WRITE ( io, 339 )  skip_time_do2d_yz
998                ENDIF
999             ELSE
1000                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1001                                   TRIM( begin_chr ), averaging_interval, &
1002                                   dt_averaging_input, 'i', TRIM( slices ), &
1003                                   TRIM( coordinates )
1004                IF ( skip_time_data_output_av /= 0.0 )  THEN
1005                   WRITE ( io, 339 )  skip_time_data_output_av
1006                ENDIF
1007             ENDIF
1008             IF ( netcdf_data_format > 4 )  THEN
1009                WRITE ( io, 352 )  ntdim_2d_yz(av)
1010             ELSE
1011                WRITE ( io, 353 )
1012             ENDIF
1013          ENDIF
1014
1015       ENDIF
1016
1017    ENDDO
1018
1019!
1020!-- 3d-arrays
1021    DO  av = 0, 1
1022
1023       i = 1
1024       do3d_chr = ''
1025       DO  WHILE ( do3d(av,i) /= ' ' )
1026
1027          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1028          i = i + 1
1029
1030       ENDDO
1031
1032       IF ( do3d_chr /= '' )  THEN
1033          IF ( av == 0 )  THEN
1034             WRITE ( io, 336 )  ''
1035          ELSE
1036             WRITE ( io, 336 )  '(time-averaged)'
1037          ENDIF
1038
1039          output_format = ''
1040          IF ( netcdf_output )  THEN
1041             output_format = output_format_netcdf
1042          ENDIF
1043          IF ( avs_output )  THEN
1044             IF ( netcdf_output )  THEN
1045                output_format = TRIM( output_format_netcdf ) // ' and avs'
1046             ELSE
1047                output_format = 'avs'
1048             ENDIF
1049          ENDIF
1050          WRITE ( io, 344 )  output_format
1051
1052          IF ( do3d_at_begin )  THEN
1053             begin_chr = 'and at the start'
1054          ELSE
1055             begin_chr = ''
1056          ENDIF
1057          IF ( av == 0 )  THEN
1058             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1059                                zu(nz_do3d), nz_do3d
1060          ELSE
1061             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1062                                TRIM( begin_chr ), averaging_interval, &
1063                                dt_averaging_input, zu(nz_do3d), nz_do3d
1064          ENDIF
1065
1066          IF ( netcdf_data_format > 4 )  THEN
1067             WRITE ( io, 352 )  ntdim_3d(av)
1068          ELSE
1069             WRITE ( io, 353 )
1070          ENDIF
1071
1072          IF ( do3d_compress )  THEN
1073             do3d_chr = ''
1074             i = 1
1075             DO WHILE ( do3d(av,i) /= ' ' )
1076
1077                SELECT CASE ( do3d(av,i) )
1078                   CASE ( 'u' )
1079                      j = 1
1080                   CASE ( 'v' )
1081                      j = 2
1082                   CASE ( 'w' )
1083                      j = 3
1084                   CASE ( 'p' )
1085                      j = 4
1086                   CASE ( 'pt' )
1087                      j = 5
1088                END SELECT
1089                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1090                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1091                           ':' // prec // ','
1092                i = i + 1
1093
1094             ENDDO
1095             WRITE ( io, 338 )  do3d_chr
1096
1097          ENDIF
1098
1099          IF ( av == 0 )  THEN
1100             IF ( skip_time_do3d /= 0.0 )  THEN
1101                WRITE ( io, 339 )  skip_time_do3d
1102             ENDIF
1103          ELSE
1104             IF ( skip_time_data_output_av /= 0.0 )  THEN
1105                WRITE ( io, 339 )  skip_time_data_output_av
1106             ENDIF
1107          ENDIF
1108
1109       ENDIF
1110
1111    ENDDO
1112
1113!
1114!-- masked arrays
1115    IF ( masks > 0 )  WRITE ( io, 345 )  &
1116         mask_scale_x, mask_scale_y, mask_scale_z
1117    DO  mid = 1, masks
1118       DO  av = 0, 1
1119
1120          i = 1
1121          domask_chr = ''
1122          DO  WHILE ( domask(mid,av,i) /= ' ' )
1123             domask_chr = TRIM( domask_chr ) // ' ' //  &
1124                          TRIM( domask(mid,av,i) ) // ','
1125             i = i + 1
1126          ENDDO
1127
1128          IF ( domask_chr /= '' )  THEN
1129             IF ( av == 0 )  THEN
1130                WRITE ( io, 346 )  '', mid
1131             ELSE
1132                WRITE ( io, 346 )  ' (time-averaged)', mid
1133             ENDIF
1134
1135             output_format = ' '
1136             IF ( netcdf_output )  THEN
1137                output_format = output_format_netcdf
1138             ENDIF
1139!--          Parallel output not implemented for mask data, hence
1140!--          output_format must be adjusted.
1141             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1142             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1143             WRITE ( io, 344 )  output_format
1144
1145             IF ( av == 0 )  THEN
1146                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1147             ELSE
1148                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1149                                   averaging_interval, dt_averaging_input
1150             ENDIF
1151
1152             IF ( av == 0 )  THEN
1153                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1154                   WRITE ( io, 339 )  skip_time_domask(mid)
1155                ENDIF
1156             ELSE
1157                IF ( skip_time_data_output_av /= 0.0 )  THEN
1158                   WRITE ( io, 339 )  skip_time_data_output_av
1159                ENDIF
1160             ENDIF
1161!
1162!--          output locations
1163             DO  dim = 1, 3
1164                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1165                   count = 0
1166                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1167                      count = count + 1
1168                   ENDDO
1169                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1170                                      mask(mid,dim,:count)
1171                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1172                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1173                         mask_loop(mid,dim,3) == 0.0 )  THEN
1174                   WRITE ( io, 350 )  dir(dim), dir(dim)
1175                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1176                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1177                                      mask_loop(mid,dim,1:2)
1178                ELSE
1179                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1180                                      mask_loop(mid,dim,1:3)
1181                ENDIF
1182             ENDDO
1183          ENDIF
1184
1185       ENDDO
1186    ENDDO
1187
1188!
1189!-- Timeseries
1190    IF ( dt_dots /= 9999999.9 )  THEN
1191       WRITE ( io, 340 )
1192
1193       output_format = ''
1194       IF ( netcdf_output )  THEN
1195          output_format = output_format_netcdf
1196       ENDIF
1197       WRITE ( io, 344 )  output_format
1198       WRITE ( io, 341 )  dt_dots
1199    ENDIF
1200
1201#if defined( __dvrp_graphics )
1202!
1203!-- Dvrp-output
1204    IF ( dt_dvrp /= 9999999.9 )  THEN
1205       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1206                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1207       i = 1
1208       l = 0
1209       m = 0
1210       DO WHILE ( mode_dvrp(i) /= ' ' )
1211          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1212             READ ( mode_dvrp(i), '(10X,I2)' )  j
1213             l = l + 1
1214             IF ( do3d(0,j) /= ' ' )  THEN
1215                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1216                                   isosurface_color(:,l)
1217             ENDIF
1218          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1219             READ ( mode_dvrp(i), '(6X,I2)' )  j
1220             m = m + 1
1221             IF ( do2d(0,j) /= ' ' )  THEN
1222                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1223                                   slicer_range_limits_dvrp(:,m)
1224             ENDIF
1225          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1226             WRITE ( io, 363 )  dvrp_psize
1227             IF ( particle_dvrpsize /= 'none' )  THEN
1228                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1229                                   dvrpsize_interval
1230             ENDIF
1231             IF ( particle_color /= 'none' )  THEN
1232                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1233                                   color_interval
1234             ENDIF
1235          ENDIF
1236          i = i + 1
1237       ENDDO
1238
1239       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1240                          superelevation_y, superelevation, clip_dvrp_l, &
1241                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1242
1243       IF ( TRIM( topography ) /= 'flat' )  THEN
1244          WRITE ( io, 366 )  topography_color
1245          IF ( cluster_size > 1 )  THEN
1246             WRITE ( io, 367 )  cluster_size
1247          ENDIF
1248       ENDIF
1249
1250    ENDIF
1251#endif
1252
1253#if defined( __spectra )
1254!
1255!-- Spectra output
1256    IF ( dt_dosp /= 9999999.9 )  THEN
1257       WRITE ( io, 370 )
1258
1259       output_format = ' '
1260       IF ( netcdf_output )  THEN
1261          output_format = output_format_netcdf
1262       ENDIF
1263       WRITE ( io, 344 )  output_format
1264       WRITE ( io, 371 )  dt_dosp
1265       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1266       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1267                          ( spectra_direction(i), i = 1,10 ),  &
1268                          ( comp_spectra_level(i), i = 1,100 ), &
1269                          ( plot_spectra_level(i), i = 1,100 ), &
1270                          averaging_interval_sp, dt_averaging_input_pr
1271    ENDIF
1272#endif
1273
1274    WRITE ( io, 99 )
1275
1276!
1277!-- Physical quantities
1278    WRITE ( io, 400 )
1279
1280!
1281!-- Geostrophic parameters
1282    WRITE ( io, 410 )  omega, phi, f, fs
1283
1284!
1285!-- Other quantities
1286    WRITE ( io, 411 )  g
1287    WRITE ( io, 412 )  TRIM( reference_state )
1288    IF ( use_single_reference_value )  THEN
1289       IF ( ocean )  THEN
1290          WRITE ( io, 413 )  prho_reference
1291       ELSE
1292          WRITE ( io, 414 )  pt_reference
1293       ENDIF
1294    ENDIF
1295
1296!
1297!-- Cloud physics parameters
1298    IF ( cloud_physics )  THEN
1299       WRITE ( io, 415 )
1300       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1301       IF ( icloud_scheme == 0 )  THEN
1302          WRITE ( io, 510 ) 1.0E-6 * nc_const
1303          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1304       ENDIF
1305    ENDIF
1306
1307!-- Profile of the geostrophic wind (component ug)
1308!-- Building output strings
1309    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1310    gradients = '------'
1311    slices = '     0'
1312    coordinates = '   0.0'
1313    i = 1
1314    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1315     
1316       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1317       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1318
1319       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1320       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1321
1322       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1323       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1324
1325       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1326       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1327
1328       IF ( i == 10 )  THEN
1329          EXIT
1330       ELSE
1331          i = i + 1
1332       ENDIF
1333
1334    ENDDO
1335
1336    IF ( .NOT. large_scale_forcing )  THEN
1337       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1338                          TRIM( gradients ), TRIM( slices )
1339    ELSE
1340       WRITE ( io, 429 ) 
1341    ENDIF
1342
1343!-- Profile of the geostrophic wind (component vg)
1344!-- Building output strings
1345    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1346    gradients = '------'
1347    slices = '     0'
1348    coordinates = '   0.0'
1349    i = 1
1350    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1351
1352       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1353       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1354
1355       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1356       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1357
1358       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1359       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1360
1361       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1362       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1363
1364       IF ( i == 10 )  THEN
1365          EXIT
1366       ELSE
1367          i = i + 1
1368       ENDIF
1369 
1370    ENDDO
1371
1372    IF ( .NOT. large_scale_forcing )  THEN
1373       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1374                          TRIM( gradients ), TRIM( slices )
1375    ENDIF
1376
1377!
1378!-- Initial wind profiles
1379    IF ( u_profile(1) /= 9999999.9 )  WRITE ( io, 427 )
1380
1381!
1382!-- Initial temperature profile
1383!-- Building output strings, starting with surface temperature
1384    WRITE ( temperatures, '(F6.2)' )  pt_surface
1385    gradients = '------'
1386    slices = '     0'
1387    coordinates = '   0.0'
1388    i = 1
1389    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1390
1391       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1392       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1393
1394       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1395       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1396
1397       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1398       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1399
1400       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1401       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1402
1403       IF ( i == 10 )  THEN
1404          EXIT
1405       ELSE
1406          i = i + 1
1407       ENDIF
1408
1409    ENDDO
1410
1411    IF ( .NOT. nudging )  THEN
1412       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1413                          TRIM( gradients ), TRIM( slices )
1414    ELSE
1415       WRITE ( io, 428 ) 
1416    ENDIF
1417
1418!
1419!-- Initial humidity profile
1420!-- Building output strings, starting with surface humidity
1421    IF ( humidity  .OR.  passive_scalar )  THEN
1422       WRITE ( temperatures, '(E8.1)' )  q_surface
1423       gradients = '--------'
1424       slices = '       0'
1425       coordinates = '     0.0'
1426       i = 1
1427       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1428         
1429          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1430          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1431
1432          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1433          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1434         
1435          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1436          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1437         
1438          WRITE (coor_chr,'(F8.1,4X)')  q_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       IF ( humidity )  THEN
1450          IF ( .NOT. nudging )  THEN
1451             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1452                                TRIM( gradients ), TRIM( slices )
1453          ENDIF
1454       ELSE
1455          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1456                             TRIM( gradients ), TRIM( slices )
1457       ENDIF
1458    ENDIF
1459
1460!
1461!-- Initial salinity profile
1462!-- Building output strings, starting with surface salinity
1463    IF ( ocean )  THEN
1464       WRITE ( temperatures, '(F6.2)' )  sa_surface
1465       gradients = '------'
1466       slices = '     0'
1467       coordinates = '   0.0'
1468       i = 1
1469       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1470
1471          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1472          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1473
1474          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1475          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1476
1477          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1478          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1479
1480          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1481          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1482
1483          IF ( i == 10 )  THEN
1484             EXIT
1485          ELSE
1486             i = i + 1
1487          ENDIF
1488
1489       ENDDO
1490
1491       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1492                          TRIM( gradients ), TRIM( slices )
1493    ENDIF
1494
1495!
1496!-- Profile for the large scale vertial velocity
1497!-- Building output strings, starting with surface value
1498    IF ( large_scale_subsidence )  THEN
1499       temperatures = '   0.0'
1500       gradients = '------'
1501       slices = '     0'
1502       coordinates = '   0.0'
1503       i = 1
1504       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
1505
1506          WRITE (coor_chr,'(E10.2,7X)')  &
1507                                w_subs(subs_vertical_gradient_level_i(i))
1508          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1509
1510          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
1511          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1512
1513          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
1514          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1515
1516          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
1517          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1518
1519          IF ( i == 10 )  THEN
1520             EXIT
1521          ELSE
1522             i = i + 1
1523          ENDIF
1524
1525       ENDDO
1526
1527 
1528       IF ( .NOT. large_scale_forcing )  THEN
1529          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1530                             TRIM( gradients ), TRIM( slices )
1531        ELSE
1532           WRITE ( io, 460 ) 
1533       ENDIF
1534
1535
1536    ENDIF
1537
1538!
1539!-- Cloud physcis parameters / quantities / numerical methods
1540    WRITE ( io, 430 )
1541    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1542       WRITE ( io, 431 )
1543    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1544       WRITE ( io, 432 )
1545       IF ( radiation )  WRITE ( io, 132 )
1546       IF ( icloud_scheme == 1 )  THEN
1547          IF ( precipitation )  WRITE ( io, 133 )
1548       ELSEIF ( icloud_scheme == 0 )  THEN
1549          IF ( drizzle )  WRITE ( io, 506 )
1550          IF ( precipitation )  THEN
1551             WRITE ( io, 505 )
1552             IF ( turbulence )  WRITE ( io, 507 )
1553             IF ( ventilation_effect )  WRITE ( io, 508 )
1554             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1555          ENDIF
1556       ENDIF
1557    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1558       WRITE ( io, 433 )
1559       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1560       IF ( collision_kernel /= 'none' )  THEN
1561          WRITE ( io, 435 )  TRIM( collision_kernel )
1562          IF ( collision_kernel(6:9) == 'fast' )  THEN
1563             WRITE ( io, 436 )  radius_classes, dissipation_classes
1564          ENDIF
1565       ELSE
1566          WRITE ( io, 437 )
1567       ENDIF
1568    ENDIF
1569
1570!
1571!-- LES / turbulence parameters
1572    WRITE ( io, 450 )
1573
1574!--
1575! ... LES-constants used must still be added here
1576!--
1577    IF ( constant_diffusion )  THEN
1578       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1579                          prandtl_number
1580    ENDIF
1581    IF ( .NOT. constant_diffusion)  THEN
1582       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1583       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1584       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1585    ENDIF
1586
1587!
1588!-- Special actions during the run
1589    WRITE ( io, 470 )
1590    IF ( create_disturbances )  THEN
1591       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1592                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1593                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1594       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1595          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1596       ELSE
1597          WRITE ( io, 473 )  disturbance_energy_limit
1598       ENDIF
1599       WRITE ( io, 474 )  TRIM( random_generator )
1600    ENDIF
1601    IF ( pt_surface_initial_change /= 0.0 )  THEN
1602       WRITE ( io, 475 )  pt_surface_initial_change
1603    ENDIF
1604    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1605       WRITE ( io, 476 )  q_surface_initial_change       
1606    ENDIF
1607    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1608       WRITE ( io, 477 )  q_surface_initial_change       
1609    ENDIF
1610
1611    IF ( particle_advection )  THEN
1612!
1613!--    Particle attributes
1614       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1615                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1616                          end_time_prel, dt_sort_particles
1617       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1618       IF ( random_start_position )  WRITE ( io, 481 )
1619       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1620       WRITE ( io, 495 )  total_number_of_particles
1621       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1622          WRITE ( io, 483 )  maximum_number_of_tailpoints
1623          IF ( minimum_tailpoint_distance /= 0 )  THEN
1624             WRITE ( io, 484 )  total_number_of_tails,      &
1625                                minimum_tailpoint_distance, &
1626                                maximum_tailpoint_age
1627          ENDIF
1628       ENDIF
1629       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1630          WRITE ( io, 485 )  dt_write_particle_data
1631          output_format = ' '
1632          IF ( netcdf_output )  THEN
1633             IF ( netcdf_data_format > 1 )  THEN
1634                output_format = 'netcdf (64 bit offset) and binary'
1635             ELSE
1636                output_format = 'netcdf and binary'
1637             ENDIF
1638          ELSE
1639             output_format = 'binary'
1640          ENDIF
1641          WRITE ( io, 344 )  output_format
1642       ENDIF
1643       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1644       IF ( write_particle_statistics )  WRITE ( io, 486 )
1645
1646       WRITE ( io, 487 )  number_of_particle_groups
1647
1648       DO  i = 1, number_of_particle_groups
1649          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1650             WRITE ( io, 490 )  i, 0.0
1651             WRITE ( io, 492 )
1652          ELSE
1653             WRITE ( io, 490 )  i, radius(i)
1654             IF ( density_ratio(i) /= 0.0 )  THEN
1655                WRITE ( io, 491 )  density_ratio(i)
1656             ELSE
1657                WRITE ( io, 492 )
1658             ENDIF
1659          ENDIF
1660          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1661                             pdx(i), pdy(i), pdz(i)
1662          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1663       ENDDO
1664
1665    ENDIF
1666
1667
1668!
1669!-- Parameters of 1D-model
1670    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1671       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1672                          mixing_length_1d, dissipation_1d
1673       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1674          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1675       ENDIF
1676    ENDIF
1677
1678!
1679!-- User-defined informations
1680    CALL user_header( io )
1681
1682    WRITE ( io, 99 )
1683
1684!
1685!-- Write buffer contents to disc immediately
1686    CALL local_flush( io )
1687
1688!
1689!-- Here the FORMATs start
1690
1691 99 FORMAT (1X,78('-'))
1692100 FORMAT (/1X,'******************************',6X,42('-')/        &
1693            1X,'* ',A,' *',6X,A/                               &
1694            1X,'******************************',6X,42('-'))
1695101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1696            37X,42('-'))
1697102 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
1698            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
1699            ' Run on host:        ',A10)
1700#if defined( __parallel )
1701103 FORMAT (' Number of PEs:',10X,I6,6X,'Processor grid (x,y): (',I3,',',I3, &
1702              ')',1X,A)
1703104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1704              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1705105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1706106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1707            37X,'because the job is running on an SMP-cluster')
1708107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1709108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
1710109 FORMAT (37X,'Precursor run for coupled atmos-ocean run'/ &
1711            37X,42('-'))
1712114 FORMAT (37X,'Coupled atmosphere-ocean run following'/ &
1713            37X,'independent precursor runs'/             &
1714            37X,42('-'))
1715117 FORMAT (' Accelerator boards / node:  ',I2)
1716#endif
1717110 FORMAT (/' Numerical Schemes:'/ &
1718             ' -----------------'/)
1719111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1720112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1721            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1722113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1723                  ' or Upstream')
1724115 FORMAT ('     FFT and transpositions are overlapping')
1725116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1726                  ' or Upstream')
1727118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1728119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1729            '     translation velocity = ',A/ &
1730            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1731120 FORMAT (' Accelerator boards: ',8X,I2)
1732122 FORMAT (' --> Time differencing scheme: ',A)
1733123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1734            '     maximum damping coefficient: ',F5.3, ' 1/s')
1735129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1736130 FORMAT (' --> Additional prognostic equation for the total water content')
1737131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1738                  F6.2, ' K assumed')
1739132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1740            '     effective emissivity scheme')
1741133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1742134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1743135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1744                  A,'-cycle)'/ &
1745            '     number of grid levels:                   ',I2/ &
1746            '     Gauss-Seidel red/black iterations:       ',I2)
1747136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1748                  I3,')')
1749137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1750            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1751                  I3,')'/ &
1752            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1753                  I3,')')
1754139 FORMAT (' --> Loop optimization method: ',A)
1755140 FORMAT ('     maximum residual allowed:                ',E10.3)
1756141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1757142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1758                  'step')
1759143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1760                  'kinetic energy')
1761144 FORMAT ('     masking method is used')
1762150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1763                  'conserved'/ &
1764            '     using the ',A,' mode')
1765151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1766152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1767           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1768           /'     starting from dp_level_b =', F8.3, 'm', A /)
1769153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1770                  'prognostic equation(s) for')
1771154 FORMAT ('     the scalar(s) only')
1772155 FORMAT (' --> Nudging is used - initial profiles for u, v, pt and q ',& 
1773                  'correspond to the')
1774156 FORMAT ('     first profiles in NUDGING_DATA')
1775157 FORMAT (' --> Large scale forcing from external file (LSF_DATA) is used: ')
1776158 FORMAT ('     prescribed surfaces fluxes and geostrophic wind components')
1777200 FORMAT (//' Run time and time step information:'/ &
1778             ' ----------------------------------'/)
1779201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1780             '    CFL-factor: ',F4.2)
1781202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1782203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1783             ' End time:            ',F9.3,' s')
1784204 FORMAT ( A,F9.3,' s')
1785205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1786206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1787             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1788               '  ',F9.3,' s'/                                                    &
1789             '                                      per second of simulated tim', &
1790               'e: ',F9.3,' s')
1791207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1792250 FORMAT (//' Computational grid and domain size:'/ &
1793              ' ----------------------------------'// &
1794              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1795              ' m    dz =    ',F7.3,' m'/ &
1796              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1797              ' m  z(u) = ',F10.3,' m'/)
1798252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1799              ' factor: ',F5.3/ &
1800            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1801254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1802            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1803260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1804             ' degrees')
1805270 FORMAT (//' Topography informations:'/ &
1806              ' -----------------------'// &
1807              1X,'Topography: ',A)
1808271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1809              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1810                ' / ',I4)
1811272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1812              ' direction' / &
1813              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1814              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1815278 FORMAT (' Topography grid definition convention:'/ &
1816            ' cell edge (staggered grid points'/  &
1817            ' (u in x-direction, v in y-direction))' /)
1818279 FORMAT (' Topography grid definition convention:'/ &
1819            ' cell center (scalar grid points)' /)
1820280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1821              ' ------------------------------'// &
1822              ' Canopy mode: ', A / &
1823              ' Canopy top: ',I4 / &
1824              ' Leaf drag coefficient: ',F6.2 /)
1825281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1826              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1827282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1828283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1829              ' Height:              ',A,'  m'/ &
1830              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1831              ' Gradient:            ',A,'  m**2/m**4'/ &
1832              ' Gridpoint:           ',A)
1833               
1834300 FORMAT (//' Boundary conditions:'/ &
1835             ' -------------------'// &
1836             '                     p                    uv             ', &
1837             '                   pt'// &
1838             ' B. bound.: ',A/ &
1839             ' T. bound.: ',A)
1840301 FORMAT (/'                     ',A// &
1841             ' B. bound.: ',A/ &
1842             ' T. bound.: ',A)
1843303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1844304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1845305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1846               'computational u,v-level:'// &
1847             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1848             ' m   kappa = ',F4.2/ &
1849             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1850306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1851307 FORMAT ('       Heatflux has a random normal distribution')
1852308 FORMAT ('       Predefined surface temperature')
1853309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1854310 FORMAT (//'    1D-Model:'// &
1855             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1856311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1857312 FORMAT ('       Predefined surface humidity')
1858313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1859314 FORMAT ('       Predefined scalar value at the surface')
1860315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1861316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1862                    'atmosphere model')
1863317 FORMAT (//' Lateral boundaries:'/ &
1864            '       left/right:  ',A/    &
1865            '       north/south: ',A)
1866318 FORMAT (/'       use_cmax: ',L1 / &
1867            '       pt damping layer width = ',F8.2,' m, pt ', &
1868                    'damping factor = ',F6.4)
1869319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1870            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1871            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1872320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1873            '                                          v: ',F9.6,' m**2/s**2')
1874325 FORMAT (//' List output:'/ &
1875             ' -----------'//  &
1876            '    1D-Profiles:'/    &
1877            '       Output every             ',F8.2,' s')
1878326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1879            '       Averaging input every    ',F8.2,' s')
1880330 FORMAT (//' Data output:'/ &
1881             ' -----------'/)
1882331 FORMAT (/'    1D-Profiles:')
1883332 FORMAT (/'       ',A)
1884333 FORMAT ('       Output every             ',F8.2,' s',/ &
1885            '       Time averaged over       ',F8.2,' s'/ &
1886            '       Averaging input every    ',F8.2,' s')
1887334 FORMAT (/'    2D-Arrays',A,':')
1888335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1889            '       Output every             ',F8.2,' s  ',A/ &
1890            '       Cross sections at ',A1,' = ',A/ &
1891            '       scalar-coordinates:   ',A,' m'/)
1892336 FORMAT (/'    3D-Arrays',A,':')
1893337 FORMAT (/'       Arrays: ',A/ &
1894            '       Output every             ',F8.2,' s  ',A/ &
1895            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1896338 FORMAT ('       Compressed data output'/ &
1897            '       Decimal precision: ',A/)
1898339 FORMAT ('       No output during initial ',F8.2,' s')
1899340 FORMAT (/'    Time series:')
1900341 FORMAT ('       Output every             ',F8.2,' s'/)
1901342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1902            '       Output every             ',F8.2,' s  ',A/ &
1903            '       Time averaged over       ',F8.2,' s'/ &
1904            '       Averaging input every    ',F8.2,' s'/ &
1905            '       Cross sections at ',A1,' = ',A/ &
1906            '       scalar-coordinates:   ',A,' m'/)
1907343 FORMAT (/'       Arrays: ',A/ &
1908            '       Output every             ',F8.2,' s  ',A/ &
1909            '       Time averaged over       ',F8.2,' s'/ &
1910            '       Averaging input every    ',F8.2,' s'/ &
1911            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1912344 FORMAT ('       Output format: ',A/)
1913345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1914            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1915            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1916            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1917346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1918347 FORMAT ('       Variables: ',A/ &
1919            '       Output every             ',F8.2,' s')
1920348 FORMAT ('       Variables: ',A/ &
1921            '       Output every             ',F8.2,' s'/ &
1922            '       Time averaged over       ',F8.2,' s'/ &
1923            '       Averaging input every    ',F8.2,' s')
1924349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1925            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1926            13('       ',8(F8.2,',')/) )
1927350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1928            'all gridpoints along ',A,'-direction (default).' )
1929351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1930            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1931            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1932352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
1933353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
1934#if defined( __dvrp_graphics )
1935360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1936            '       Output every      ',F7.1,' s'/ &
1937            '       Output mode:      ',A/ &
1938            '       Host / User:      ',A,' / ',A/ &
1939            '       Directory:        ',A// &
1940            '       The sequence contains:')
1941361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1942            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1943362 FORMAT (/'       Slicer plane ',A/ &
1944            '       Slicer limits: [',F6.2,',',F6.2,']')
1945363 FORMAT (/'       Particles'/ &
1946            '          particle size:  ',F7.2,' m')
1947364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1948                       F6.2,',',F6.2,']')
1949365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1950            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1951                     ')'/ &
1952            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1953            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1954366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1955367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1956#endif
1957#if defined( __spectra )
1958370 FORMAT ('    Spectra:')
1959371 FORMAT ('       Output every ',F7.1,' s'/)
1960372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1961            '       Directions: ', 10(A5,',')/                         &
1962            '       height levels  k = ', 20(I3,',')/                  &
1963            '                          ', 20(I3,',')/                  &
1964            '                          ', 20(I3,',')/                  &
1965            '                          ', 20(I3,',')/                  &
1966            '                          ', 19(I3,','),I3,'.'/           &
1967            '       height levels selected for standard plot:'/        &
1968            '                      k = ', 20(I3,',')/                  &
1969            '                          ', 20(I3,',')/                  &
1970            '                          ', 20(I3,',')/                  &
1971            '                          ', 20(I3,',')/                  &
1972            '                          ', 19(I3,','),I3,'.'/           &
1973            '       Time averaged over ', F7.1, ' s,' /                &
1974            '       Profiles for the time averaging are taken every ', &
1975                    F6.1,' s')
1976#endif
1977400 FORMAT (//' Physical quantities:'/ &
1978              ' -------------------'/)
1979410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1980            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1981            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1982            '                            f*    = ',F9.6,' 1/s')
1983411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1984412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
1985413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1986414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
1987415 FORMAT (/'    Cloud physics parameters:'/ &
1988             '    ------------------------'/)
1989416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1990            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1991            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1992            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1993            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1994420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1995            '       Height:        ',A,'  m'/ &
1996            '       Temperature:   ',A,'  K'/ &
1997            '       Gradient:      ',A,'  K/100m'/ &
1998            '       Gridpoint:     ',A)
1999421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2000            '       Height:      ',A,'  m'/ &
2001            '       Humidity:    ',A,'  kg/kg'/ &
2002            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2003            '       Gridpoint:   ',A)
2004422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2005            '       Height:                  ',A,'  m'/ &
2006            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2007            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2008            '       Gridpoint:               ',A)
2009423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2010            '       Height:      ',A,'  m'/ &
2011            '       ug:          ',A,'  m/s'/ &
2012            '       Gradient:    ',A,'  1/100s'/ &
2013            '       Gridpoint:   ',A)
2014424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2015            '       Height:      ',A,'  m'/ &
2016            '       vg:          ',A,'  m/s'/ &
2017            '       Gradient:    ',A,'  1/100s'/ &
2018            '       Gridpoint:   ',A)
2019425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2020            '       Height:     ',A,'  m'/ &
2021            '       Salinity:   ',A,'  psu'/ &
2022            '       Gradient:   ',A,'  psu/100m'/ &
2023            '       Gridpoint:  ',A)
2024426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2025            '       Height:      ',A,'  m'/ &
2026            '       w_subs:      ',A,'  m/s'/ &
2027            '       Gradient:    ',A,'  (m/s)/100m'/ &
2028            '       Gridpoint:   ',A)
2029427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2030                  ' profiles')
2031428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2032             '    NUDGING_DATA')
2033429 FORMAT (/'    Geostrophic wind profiles (ug, vg) are are taken from file '/ &
2034             '    LSF_DATA')
2035430 FORMAT (//' Cloud physics quantities / methods:'/ &
2036              ' ----------------------------------'/)
2037431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2038                 'on)')
2039432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2040            '    total water content is used.'/ &
2041            '    Condensation is parameterized via 0% - or 100% scheme.')
2042433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2043                 'icle model')
2044434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2045                 ' droplets < 1.0E-6 m')
2046435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2047436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2048                    'are used'/ &
2049            '          number of radius classes:       ',I3,'    interval ', &
2050                       '[1.0E-6,2.0E-4] m'/ &
2051            '          number of dissipation classes:   ',I2,'    interval ', &
2052                       '[0,1000] cm**2/s**3')
2053437 FORMAT ('    Droplet collision is switched off')
2054450 FORMAT (//' LES / Turbulence quantities:'/ &
2055              ' ---------------------------'/)
2056451 FORMAT ('    Diffusion coefficients are constant:'/ &
2057            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2058453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2059454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2060455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2061460 FORMAT (/'    Profiles for large scale vertical velocity are '/ &
2062             '    taken from file LSF_DATA')
2063470 FORMAT (//' Actions during the simulation:'/ &
2064              ' -----------------------------'/)
2065471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2066            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2067            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2068            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2069472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2070                 ' to i/j =',I4)
2071473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2072                 1X,F5.3, ' m**2/s**2')
2073474 FORMAT ('    Random number generator used    : ',A/)
2074475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2075                 'respectively, if'/ &
2076            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2077                 ' 3D-simulation'/)
2078476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2079                 'respectively, if the'/ &
2080            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2081                 ' the 3D-simulation'/)
2082477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2083                 'respectively, if the'/ &
2084            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2085                 ' the 3D-simulation'/)
2086480 FORMAT ('    Particles:'/ &
2087            '    ---------'// &
2088            '       Particle advection is active (switched on at t = ', F7.1, &
2089                    ' s)'/ &
2090            '       Start of new particle generations every  ',F6.1,' s'/ &
2091            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2092            '                            bottom:     ', A, ' top:         ', A/&
2093            '       Maximum particle age:                 ',F9.1,' s'/ &
2094            '       Advection stopped at t = ',F9.1,' s'/ &
2095            '       Particles are sorted every ',F9.1,' s'/)
2096481 FORMAT ('       Particles have random start positions'/)
2097482 FORMAT ('          Particles are advected only horizontally'/)
2098483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2099484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2100            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2101            '            Maximum age of the end of the tail:  ',F8.2,' s')
2102485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2103486 FORMAT ('       Particle statistics are written on file'/)
2104487 FORMAT ('       Number of particle groups: ',I2/)
2105488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2106            '          minimum timestep for advection: ', F7.5/)
2107489 FORMAT ('       Number of particles simultaneously released at each ', &
2108                    'point: ', I5/)
2109490 FORMAT ('       Particle group ',I2,':'/ &
2110            '          Particle radius: ',E10.3, 'm')
2111491 FORMAT ('          Particle inertia is activated'/ &
2112            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2113492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2114493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2115            '                                         y:',F8.1,' - ',F8.1,' m'/&
2116            '                                         z:',F8.1,' - ',F8.1,' m'/&
2117            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2118                       ' m  dz = ',F8.1,' m'/)
2119494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2120                    F8.2,' s'/)
2121495 FORMAT ('       Number of particles in total domain: ',I10/)
2122500 FORMAT (//' 1D-Model parameters:'/                           &
2123              ' -------------------'//                           &
2124            '    Simulation time:                   ',F8.1,' s'/ &
2125            '    Run-controll output every:         ',F8.1,' s'/ &
2126            '    Vertical profile output every:     ',F8.1,' s'/ &
2127            '    Mixing length calculation:         ',A/         &
2128            '    Dissipation calculation:           ',A/)
2129502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2130503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2131504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2132505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2133506 FORMAT ('    Drizzle parameterization via Stokes law')
2134507 FORMAT ('    Turbulence effects on precipitation process')
2135508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2136509 FORMAT ('    Slope limiter used for sedimentation process')
2137510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2138511 FORMAT ('        Sedimentation Courant number:                  '/&
2139            '                               C_s   = ',F3.1,'        ')
2140
2141 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.