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

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

last commit documented

  • Property svn:keywords set to Id
File size: 80.6 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 1329 2014-03-21 11:09:15Z heinze $
27!
28! 1327 2014-03-21 11:00:16Z raasch
29! parts concerning iso2d and avs output removed,
30! -netcdf output queries
31!
32! 1324 2014-03-21 09:13:16Z suehring
33! Bugfix: module spectrum added
34!
35! 1322 2014-03-20 16:38:49Z raasch
36! REAL functions provided with KIND-attribute,
37! some REAL constants defined as wp-kind
38!
39! 1320 2014-03-20 08:40:49Z raasch
40! ONLY-attribute added to USE-statements,
41! kind-parameters added to all INTEGER and REAL declaration statements,
42! kinds are defined in new module kinds,
43! revision history before 2012 removed,
44! comment fields (!:) to be used for variable explanations added to
45! all variable declaration statements
46!
47! 1308 2014-03-13 14:58:42Z fricke
48! output of the fixed number of output time levels
49! output_format adjusted for masked data if netcdf_data_format > 5
50!
51! 1299 2014-03-06 13:15:21Z heinze
52! output for using large_scale subsidence in combination
53! with large_scale_forcing
54! reformatting, more detailed explanations
55!
56! 1241 2013-10-30 11:36:58Z heinze
57! output for nudging + large scale forcing from external file
58!
59! 1216 2013-08-26 09:31:42Z raasch
60! output for transpose_compute_overlap
61!
62! 1212 2013-08-15 08:46:27Z raasch
63! output for poisfft_hybrid removed
64!
65! 1179 2013-06-14 05:57:58Z raasch
66! output of reference_state, use_reference renamed use_single_reference_value
67!
68! 1159 2013-05-21 11:58:22Z fricke
69! +use_cmax
70!
71! 1115 2013-03-26 18:16:16Z hoffmann
72! descriptions for Seifert-Beheng-cloud-physics-scheme added
73!
74! 1111 2013-03-08 23:54:10Z raasch
75! output of accelerator board information
76! ibc_p_b = 2 removed
77!
78! 1108 2013-03-05 07:03:32Z raasch
79! bugfix for r1106
80!
81! 1106 2013-03-04 05:31:38Z raasch
82! some format changes for coupled runs
83!
84! 1092 2013-02-02 11:24:22Z raasch
85! unused variables removed
86!
87! 1036 2012-10-22 13:43:42Z raasch
88! code put under GPL (PALM 3.9)
89!
90! 1031 2012-10-19 14:35:30Z raasch
91! output of netCDF data format modified
92!
93! 1015 2012-09-27 09:23:24Z raasch
94! output of Aajustment of mixing length to the Prandtl mixing length at first
95! grid point above ground removed
96!
97! 1003 2012-09-14 14:35:53Z raasch
98! output of information about equal/unequal subdomain size removed
99!
100! 1001 2012-09-13 14:08:46Z raasch
101! all actions concerning leapfrog- and upstream-spline-scheme removed
102!
103! 978 2012-08-09 08:28:32Z fricke
104! -km_damp_max, outflow_damping_width
105! +pt_damping_factor, pt_damping_width
106! +z0h
107!
108! 964 2012-07-26 09:14:24Z raasch
109! output of profil-related quantities removed
110!
111! 940 2012-07-09 14:31:00Z raasch
112! Output in case of simulations for pure neutral stratification (no pt-equation
113! solved)
114!
115! 927 2012-06-06 19:15:04Z raasch
116! output of masking_method for mg-solver
117!
118! 868 2012-03-28 12:21:07Z raasch
119! translation velocity in Galilean transformation changed to 0.6 * ug
120!
121! 833 2012-02-22 08:55:55Z maronga
122! Adjusted format for leaf area density
123!
124! 828 2012-02-21 12:00:36Z raasch
125! output of dissipation_classes + radius_classes
126!
127! 825 2012-02-19 03:03:44Z raasch
128! Output of cloud physics parameters/quantities complemented and restructured
129!
130! Revision 1.1  1997/08/11 06:17:20  raasch
131! Initial revision
132!
133!
134! Description:
135! ------------
136! Writing a header with all important informations about the actual run.
137! This subroutine is called three times, two times at the beginning
138! (writing information on files RUN_CONTROL and HEADER) and one time at the
139! end of the run, then writing additional information about CPU-usage on file
140! header.
141!-----------------------------------------------------------------------------!
142
143    USE arrays_3d,                                                             &
144        ONLY:  lad, pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
145       
146    USE control_parameters
147       
148    USE cloud_parameters,                                                      &
149        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
150               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
151       
152    USE cpulog,                                                                &
153        ONLY:  log_point_s
154       
155    USE dvrp_variables,                                                        &
156        ONLY:  use_seperate_pe_for_dvrp_output
157       
158    USE grid_variables,                                                        &
159        ONLY:  dx, dy
160       
161    USE indices,                                                               &
162        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
163               nys_mg, nzt, nzt_mg
164       
165    USE kinds
166   
167    USE model_1d,                                                              &
168        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
169       
170    USE particle_attributes,                                                   &
171        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
172               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
173               dt_sort_particles, dt_write_particle_data, end_time_prel,       &
174               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
175               minimum_tailpoint_distance, number_of_particle_groups,          &
176               particle_advection, particle_advection_start,                   &
177               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
178               pst, radius, radius_classes, random_start_position,             &
179               total_number_of_particles, use_particle_tails,                  &
180               use_sgs_for_particles, total_number_of_tails,                   &
181               vertical_particle_advection, write_particle_statistics
182       
183    USE pegrid
184   
185    USE spectrum,                                                              &
186        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
187               spectra_direction
188
189    IMPLICIT NONE
190
191    CHARACTER (LEN=1)  ::  prec                !:
192   
193    CHARACTER (LEN=2)  ::  do2d_mode           !:
194   
195    CHARACTER (LEN=5)  ::  section_chr         !:
196   
197    CHARACTER (LEN=10) ::  coor_chr            !:
198    CHARACTER (LEN=10) ::  host_chr            !:
199   
200    CHARACTER (LEN=16) ::  begin_chr           !:
201   
202    CHARACTER (LEN=26) ::  ver_rev             !:
203   
204    CHARACTER (LEN=40) ::  output_format       !:
205   
206    CHARACTER (LEN=70) ::  char1               !:
207    CHARACTER (LEN=70) ::  char2               !:
208    CHARACTER (LEN=70) ::  dopr_chr            !:
209    CHARACTER (LEN=70) ::  do2d_xy             !:
210    CHARACTER (LEN=70) ::  do2d_xz             !:
211    CHARACTER (LEN=70) ::  do2d_yz             !:
212    CHARACTER (LEN=70) ::  do3d_chr            !:
213    CHARACTER (LEN=70) ::  domask_chr          !:
214    CHARACTER (LEN=70) ::  run_classification  !:
215   
216    CHARACTER (LEN=85) ::  roben               !:
217    CHARACTER (LEN=85) ::  runten              !:
218   
219    CHARACTER (LEN=86) ::  coordinates         !:
220    CHARACTER (LEN=86) ::  gradients           !:
221    CHARACTER (LEN=86) ::  learde              !:
222    CHARACTER (LEN=86) ::  slices              !:
223    CHARACTER (LEN=86) ::  temperatures        !:
224    CHARACTER (LEN=86) ::  ugcomponent         !:
225    CHARACTER (LEN=86) ::  vgcomponent         !:
226
227    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
228
229    INTEGER(iwp) ::  av        !:
230    INTEGER(iwp) ::  bh        !:
231    INTEGER(iwp) ::  blx       !:
232    INTEGER(iwp) ::  bly       !:
233    INTEGER(iwp) ::  bxl       !:
234    INTEGER(iwp) ::  bxr       !:
235    INTEGER(iwp) ::  byn       !:
236    INTEGER(iwp) ::  bys       !:
237    INTEGER(iwp) ::  ch        !:
238    INTEGER(iwp) ::  count     !:
239    INTEGER(iwp) ::  cwx       !:
240    INTEGER(iwp) ::  cwy       !:
241    INTEGER(iwp) ::  cxl       !:
242    INTEGER(iwp) ::  cxr       !:
243    INTEGER(iwp) ::  cyn       !:
244    INTEGER(iwp) ::  cys       !:
245    INTEGER(iwp) ::  dim       !:
246    INTEGER(iwp) ::  i         !:
247    INTEGER(iwp) ::  io        !:
248    INTEGER(iwp) ::  j         !:
249    INTEGER(iwp) ::  l         !:
250    INTEGER(iwp) ::  ll        !:
251    INTEGER(iwp) ::  mpi_type  !:
252   
253    REAL(wp) ::  cpuseconds_per_simulated_second  !:
254
255!
256!-- Open the output file. At the end of the simulation, output is directed
257!-- to unit 19.
258    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
259         .NOT. simulated_time_at_begin /= simulated_time )  THEN
260       io = 15   !  header output on file RUN_CONTROL
261    ELSE
262       io = 19   !  header output on file HEADER
263    ENDIF
264    CALL check_open( io )
265
266!
267!-- At the end of the run, output file (HEADER) will be rewritten with
268!-- new informations
269    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
270
271!
272!-- Determine kind of model run
273    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
274       run_classification = '3D - restart run'
275    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
276       run_classification = '3D - run with cyclic fill of 3D - prerun data'
277    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
278       run_classification = '3D - run without 1D - prerun'
279    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
280       run_classification = '3D - run with 1D - prerun'
281    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
282       run_classification = '3D - run initialized by user'
283    ELSE
284       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
285       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
286    ENDIF
287    IF ( ocean )  THEN
288       run_classification = 'ocean - ' // run_classification
289    ELSE
290       run_classification = 'atmosphere - ' // run_classification
291    ENDIF
292
293!
294!-- Run-identification, date, time, host
295    host_chr = host(1:10)
296    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
297    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
298    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
299#if defined( __mpi2 )
300       mpi_type = 2
301#else
302       mpi_type = 1
303#endif
304       WRITE ( io, 101 )  mpi_type, coupling_mode
305    ENDIF
306#if defined( __parallel )
307    IF ( coupling_start_time /= 0.0 )  THEN
308       IF ( coupling_start_time > simulated_time_at_begin )  THEN
309          WRITE ( io, 109 )
310       ELSE
311          WRITE ( io, 114 )
312       ENDIF
313    ENDIF
314#endif
315    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
316                       ADJUSTR( host_chr )
317#if defined( __parallel )
318    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
319       char1 = 'calculated'
320    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
321               host(1:2) == 'lc' )  .AND.                          &
322             npex == -1  .AND.  pdims(2) == 1 )  THEN
323       char1 = 'forced'
324    ELSE
325       char1 = 'predefined'
326    ENDIF
327    IF ( threads_per_task == 1 )  THEN
328       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
329    ELSE
330       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
331                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
332    ENDIF
333    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
334    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
335           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
336         npex == -1  .AND.  pdims(2) == 1 )                      &
337    THEN
338       WRITE ( io, 106 )
339    ELSEIF ( pdims(2) == 1 )  THEN
340       WRITE ( io, 107 )  'x'
341    ELSEIF ( pdims(1) == 1 )  THEN
342       WRITE ( io, 107 )  'y'
343    ENDIF
344    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
345    IF ( numprocs /= maximum_parallel_io_streams )  THEN
346       WRITE ( io, 108 )  maximum_parallel_io_streams
347    ENDIF
348#else
349    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
350#endif
351    WRITE ( io, 99 )
352
353!
354!-- Numerical schemes
355    WRITE ( io, 110 )
356    IF ( psolver(1:7) == 'poisfft' )  THEN
357       WRITE ( io, 111 )  TRIM( fft_method )
358       IF ( transpose_compute_overlap )  WRITE( io, 115 )
359    ELSEIF ( psolver == 'sor' )  THEN
360       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
361    ELSEIF ( psolver == 'multigrid' )  THEN
362       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
363       IF ( mg_cycles == -1 )  THEN
364          WRITE ( io, 140 )  residual_limit
365       ELSE
366          WRITE ( io, 141 )  mg_cycles
367       ENDIF
368       IF ( mg_switch_to_pe0_level == 0 )  THEN
369          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
370                             nzt_mg(1)
371       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
372          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
373                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
374                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
375                             nzt_mg(mg_switch_to_pe0_level),    &
376                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
377                             nzt_mg(1)
378       ENDIF
379       IF ( masking_method )  WRITE ( io, 144 )
380    ENDIF
381    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
382    THEN
383       WRITE ( io, 142 )
384    ENDIF
385
386    IF ( momentum_advec == 'pw-scheme' )  THEN
387       WRITE ( io, 113 )
388    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
389       WRITE ( io, 503 )
390    ENDIF
391    IF ( scalar_advec == 'pw-scheme' )  THEN
392       WRITE ( io, 116 )
393    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
394       WRITE ( io, 504 )
395    ELSE
396       WRITE ( io, 118 )
397    ENDIF
398
399    WRITE ( io, 139 )  TRIM( loop_optimization )
400
401    IF ( galilei_transformation )  THEN
402       IF ( use_ug_for_galilei_tr )  THEN
403          char1 = '0.6 * geostrophic wind'
404       ELSE
405          char1 = 'mean wind in model domain'
406       ENDIF
407       IF ( simulated_time_at_begin == simulated_time )  THEN
408          char2 = 'at the start of the run'
409       ELSE
410          char2 = 'at the end of the run'
411       ENDIF
412       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
413                          advected_distance_x/1000.0, advected_distance_y/1000.0
414    ENDIF
415    WRITE ( io, 122 )  timestep_scheme
416    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
417    IF ( rayleigh_damping_factor /= 0.0 )  THEN
418       IF ( .NOT. ocean )  THEN
419          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
420               rayleigh_damping_factor
421       ELSE
422          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
423               rayleigh_damping_factor
424       ENDIF
425    ENDIF
426    IF ( neutral )  WRITE ( io, 131 )  pt_surface
427    IF ( humidity )  THEN
428       IF ( .NOT. cloud_physics )  THEN
429          WRITE ( io, 129 )
430       ELSE
431          WRITE ( io, 130 )
432       ENDIF
433    ENDIF
434    IF ( passive_scalar )  WRITE ( io, 134 )
435    IF ( conserve_volume_flow )  THEN
436       WRITE ( io, 150 )  conserve_volume_flow_mode
437       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
438          WRITE ( io, 151 )  u_bulk, v_bulk
439       ENDIF
440    ELSEIF ( dp_external )  THEN
441       IF ( dp_smooth )  THEN
442          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
443       ELSE
444          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
445       ENDIF
446    ENDIF
447    IF ( large_scale_subsidence )  THEN
448        WRITE ( io, 153 )
449        WRITE ( io, 154 )
450    ENDIF
451    IF ( nudging )  THEN
452        WRITE ( io, 155 )
453        WRITE ( io, 156 )
454    ENDIF
455    IF ( large_scale_forcing )  THEN
456        WRITE ( io, 157 )
457        WRITE ( io, 158 )
458    ENDIF
459    WRITE ( io, 99 )
460
461!
462!-- Runtime and timestep informations
463    WRITE ( io, 200 )
464    IF ( .NOT. dt_fixed )  THEN
465       WRITE ( io, 201 )  dt_max, cfl_factor
466    ELSE
467       WRITE ( io, 202 )  dt
468    ENDIF
469    WRITE ( io, 203 )  simulated_time_at_begin, end_time
470
471    IF ( time_restart /= 9999999.9_wp  .AND. &
472         simulated_time_at_begin == simulated_time )  THEN
473       IF ( dt_restart == 9999999.9_wp )  THEN
474          WRITE ( io, 204 )  ' Restart at:       ',time_restart
475       ELSE
476          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
477       ENDIF
478    ENDIF
479
480    IF ( simulated_time_at_begin /= simulated_time )  THEN
481       i = MAX ( log_point_s(10)%counts, 1 )
482       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
483          cpuseconds_per_simulated_second = 0.0
484       ELSE
485          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
486                                            ( simulated_time -    &
487                                              simulated_time_at_begin )
488       ENDIF
489       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
490                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
491                          cpuseconds_per_simulated_second
492       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
493          IF ( dt_restart == 9999999.9_wp )  THEN
494             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
495          ELSE
496             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
497          ENDIF
498       ENDIF
499    ENDIF
500
501
502!
503!-- Start time for coupled runs, if independent precursor runs for atmosphere
504!-- and ocean are used or have been used. In this case, coupling_start_time
505!-- defines the time when the coupling is switched on.
506    IF ( coupling_start_time /= 0.0 )  THEN
507       WRITE ( io, 207 )  coupling_start_time
508    ENDIF
509
510!
511!-- Computational grid
512    IF ( .NOT. ocean )  THEN
513       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
514       IF ( dz_stretch_level_index < nzt+1 )  THEN
515          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
516                             dz_stretch_factor, dz_max
517       ENDIF
518    ELSE
519       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
520       IF ( dz_stretch_level_index > 0 )  THEN
521          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
522                             dz_stretch_factor, dz_max
523       ENDIF
524    ENDIF
525    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
526                       MIN( nnz+2, nzt+2 )
527    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
528
529!
530!-- Topography
531    WRITE ( io, 270 )  topography
532    SELECT CASE ( TRIM( topography ) )
533
534       CASE ( 'flat' )
535          ! no actions necessary
536
537       CASE ( 'single_building' )
538          blx = INT( building_length_x / dx )
539          bly = INT( building_length_y / dy )
540          bh  = INT( building_height / dz )
541
542          IF ( building_wall_left == 9999999.9_wp )  THEN
543             building_wall_left = ( nx + 1 - blx ) / 2 * dx
544          ENDIF
545          bxl = INT ( building_wall_left / dx + 0.5 )
546          bxr = bxl + blx
547
548          IF ( building_wall_south == 9999999.9_wp )  THEN
549             building_wall_south = ( ny + 1 - bly ) / 2 * dy
550          ENDIF
551          bys = INT ( building_wall_south / dy + 0.5 )
552          byn = bys + bly
553
554          WRITE ( io, 271 )  building_length_x, building_length_y, &
555                             building_height, bxl, bxr, bys, byn
556
557       CASE ( 'single_street_canyon' )
558          ch  = NINT( canyon_height / dz )
559          IF ( canyon_width_x /= 9999999.9_wp )  THEN
560!
561!--          Street canyon in y direction
562             cwx = NINT( canyon_width_x / dx )
563             IF ( canyon_wall_left == 9999999.9_wp )  THEN
564                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
565             ENDIF
566             cxl = NINT( canyon_wall_left / dx )
567             cxr = cxl + cwx
568             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
569
570          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
571!
572!--          Street canyon in x direction
573             cwy = NINT( canyon_width_y / dy )
574             IF ( canyon_wall_south == 9999999.9_wp )  THEN
575                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
576             ENDIF
577             cys = NINT( canyon_wall_south / dy )
578             cyn = cys + cwy
579             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
580          ENDIF
581
582    END SELECT
583
584    IF ( TRIM( topography ) /= 'flat' )  THEN
585       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
586          IF ( TRIM( topography ) == 'single_building' .OR.  &
587               TRIM( topography ) == 'single_street_canyon' )  THEN
588             WRITE ( io, 278 )
589          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
590             WRITE ( io, 279 )
591          ENDIF
592       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
593          WRITE ( io, 278 )
594       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
595          WRITE ( io, 279 )
596       ENDIF
597    ENDIF
598
599    IF ( plant_canopy )  THEN
600
601       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
602       IF ( passive_scalar )  THEN
603          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
604                            leaf_surface_concentration
605       ENDIF
606
607!
608!--    Heat flux at the top of vegetation
609       WRITE ( io, 282 ) cthf
610
611!
612!--    Leaf area density profile
613!--    Building output strings, starting with surface value
614       WRITE ( learde, '(F6.4)' )  lad_surface
615       gradients = '------'
616       slices = '     0'
617       coordinates = '   0.0'
618       i = 1
619       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
620
621          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
622          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
623
624          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
625          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
626
627          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
628          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
629
630          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
631          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
632
633          i = i + 1
634       ENDDO
635
636       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
637                          TRIM( gradients ), TRIM( slices )
638
639    ENDIF
640
641!
642!-- Boundary conditions
643    IF ( ibc_p_b == 0 )  THEN
644       runten = 'p(0)     = 0      |'
645    ELSEIF ( ibc_p_b == 1 )  THEN
646       runten = 'p(0)     = p(1)   |'
647    ENDIF
648    IF ( ibc_p_t == 0 )  THEN
649       roben  = 'p(nzt+1) = 0      |'
650    ELSE
651       roben  = 'p(nzt+1) = p(nzt) |'
652    ENDIF
653
654    IF ( ibc_uv_b == 0 )  THEN
655       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
656    ELSE
657       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
658    ENDIF
659    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
660       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
661    ELSEIF ( ibc_uv_t == 0 )  THEN
662       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
663    ELSE
664       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
665    ENDIF
666
667    IF ( ibc_pt_b == 0 )  THEN
668       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
669    ELSEIF ( ibc_pt_b == 1 )  THEN
670       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
671    ELSEIF ( ibc_pt_b == 2 )  THEN
672       runten = TRIM( runten ) // ' pt(0) = from coupled model'
673    ENDIF
674    IF ( ibc_pt_t == 0 )  THEN
675       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
676    ELSEIF( ibc_pt_t == 1 )  THEN
677       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
678    ELSEIF( ibc_pt_t == 2 )  THEN
679       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
680
681    ENDIF
682
683    WRITE ( io, 300 )  runten, roben
684
685    IF ( .NOT. constant_diffusion )  THEN
686       IF ( ibc_e_b == 1 )  THEN
687          runten = 'e(0)     = e(1)'
688       ELSE
689          runten = 'e(0)     = e(1) = (u*/0.1)**2'
690       ENDIF
691       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
692
693       WRITE ( io, 301 )  'e', runten, roben       
694
695    ENDIF
696
697    IF ( ocean )  THEN
698       runten = 'sa(0)    = sa(1)'
699       IF ( ibc_sa_t == 0 )  THEN
700          roben =  'sa(nzt+1) = sa_surface'
701       ELSE
702          roben =  'sa(nzt+1) = sa(nzt)'
703       ENDIF
704       WRITE ( io, 301 ) 'sa', runten, roben
705    ENDIF
706
707    IF ( humidity )  THEN
708       IF ( ibc_q_b == 0 )  THEN
709          runten = 'q(0)     = q_surface'
710       ELSE
711          runten = 'q(0)     = q(1)'
712       ENDIF
713       IF ( ibc_q_t == 0 )  THEN
714          roben =  'q(nzt)   = q_top'
715       ELSE
716          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
717       ENDIF
718       WRITE ( io, 301 ) 'q', runten, roben
719    ENDIF
720
721    IF ( passive_scalar )  THEN
722       IF ( ibc_q_b == 0 )  THEN
723          runten = 's(0)     = s_surface'
724       ELSE
725          runten = 's(0)     = s(1)'
726       ENDIF
727       IF ( ibc_q_t == 0 )  THEN
728          roben =  's(nzt)   = s_top'
729       ELSE
730          roben =  's(nzt)   = s(nzt-1) + ds/dz'
731       ENDIF
732       WRITE ( io, 301 ) 's', runten, roben
733    ENDIF
734
735    IF ( use_surface_fluxes )  THEN
736       WRITE ( io, 303 )
737       IF ( constant_heatflux )  THEN
738          IF ( large_scale_forcing .AND. lsf_surf )  THEN
739             WRITE ( io, 306 )  shf(0,0)
740          ELSE
741             WRITE ( io, 306 )  surface_heatflux
742          ENDIF
743          IF ( random_heatflux )  WRITE ( io, 307 )
744       ENDIF
745       IF ( humidity  .AND.  constant_waterflux )  THEN
746          IF ( large_scale_forcing .AND. lsf_surf )  THEN
747             WRITE ( io, 311 ) qsws(0,0)
748          ELSE
749             WRITE ( io, 311 ) surface_waterflux
750          ENDIF
751       ENDIF
752       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
753          WRITE ( io, 313 ) surface_waterflux
754       ENDIF
755    ENDIF
756
757    IF ( use_top_fluxes )  THEN
758       WRITE ( io, 304 )
759       IF ( coupling_mode == 'uncoupled' )  THEN
760          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
761          IF ( constant_top_heatflux )  THEN
762             WRITE ( io, 306 )  top_heatflux
763          ENDIF
764       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
765          WRITE ( io, 316 )
766       ENDIF
767       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
768          WRITE ( io, 309 )  top_salinityflux
769       ENDIF
770       IF ( humidity  .OR.  passive_scalar )  THEN
771          WRITE ( io, 315 )
772       ENDIF
773    ENDIF
774
775    IF ( prandtl_layer )  THEN
776       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
777                          z0h_factor*roughness_length, kappa, &
778                          rif_min, rif_max
779       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
780       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
781          WRITE ( io, 312 )
782       ENDIF
783       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
784          WRITE ( io, 314 )
785       ENDIF
786    ELSE
787       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
788          WRITE ( io, 310 )  rif_min, rif_max
789       ENDIF
790    ENDIF
791
792    WRITE ( io, 317 )  bc_lr, bc_ns
793    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
794       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
795       IF ( turbulent_inflow )  THEN
796          WRITE ( io, 319 )  recycling_width, recycling_plane, &
797                             inflow_damping_height, inflow_damping_width
798       ENDIF
799    ENDIF
800
801!
802!-- Listing of 1D-profiles
803    WRITE ( io, 325 )  dt_dopr_listing
804    IF ( averaging_interval_pr /= 0.0 )  THEN
805       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
806    ENDIF
807
808!
809!-- DATA output
810    WRITE ( io, 330 )
811    IF ( averaging_interval_pr /= 0.0 )  THEN
812       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
813    ENDIF
814
815!
816!-- 1D-profiles
817    dopr_chr = 'Profile:'
818    IF ( dopr_n /= 0 )  THEN
819       WRITE ( io, 331 )
820
821       output_format = ''
822       output_format = output_format_netcdf
823       WRITE ( io, 344 )  output_format
824
825       DO  i = 1, dopr_n
826          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
827          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
828             WRITE ( io, 332 )  dopr_chr
829             dopr_chr = '       :'
830          ENDIF
831       ENDDO
832
833       IF ( dopr_chr /= '' )  THEN
834          WRITE ( io, 332 )  dopr_chr
835       ENDIF
836       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
837       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
838    ENDIF
839
840!
841!-- 2D-arrays
842    DO  av = 0, 1
843
844       i = 1
845       do2d_xy = ''
846       do2d_xz = ''
847       do2d_yz = ''
848       DO  WHILE ( do2d(av,i) /= ' ' )
849
850          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
851          do2d_mode = do2d(av,i)(l-1:l)
852
853          SELECT CASE ( do2d_mode )
854             CASE ( 'xy' )
855                ll = LEN_TRIM( do2d_xy )
856                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
857             CASE ( 'xz' )
858                ll = LEN_TRIM( do2d_xz )
859                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
860             CASE ( 'yz' )
861                ll = LEN_TRIM( do2d_yz )
862                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
863          END SELECT
864
865          i = i + 1
866
867       ENDDO
868
869       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
870              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
871              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
872
873          IF (  av == 0 )  THEN
874             WRITE ( io, 334 )  ''
875          ELSE
876             WRITE ( io, 334 )  '(time-averaged)'
877          ENDIF
878
879          IF ( do2d_at_begin )  THEN
880             begin_chr = 'and at the start'
881          ELSE
882             begin_chr = ''
883          ENDIF
884
885          output_format = ''
886          output_format = output_format_netcdf
887          WRITE ( io, 344 )  output_format
888
889          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
890             i = 1
891             slices = '/'
892             coordinates = '/'
893!
894!--          Building strings with index and coordinate informations of the
895!--          slices
896             DO  WHILE ( section(i,1) /= -9999 )
897
898                WRITE (section_chr,'(I5)')  section(i,1)
899                section_chr = ADJUSTL( section_chr )
900                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
901
902                IF ( section(i,1) == -1 )  THEN
903                   WRITE (coor_chr,'(F10.1)')  -1.0
904                ELSE
905                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
906                ENDIF
907                coor_chr = ADJUSTL( coor_chr )
908                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
909
910                i = i + 1
911             ENDDO
912             IF ( av == 0 )  THEN
913                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
914                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
915                                   TRIM( coordinates )
916                IF ( skip_time_do2d_xy /= 0.0 )  THEN
917                   WRITE ( io, 339 )  skip_time_do2d_xy
918                ENDIF
919             ELSE
920                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
921                                   TRIM( begin_chr ), averaging_interval, &
922                                   dt_averaging_input, 'k', TRIM( slices ), &
923                                   TRIM( coordinates )
924                IF ( skip_time_data_output_av /= 0.0 )  THEN
925                   WRITE ( io, 339 )  skip_time_data_output_av
926                ENDIF
927             ENDIF
928             IF ( netcdf_data_format > 4 )  THEN
929                WRITE ( io, 352 )  ntdim_2d_xy(av)
930             ELSE
931                WRITE ( io, 353 )
932             ENDIF
933          ENDIF
934
935          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
936             i = 1
937             slices = '/'
938             coordinates = '/'
939!
940!--          Building strings with index and coordinate informations of the
941!--          slices
942             DO  WHILE ( section(i,2) /= -9999 )
943
944                WRITE (section_chr,'(I5)')  section(i,2)
945                section_chr = ADJUSTL( section_chr )
946                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
947
948                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
949                coor_chr = ADJUSTL( coor_chr )
950                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
951
952                i = i + 1
953             ENDDO
954             IF ( av == 0 )  THEN
955                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
956                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
957                                   TRIM( coordinates )
958                IF ( skip_time_do2d_xz /= 0.0 )  THEN
959                   WRITE ( io, 339 )  skip_time_do2d_xz
960                ENDIF
961             ELSE
962                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
963                                   TRIM( begin_chr ), averaging_interval, &
964                                   dt_averaging_input, 'j', TRIM( slices ), &
965                                   TRIM( coordinates )
966                IF ( skip_time_data_output_av /= 0.0 )  THEN
967                   WRITE ( io, 339 )  skip_time_data_output_av
968                ENDIF
969             ENDIF
970             IF ( netcdf_data_format > 4 )  THEN
971                WRITE ( io, 352 )  ntdim_2d_xz(av)
972             ELSE
973                WRITE ( io, 353 )
974             ENDIF
975          ENDIF
976
977          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
978             i = 1
979             slices = '/'
980             coordinates = '/'
981!
982!--          Building strings with index and coordinate informations of the
983!--          slices
984             DO  WHILE ( section(i,3) /= -9999 )
985
986                WRITE (section_chr,'(I5)')  section(i,3)
987                section_chr = ADJUSTL( section_chr )
988                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
989
990                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
991                coor_chr = ADJUSTL( coor_chr )
992                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
993
994                i = i + 1
995             ENDDO
996             IF ( av == 0 )  THEN
997                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
998                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
999                                   TRIM( coordinates )
1000                IF ( skip_time_do2d_yz /= 0.0 )  THEN
1001                   WRITE ( io, 339 )  skip_time_do2d_yz
1002                ENDIF
1003             ELSE
1004                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1005                                   TRIM( begin_chr ), averaging_interval, &
1006                                   dt_averaging_input, 'i', TRIM( slices ), &
1007                                   TRIM( coordinates )
1008                IF ( skip_time_data_output_av /= 0.0 )  THEN
1009                   WRITE ( io, 339 )  skip_time_data_output_av
1010                ENDIF
1011             ENDIF
1012             IF ( netcdf_data_format > 4 )  THEN
1013                WRITE ( io, 352 )  ntdim_2d_yz(av)
1014             ELSE
1015                WRITE ( io, 353 )
1016             ENDIF
1017          ENDIF
1018
1019       ENDIF
1020
1021    ENDDO
1022
1023!
1024!-- 3d-arrays
1025    DO  av = 0, 1
1026
1027       i = 1
1028       do3d_chr = ''
1029       DO  WHILE ( do3d(av,i) /= ' ' )
1030
1031          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1032          i = i + 1
1033
1034       ENDDO
1035
1036       IF ( do3d_chr /= '' )  THEN
1037          IF ( av == 0 )  THEN
1038             WRITE ( io, 336 )  ''
1039          ELSE
1040             WRITE ( io, 336 )  '(time-averaged)'
1041          ENDIF
1042
1043          output_format = output_format_netcdf
1044          WRITE ( io, 344 )  output_format
1045
1046          IF ( do3d_at_begin )  THEN
1047             begin_chr = 'and at the start'
1048          ELSE
1049             begin_chr = ''
1050          ENDIF
1051          IF ( av == 0 )  THEN
1052             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1053                                zu(nz_do3d), nz_do3d
1054          ELSE
1055             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1056                                TRIM( begin_chr ), averaging_interval, &
1057                                dt_averaging_input, zu(nz_do3d), nz_do3d
1058          ENDIF
1059
1060          IF ( netcdf_data_format > 4 )  THEN
1061             WRITE ( io, 352 )  ntdim_3d(av)
1062          ELSE
1063             WRITE ( io, 353 )
1064          ENDIF
1065
1066          IF ( av == 0 )  THEN
1067             IF ( skip_time_do3d /= 0.0 )  THEN
1068                WRITE ( io, 339 )  skip_time_do3d
1069             ENDIF
1070          ELSE
1071             IF ( skip_time_data_output_av /= 0.0 )  THEN
1072                WRITE ( io, 339 )  skip_time_data_output_av
1073             ENDIF
1074          ENDIF
1075
1076       ENDIF
1077
1078    ENDDO
1079
1080!
1081!-- masked arrays
1082    IF ( masks > 0 )  WRITE ( io, 345 )  &
1083         mask_scale_x, mask_scale_y, mask_scale_z
1084    DO  mid = 1, masks
1085       DO  av = 0, 1
1086
1087          i = 1
1088          domask_chr = ''
1089          DO  WHILE ( domask(mid,av,i) /= ' ' )
1090             domask_chr = TRIM( domask_chr ) // ' ' //  &
1091                          TRIM( domask(mid,av,i) ) // ','
1092             i = i + 1
1093          ENDDO
1094
1095          IF ( domask_chr /= '' )  THEN
1096             IF ( av == 0 )  THEN
1097                WRITE ( io, 346 )  '', mid
1098             ELSE
1099                WRITE ( io, 346 )  ' (time-averaged)', mid
1100             ENDIF
1101
1102             output_format = output_format_netcdf
1103!--          Parallel output not implemented for mask data, hence
1104!--          output_format must be adjusted.
1105             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1106             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1107             WRITE ( io, 344 )  output_format
1108
1109             IF ( av == 0 )  THEN
1110                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1111             ELSE
1112                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1113                                   averaging_interval, dt_averaging_input
1114             ENDIF
1115
1116             IF ( av == 0 )  THEN
1117                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1118                   WRITE ( io, 339 )  skip_time_domask(mid)
1119                ENDIF
1120             ELSE
1121                IF ( skip_time_data_output_av /= 0.0 )  THEN
1122                   WRITE ( io, 339 )  skip_time_data_output_av
1123                ENDIF
1124             ENDIF
1125!
1126!--          output locations
1127             DO  dim = 1, 3
1128                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1129                   count = 0
1130                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1131                      count = count + 1
1132                   ENDDO
1133                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1134                                      mask(mid,dim,:count)
1135                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1136                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1137                         mask_loop(mid,dim,3) == 0.0 )  THEN
1138                   WRITE ( io, 350 )  dir(dim), dir(dim)
1139                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1140                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1141                                      mask_loop(mid,dim,1:2)
1142                ELSE
1143                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1144                                      mask_loop(mid,dim,1:3)
1145                ENDIF
1146             ENDDO
1147          ENDIF
1148
1149       ENDDO
1150    ENDDO
1151
1152!
1153!-- Timeseries
1154    IF ( dt_dots /= 9999999.9_wp )  THEN
1155       WRITE ( io, 340 )
1156
1157       output_format = output_format_netcdf
1158       WRITE ( io, 344 )  output_format
1159       WRITE ( io, 341 )  dt_dots
1160    ENDIF
1161
1162#if defined( __dvrp_graphics )
1163!
1164!-- Dvrp-output
1165    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1166       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1167                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1168       i = 1
1169       l = 0
1170       m = 0
1171       DO WHILE ( mode_dvrp(i) /= ' ' )
1172          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1173             READ ( mode_dvrp(i), '(10X,I2)' )  j
1174             l = l + 1
1175             IF ( do3d(0,j) /= ' ' )  THEN
1176                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1177                                   isosurface_color(:,l)
1178             ENDIF
1179          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1180             READ ( mode_dvrp(i), '(6X,I2)' )  j
1181             m = m + 1
1182             IF ( do2d(0,j) /= ' ' )  THEN
1183                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1184                                   slicer_range_limits_dvrp(:,m)
1185             ENDIF
1186          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1187             WRITE ( io, 363 )  dvrp_psize
1188             IF ( particle_dvrpsize /= 'none' )  THEN
1189                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1190                                   dvrpsize_interval
1191             ENDIF
1192             IF ( particle_color /= 'none' )  THEN
1193                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1194                                   color_interval
1195             ENDIF
1196          ENDIF
1197          i = i + 1
1198       ENDDO
1199
1200       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1201                          superelevation_y, superelevation, clip_dvrp_l, &
1202                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1203
1204       IF ( TRIM( topography ) /= 'flat' )  THEN
1205          WRITE ( io, 366 )  topography_color
1206          IF ( cluster_size > 1 )  THEN
1207             WRITE ( io, 367 )  cluster_size
1208          ENDIF
1209       ENDIF
1210
1211    ENDIF
1212#endif
1213
1214#if defined( __spectra )
1215!
1216!-- Spectra output
1217    IF ( dt_dosp /= 9999999.9_wp )  THEN
1218       WRITE ( io, 370 )
1219
1220       output_format = output_format_netcdf
1221       WRITE ( io, 344 )  output_format
1222       WRITE ( io, 371 )  dt_dosp
1223       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1224       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1225                          ( spectra_direction(i), i = 1,10 ),  &
1226                          ( comp_spectra_level(i), i = 1,100 ), &
1227                          ( plot_spectra_level(i), i = 1,100 ), &
1228                          averaging_interval_sp, dt_averaging_input_pr
1229    ENDIF
1230#endif
1231
1232    WRITE ( io, 99 )
1233
1234!
1235!-- Physical quantities
1236    WRITE ( io, 400 )
1237
1238!
1239!-- Geostrophic parameters
1240    WRITE ( io, 410 )  omega, phi, f, fs
1241
1242!
1243!-- Other quantities
1244    WRITE ( io, 411 )  g
1245    WRITE ( io, 412 )  TRIM( reference_state )
1246    IF ( use_single_reference_value )  THEN
1247       IF ( ocean )  THEN
1248          WRITE ( io, 413 )  prho_reference
1249       ELSE
1250          WRITE ( io, 414 )  pt_reference
1251       ENDIF
1252    ENDIF
1253
1254!
1255!-- Cloud physics parameters
1256    IF ( cloud_physics )  THEN
1257       WRITE ( io, 415 )
1258       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1259       IF ( icloud_scheme == 0 )  THEN
1260          WRITE ( io, 510 ) 1.0E-6 * nc_const
1261          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1262       ENDIF
1263    ENDIF
1264
1265!-- Profile of the geostrophic wind (component ug)
1266!-- Building output strings
1267    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1268    gradients = '------'
1269    slices = '     0'
1270    coordinates = '   0.0'
1271    i = 1
1272    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1273     
1274       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1275       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1276
1277       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1278       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1279
1280       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1281       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1282
1283       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1284       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1285
1286       IF ( i == 10 )  THEN
1287          EXIT
1288       ELSE
1289          i = i + 1
1290       ENDIF
1291
1292    ENDDO
1293
1294    IF ( .NOT. large_scale_forcing )  THEN
1295       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1296                          TRIM( gradients ), TRIM( slices )
1297    ELSE
1298       WRITE ( io, 429 ) 
1299    ENDIF
1300
1301!-- Profile of the geostrophic wind (component vg)
1302!-- Building output strings
1303    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1304    gradients = '------'
1305    slices = '     0'
1306    coordinates = '   0.0'
1307    i = 1
1308    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1309
1310       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1311       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1312
1313       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1314       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1315
1316       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1317       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1318
1319       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1320       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1321
1322       IF ( i == 10 )  THEN
1323          EXIT
1324       ELSE
1325          i = i + 1
1326       ENDIF
1327 
1328    ENDDO
1329
1330    IF ( .NOT. large_scale_forcing )  THEN
1331       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1332                          TRIM( gradients ), TRIM( slices )
1333    ENDIF
1334
1335!
1336!-- Initial wind profiles
1337    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1338
1339!
1340!-- Initial temperature profile
1341!-- Building output strings, starting with surface temperature
1342    WRITE ( temperatures, '(F6.2)' )  pt_surface
1343    gradients = '------'
1344    slices = '     0'
1345    coordinates = '   0.0'
1346    i = 1
1347    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1348
1349       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1350       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1351
1352       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1353       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1354
1355       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1356       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1357
1358       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1359       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1360
1361       IF ( i == 10 )  THEN
1362          EXIT
1363       ELSE
1364          i = i + 1
1365       ENDIF
1366
1367    ENDDO
1368
1369    IF ( .NOT. nudging )  THEN
1370       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1371                          TRIM( gradients ), TRIM( slices )
1372    ELSE
1373       WRITE ( io, 428 ) 
1374    ENDIF
1375
1376!
1377!-- Initial humidity profile
1378!-- Building output strings, starting with surface humidity
1379    IF ( humidity  .OR.  passive_scalar )  THEN
1380       WRITE ( temperatures, '(E8.1)' )  q_surface
1381       gradients = '--------'
1382       slices = '       0'
1383       coordinates = '     0.0'
1384       i = 1
1385       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1386         
1387          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1388          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1389
1390          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1391          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1392         
1393          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1394          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1395         
1396          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1397          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1398
1399          IF ( i == 10 )  THEN
1400             EXIT
1401          ELSE
1402             i = i + 1
1403          ENDIF
1404
1405       ENDDO
1406
1407       IF ( humidity )  THEN
1408          IF ( .NOT. nudging )  THEN
1409             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1410                                TRIM( gradients ), TRIM( slices )
1411          ENDIF
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 
1486       IF ( .NOT. large_scale_forcing )  THEN
1487          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1488                             TRIM( gradients ), TRIM( slices )
1489        ELSE
1490           WRITE ( io, 460 ) 
1491       ENDIF
1492
1493
1494    ENDIF
1495
1496!
1497!-- Cloud physcis parameters / quantities / numerical methods
1498    WRITE ( io, 430 )
1499    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1500       WRITE ( io, 431 )
1501    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1502       WRITE ( io, 432 )
1503       IF ( radiation )  WRITE ( io, 132 )
1504       IF ( icloud_scheme == 1 )  THEN
1505          IF ( precipitation )  WRITE ( io, 133 )
1506       ELSEIF ( icloud_scheme == 0 )  THEN
1507          IF ( drizzle )  WRITE ( io, 506 )
1508          IF ( precipitation )  THEN
1509             WRITE ( io, 505 )
1510             IF ( turbulence )  WRITE ( io, 507 )
1511             IF ( ventilation_effect )  WRITE ( io, 508 )
1512             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1513          ENDIF
1514       ENDIF
1515    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1516       WRITE ( io, 433 )
1517       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1518       IF ( collision_kernel /= 'none' )  THEN
1519          WRITE ( io, 435 )  TRIM( collision_kernel )
1520          IF ( collision_kernel(6:9) == 'fast' )  THEN
1521             WRITE ( io, 436 )  radius_classes, dissipation_classes
1522          ENDIF
1523       ELSE
1524          WRITE ( io, 437 )
1525       ENDIF
1526    ENDIF
1527
1528!
1529!-- LES / turbulence parameters
1530    WRITE ( io, 450 )
1531
1532!--
1533! ... LES-constants used must still be added here
1534!--
1535    IF ( constant_diffusion )  THEN
1536       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1537                          prandtl_number
1538    ENDIF
1539    IF ( .NOT. constant_diffusion)  THEN
1540       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1541       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1542       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1543    ENDIF
1544
1545!
1546!-- Special actions during the run
1547    WRITE ( io, 470 )
1548    IF ( create_disturbances )  THEN
1549       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1550                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1551                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1552       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1553          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1554       ELSE
1555          WRITE ( io, 473 )  disturbance_energy_limit
1556       ENDIF
1557       WRITE ( io, 474 )  TRIM( random_generator )
1558    ENDIF
1559    IF ( pt_surface_initial_change /= 0.0 )  THEN
1560       WRITE ( io, 475 )  pt_surface_initial_change
1561    ENDIF
1562    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1563       WRITE ( io, 476 )  q_surface_initial_change       
1564    ENDIF
1565    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1566       WRITE ( io, 477 )  q_surface_initial_change       
1567    ENDIF
1568
1569    IF ( particle_advection )  THEN
1570!
1571!--    Particle attributes
1572       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1573                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1574                          end_time_prel, dt_sort_particles
1575       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1576       IF ( random_start_position )  WRITE ( io, 481 )
1577       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1578       WRITE ( io, 495 )  total_number_of_particles
1579       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1580          WRITE ( io, 483 )  maximum_number_of_tailpoints
1581          IF ( minimum_tailpoint_distance /= 0 )  THEN
1582             WRITE ( io, 484 )  total_number_of_tails,      &
1583                                minimum_tailpoint_distance, &
1584                                maximum_tailpoint_age
1585          ENDIF
1586       ENDIF
1587       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1588          WRITE ( io, 485 )  dt_write_particle_data
1589          IF ( netcdf_data_format > 1 )  THEN
1590             output_format = 'netcdf (64 bit offset) and binary'
1591          ELSE
1592             output_format = 'netcdf and binary'
1593          ENDIF
1594          WRITE ( io, 344 )  output_format
1595       ENDIF
1596       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1597       IF ( write_particle_statistics )  WRITE ( io, 486 )
1598
1599       WRITE ( io, 487 )  number_of_particle_groups
1600
1601       DO  i = 1, number_of_particle_groups
1602          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1603             WRITE ( io, 490 )  i, 0.0
1604             WRITE ( io, 492 )
1605          ELSE
1606             WRITE ( io, 490 )  i, radius(i)
1607             IF ( density_ratio(i) /= 0.0 )  THEN
1608                WRITE ( io, 491 )  density_ratio(i)
1609             ELSE
1610                WRITE ( io, 492 )
1611             ENDIF
1612          ENDIF
1613          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1614                             pdx(i), pdy(i), pdz(i)
1615          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1616       ENDDO
1617
1618    ENDIF
1619
1620
1621!
1622!-- Parameters of 1D-model
1623    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1624       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1625                          mixing_length_1d, dissipation_1d
1626       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1627          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1628       ENDIF
1629    ENDIF
1630
1631!
1632!-- User-defined informations
1633    CALL user_header( io )
1634
1635    WRITE ( io, 99 )
1636
1637!
1638!-- Write buffer contents to disc immediately
1639    CALL local_flush( io )
1640
1641!
1642!-- Here the FORMATs start
1643
1644 99 FORMAT (1X,78('-'))
1645100 FORMAT (/1X,'******************************',6X,42('-')/        &
1646            1X,'* ',A,' *',6X,A/                               &
1647            1X,'******************************',6X,42('-'))
1648101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1649            37X,42('-'))
1650102 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
1651            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
1652            ' Run on host:        ',A10)
1653#if defined( __parallel )
1654103 FORMAT (' Number of PEs:',10X,I6,6X,'Processor grid (x,y): (',I3,',',I3, &
1655              ')',1X,A)
1656104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1657              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1658105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1659106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1660            37X,'because the job is running on an SMP-cluster')
1661107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1662108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
1663109 FORMAT (37X,'Precursor run for coupled atmos-ocean run'/ &
1664            37X,42('-'))
1665114 FORMAT (37X,'Coupled atmosphere-ocean run following'/ &
1666            37X,'independent precursor runs'/             &
1667            37X,42('-'))
1668117 FORMAT (' Accelerator boards / node:  ',I2)
1669#endif
1670110 FORMAT (/' Numerical Schemes:'/ &
1671             ' -----------------'/)
1672111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1673112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1674            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1675113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1676                  ' or Upstream')
1677115 FORMAT ('     FFT and transpositions are overlapping')
1678116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1679                  ' or Upstream')
1680118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1681119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1682            '     translation velocity = ',A/ &
1683            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1684120 FORMAT (' Accelerator boards: ',8X,I2)
1685122 FORMAT (' --> Time differencing scheme: ',A)
1686123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1687            '     maximum damping coefficient: ',F5.3, ' 1/s')
1688129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1689130 FORMAT (' --> Additional prognostic equation for the total water content')
1690131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1691                  F6.2, ' K assumed')
1692132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1693            '     effective emissivity scheme')
1694133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1695134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1696135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1697                  A,'-cycle)'/ &
1698            '     number of grid levels:                   ',I2/ &
1699            '     Gauss-Seidel red/black iterations:       ',I2)
1700136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1701                  I3,')')
1702137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1703            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1704                  I3,')'/ &
1705            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1706                  I3,')')
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(s) for')
1724154 FORMAT ('     the scalar(s) only')
1725155 FORMAT (' --> Nudging is used - initial profiles for u, v, pt and q ',& 
1726                  'correspond to the')
1727156 FORMAT ('     first profiles in NUDGING_DATA')
1728157 FORMAT (' --> Large scale forcing from external file (LSF_DATA) is used: ')
1729158 FORMAT ('     prescribed surfaces fluxes and geostrophic wind components')
1730200 FORMAT (//' Run time and time step information:'/ &
1731             ' ----------------------------------'/)
1732201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1733             '    CFL-factor: ',F4.2)
1734202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1735203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1736             ' End time:            ',F9.3,' s')
1737204 FORMAT ( A,F9.3,' s')
1738205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1739206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1740             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1741               '  ',F9.3,' s'/                                                    &
1742             '                                      per second of simulated tim', &
1743               'e: ',F9.3,' s')
1744207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1745250 FORMAT (//' Computational grid and domain size:'/ &
1746              ' ----------------------------------'// &
1747              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1748              ' m    dz =    ',F7.3,' m'/ &
1749              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1750              ' m  z(u) = ',F10.3,' m'/)
1751252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1752              ' factor: ',F5.3/ &
1753            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1754254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1755            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1756260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1757             ' degrees')
1758270 FORMAT (//' Topography informations:'/ &
1759              ' -----------------------'// &
1760              1X,'Topography: ',A)
1761271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1762              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1763                ' / ',I4)
1764272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1765              ' direction' / &
1766              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1767              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1768278 FORMAT (' Topography grid definition convention:'/ &
1769            ' cell edge (staggered grid points'/  &
1770            ' (u in x-direction, v in y-direction))' /)
1771279 FORMAT (' Topography grid definition convention:'/ &
1772            ' cell center (scalar grid points)' /)
1773280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1774              ' ------------------------------'// &
1775              ' Canopy mode: ', A / &
1776              ' Canopy top: ',I4 / &
1777              ' Leaf drag coefficient: ',F6.2 /)
1778281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1779              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1780282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1781283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1782              ' Height:              ',A,'  m'/ &
1783              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1784              ' Gradient:            ',A,'  m**2/m**4'/ &
1785              ' Gridpoint:           ',A)
1786               
1787300 FORMAT (//' Boundary conditions:'/ &
1788             ' -------------------'// &
1789             '                     p                    uv             ', &
1790             '                   pt'// &
1791             ' B. bound.: ',A/ &
1792             ' T. bound.: ',A)
1793301 FORMAT (/'                     ',A// &
1794             ' B. bound.: ',A/ &
1795             ' T. bound.: ',A)
1796303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1797304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1798305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1799               'computational u,v-level:'// &
1800             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1801             ' m   kappa = ',F4.2/ &
1802             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1803306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1804307 FORMAT ('       Heatflux has a random normal distribution')
1805308 FORMAT ('       Predefined surface temperature')
1806309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1807310 FORMAT (//'    1D-Model:'// &
1808             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1809311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1810312 FORMAT ('       Predefined surface humidity')
1811313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1812314 FORMAT ('       Predefined scalar value at the surface')
1813315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1814316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1815                    'atmosphere model')
1816317 FORMAT (//' Lateral boundaries:'/ &
1817            '       left/right:  ',A/    &
1818            '       north/south: ',A)
1819318 FORMAT (/'       use_cmax: ',L1 / &
1820            '       pt damping layer width = ',F8.2,' m, pt ', &
1821                    'damping factor = ',F6.4)
1822319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1823            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1824            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1825320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1826            '                                          v: ',F9.6,' m**2/s**2')
1827325 FORMAT (//' List output:'/ &
1828             ' -----------'//  &
1829            '    1D-Profiles:'/    &
1830            '       Output every             ',F8.2,' s')
1831326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1832            '       Averaging input every    ',F8.2,' s')
1833330 FORMAT (//' Data output:'/ &
1834             ' -----------'/)
1835331 FORMAT (/'    1D-Profiles:')
1836332 FORMAT (/'       ',A)
1837333 FORMAT ('       Output every             ',F8.2,' s',/ &
1838            '       Time averaged over       ',F8.2,' s'/ &
1839            '       Averaging input every    ',F8.2,' s')
1840334 FORMAT (/'    2D-Arrays',A,':')
1841335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1842            '       Output every             ',F8.2,' s  ',A/ &
1843            '       Cross sections at ',A1,' = ',A/ &
1844            '       scalar-coordinates:   ',A,' m'/)
1845336 FORMAT (/'    3D-Arrays',A,':')
1846337 FORMAT (/'       Arrays: ',A/ &
1847            '       Output every             ',F8.2,' s  ',A/ &
1848            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1849339 FORMAT ('       No output during initial ',F8.2,' s')
1850340 FORMAT (/'    Time series:')
1851341 FORMAT ('       Output every             ',F8.2,' s'/)
1852342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1853            '       Output every             ',F8.2,' s  ',A/ &
1854            '       Time averaged over       ',F8.2,' s'/ &
1855            '       Averaging input every    ',F8.2,' s'/ &
1856            '       Cross sections at ',A1,' = ',A/ &
1857            '       scalar-coordinates:   ',A,' m'/)
1858343 FORMAT (/'       Arrays: ',A/ &
1859            '       Output every             ',F8.2,' s  ',A/ &
1860            '       Time averaged over       ',F8.2,' s'/ &
1861            '       Averaging input every    ',F8.2,' s'/ &
1862            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1863344 FORMAT ('       Output format: ',A/)
1864345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1865            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1866            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1867            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1868346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1869347 FORMAT ('       Variables: ',A/ &
1870            '       Output every             ',F8.2,' s')
1871348 FORMAT ('       Variables: ',A/ &
1872            '       Output every             ',F8.2,' s'/ &
1873            '       Time averaged over       ',F8.2,' s'/ &
1874            '       Averaging input every    ',F8.2,' s')
1875349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1876            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1877            13('       ',8(F8.2,',')/) )
1878350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1879            'all gridpoints along ',A,'-direction (default).' )
1880351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1881            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1882            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1883352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
1884353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
1885#if defined( __dvrp_graphics )
1886360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1887            '       Output every      ',F7.1,' s'/ &
1888            '       Output mode:      ',A/ &
1889            '       Host / User:      ',A,' / ',A/ &
1890            '       Directory:        ',A// &
1891            '       The sequence contains:')
1892361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1893            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1894362 FORMAT (/'       Slicer plane ',A/ &
1895            '       Slicer limits: [',F6.2,',',F6.2,']')
1896363 FORMAT (/'       Particles'/ &
1897            '          particle size:  ',F7.2,' m')
1898364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1899                       F6.2,',',F6.2,']')
1900365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1901            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1902                     ')'/ &
1903            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1904            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1905366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1906367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1907#endif
1908#if defined( __spectra )
1909370 FORMAT ('    Spectra:')
1910371 FORMAT ('       Output every ',F7.1,' s'/)
1911372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1912            '       Directions: ', 10(A5,',')/                         &
1913            '       height levels  k = ', 20(I3,',')/                  &
1914            '                          ', 20(I3,',')/                  &
1915            '                          ', 20(I3,',')/                  &
1916            '                          ', 20(I3,',')/                  &
1917            '                          ', 19(I3,','),I3,'.'/           &
1918            '       height levels selected for standard plot:'/        &
1919            '                      k = ', 20(I3,',')/                  &
1920            '                          ', 20(I3,',')/                  &
1921            '                          ', 20(I3,',')/                  &
1922            '                          ', 20(I3,',')/                  &
1923            '                          ', 19(I3,','),I3,'.'/           &
1924            '       Time averaged over ', F7.1, ' s,' /                &
1925            '       Profiles for the time averaging are taken every ', &
1926                    F6.1,' s')
1927#endif
1928400 FORMAT (//' Physical quantities:'/ &
1929              ' -------------------'/)
1930410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1931            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1932            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1933            '                            f*    = ',F9.6,' 1/s')
1934411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1935412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
1936413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1937414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
1938415 FORMAT (/'    Cloud physics parameters:'/ &
1939             '    ------------------------'/)
1940416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1941            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1942            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1943            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1944            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1945420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1946            '       Height:        ',A,'  m'/ &
1947            '       Temperature:   ',A,'  K'/ &
1948            '       Gradient:      ',A,'  K/100m'/ &
1949            '       Gridpoint:     ',A)
1950421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1951            '       Height:      ',A,'  m'/ &
1952            '       Humidity:    ',A,'  kg/kg'/ &
1953            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1954            '       Gridpoint:   ',A)
1955422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1956            '       Height:                  ',A,'  m'/ &
1957            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1958            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1959            '       Gridpoint:               ',A)
1960423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1961            '       Height:      ',A,'  m'/ &
1962            '       ug:          ',A,'  m/s'/ &
1963            '       Gradient:    ',A,'  1/100s'/ &
1964            '       Gridpoint:   ',A)
1965424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1966            '       Height:      ',A,'  m'/ &
1967            '       vg:          ',A,'  m/s'/ &
1968            '       Gradient:    ',A,'  1/100s'/ &
1969            '       Gridpoint:   ',A)
1970425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1971            '       Height:     ',A,'  m'/ &
1972            '       Salinity:   ',A,'  psu'/ &
1973            '       Gradient:   ',A,'  psu/100m'/ &
1974            '       Gridpoint:  ',A)
1975426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1976            '       Height:      ',A,'  m'/ &
1977            '       w_subs:      ',A,'  m/s'/ &
1978            '       Gradient:    ',A,'  (m/s)/100m'/ &
1979            '       Gridpoint:   ',A)
1980427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1981                  ' profiles')
1982428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
1983             '    NUDGING_DATA')
1984429 FORMAT (/'    Geostrophic wind profiles (ug, vg) are are taken from file '/ &
1985             '    LSF_DATA')
1986430 FORMAT (//' Cloud physics quantities / methods:'/ &
1987              ' ----------------------------------'/)
1988431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1989                 'on)')
1990432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1991            '    total water content is used.'/ &
1992            '    Condensation is parameterized via 0% - or 100% scheme.')
1993433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1994                 'icle model')
1995434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1996                 ' droplets < 1.0E-6 m')
1997435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
1998436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1999                    'are used'/ &
2000            '          number of radius classes:       ',I3,'    interval ', &
2001                       '[1.0E-6,2.0E-4] m'/ &
2002            '          number of dissipation classes:   ',I2,'    interval ', &
2003                       '[0,1000] cm**2/s**3')
2004437 FORMAT ('    Droplet collision is switched off')
2005450 FORMAT (//' LES / Turbulence quantities:'/ &
2006              ' ---------------------------'/)
2007451 FORMAT ('    Diffusion coefficients are constant:'/ &
2008            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2009453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2010454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2011455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2012460 FORMAT (/'    Profiles for large scale vertical velocity are '/ &
2013             '    taken from file LSF_DATA')
2014470 FORMAT (//' Actions during the simulation:'/ &
2015              ' -----------------------------'/)
2016471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2017            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2018            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2019            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2020472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2021                 ' to i/j =',I4)
2022473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2023                 1X,F5.3, ' m**2/s**2')
2024474 FORMAT ('    Random number generator used    : ',A/)
2025475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2026                 'respectively, if'/ &
2027            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2028                 ' 3D-simulation'/)
2029476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2030                 'respectively, if the'/ &
2031            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2032                 ' the 3D-simulation'/)
2033477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2034                 'respectively, if the'/ &
2035            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2036                 ' the 3D-simulation'/)
2037480 FORMAT ('    Particles:'/ &
2038            '    ---------'// &
2039            '       Particle advection is active (switched on at t = ', F7.1, &
2040                    ' s)'/ &
2041            '       Start of new particle generations every  ',F6.1,' s'/ &
2042            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2043            '                            bottom:     ', A, ' top:         ', A/&
2044            '       Maximum particle age:                 ',F9.1,' s'/ &
2045            '       Advection stopped at t = ',F9.1,' s'/ &
2046            '       Particles are sorted every ',F9.1,' s'/)
2047481 FORMAT ('       Particles have random start positions'/)
2048482 FORMAT ('          Particles are advected only horizontally'/)
2049483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2050484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2051            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2052            '            Maximum age of the end of the tail:  ',F8.2,' s')
2053485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2054486 FORMAT ('       Particle statistics are written on file'/)
2055487 FORMAT ('       Number of particle groups: ',I2/)
2056488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2057            '          minimum timestep for advection: ', F7.5/)
2058489 FORMAT ('       Number of particles simultaneously released at each ', &
2059                    'point: ', I5/)
2060490 FORMAT ('       Particle group ',I2,':'/ &
2061            '          Particle radius: ',E10.3, 'm')
2062491 FORMAT ('          Particle inertia is activated'/ &
2063            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2064492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2065493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2066            '                                         y:',F8.1,' - ',F8.1,' m'/&
2067            '                                         z:',F8.1,' - ',F8.1,' m'/&
2068            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2069                       ' m  dz = ',F8.1,' m'/)
2070494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2071                    F8.2,' s'/)
2072495 FORMAT ('       Number of particles in total domain: ',I10/)
2073500 FORMAT (//' 1D-Model parameters:'/                           &
2074              ' -------------------'//                           &
2075            '    Simulation time:                   ',F8.1,' s'/ &
2076            '    Run-controll output every:         ',F8.1,' s'/ &
2077            '    Vertical profile output every:     ',F8.1,' s'/ &
2078            '    Mixing length calculation:         ',A/         &
2079            '    Dissipation calculation:           ',A/)
2080502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2081503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2082504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2083505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2084506 FORMAT ('    Drizzle parameterization via Stokes law')
2085507 FORMAT ('    Turbulence effects on precipitation process')
2086508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2087509 FORMAT ('    Slope limiter used for sedimentation process')
2088510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2089511 FORMAT ('        Sedimentation Courant number:                  '/&
2090            '                               C_s   = ',F3.1,'        ')
2091
2092 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.