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

Last change on this file since 1484 was 1484, checked in by kanani, 10 years ago

New:
---
Subroutine init_plant_canopy added to module plant_canopy_model_mod. (plant_canopy_model)
Alternative method for lad-profile construction added, also, new parameters added.
(header, package_parin, plant_canopy_model, read_var_list, write_var_list)
plant_canopy_model-dependency added to several subroutines. (Makefile)
New package/namelist canopy_par for canopy-related parameters added. (package_parin)

Changed:
---
Code structure of the plant canopy model changed, all canopy-model related code
combined to module plant_canopy_model_mod. (check_parameters, init_3d_model,
modules, timestep)
Module plant_canopy_model_mod added in USE-lists of some subroutines. (check_parameters,
header, init_3d_model, package_parin, read_var_list, user_init_plant_canopy, write_var_list)
Canopy initialization moved to new subroutine init_plant_canopy. (check_parameters,
init_3d_model, plant_canopy_model)
Calculation of canopy timestep-criterion removed, instead, the canopy
drag is now directly limited in the calculation of the canopy tendency terms.
(plant_canopy_model, timestep)
Some parameters renamed. (check_parameters, header, init_plant_canopy,
plant_canopy_model, read_var_list, write_var_list)
Unnecessary 3d-arrays removed. (init_plant_canopy, plant_canopy_model, user_init_plant_canopy)
Parameter checks regarding canopy initialization added. (check_parameters)
All canopy steering parameters moved from namelist inipar to canopy_par. (package_parin, parin)
Some redundant MPI communication removed. (init_plant_canopy)

Bugfix:
---
Missing KIND-attribute for REAL constant added. (check_parameters)
DO-WHILE-loop for lad-profile output restricted. (header)
Removed double-listing of use_upstream_for_tke in ONLY-list of module
control_parameters. (prognostic_equations)

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