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

Last change on this file since 1365 was 1365, checked in by boeske, 10 years ago

large scale forcing enabled

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