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

Last change on this file since 1586 was 1586, checked in by maronga, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 91.4 KB
Line 
1 SUBROUTINE header
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 1586 2015-04-30 07:11:33Z maronga $
27!
28! 1585 2015-04-30 07:05:52Z maronga
29! Further output for radiation model(s).
30!
31! 1575 2015-03-27 09:56:27Z raasch
32! adjustments for psolver-queries, output of seed_follows_topography
33!
34! 1560 2015-03-06 10:48:54Z keck
35! output for recycling y shift
36!
37! 1557 2015-03-05 16:43:04Z suehring
38! output for monotonic limiter
39!
40! 1551 2015-03-03 14:18:16Z maronga
41! Added informal output for land surface model and radiation model. Removed typo.
42!
43! 1496 2014-12-02 17:25:50Z maronga
44! Renamed: "radiation -> "cloud_top_radiation"
45!
46! 1484 2014-10-21 10:53:05Z kanani
47! Changes due to new module structure of the plant canopy model:
48!   module plant_canopy_model_mod and output for new canopy model parameters
49!   (alpha_lad, beta_lad, lai_beta,...) added,
50!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
51!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
52!   learde renamed leaf_area_density.
53! Bugfix: DO-WHILE-loop for lad header information additionally restricted
54! by maximum number of gradient levels (currently 10)
55!
56! 1482 2014-10-18 12:34:45Z raasch
57! information about calculated or predefined virtual processor topology adjusted
58!
59! 1468 2014-09-24 14:06:57Z maronga
60! Adapted for use on up to 6-digit processor cores
61!
62! 1429 2014-07-15 12:53:45Z knoop
63! header exended to provide ensemble_member_nr if specified
64!
65! 1376 2014-04-26 11:21:22Z boeske
66! Correction of typos
67!
68! 1365 2014-04-22 15:03:56Z boeske
69! New section 'Large scale forcing and nudging':
70! output of large scale forcing and nudging information,
71! new section for initial profiles created
72!
73! 1359 2014-04-11 17:15:14Z hoffmann
74! dt_sort_particles removed
75!
76! 1353 2014-04-08 15:21:23Z heinze
77! REAL constants provided with KIND-attribute
78!
79! 1327 2014-03-21 11:00:16Z raasch
80! parts concerning iso2d and avs output removed,
81! -netcdf output queries
82!
83! 1324 2014-03-21 09:13:16Z suehring
84! Bugfix: module spectrum added
85!
86! 1322 2014-03-20 16:38:49Z raasch
87! REAL functions provided with KIND-attribute,
88! some REAL constants defined as wp-kind
89!
90! 1320 2014-03-20 08:40:49Z raasch
91! ONLY-attribute added to USE-statements,
92! kind-parameters added to all INTEGER and REAL declaration statements,
93! kinds are defined in new module kinds,
94! revision history before 2012 removed,
95! comment fields (!:) to be used for variable explanations added to
96! all variable declaration statements
97!
98! 1308 2014-03-13 14:58:42Z fricke
99! output of the fixed number of output time levels
100! output_format adjusted for masked data if netcdf_data_format > 5
101!
102! 1299 2014-03-06 13:15:21Z heinze
103! output for using large_scale subsidence in combination
104! with large_scale_forcing
105! reformatting, more detailed explanations
106!
107! 1241 2013-10-30 11:36:58Z heinze
108! output for nudging + large scale forcing from external file
109!
110! 1216 2013-08-26 09:31:42Z raasch
111! output for transpose_compute_overlap
112!
113! 1212 2013-08-15 08:46:27Z raasch
114! output for poisfft_hybrid removed
115!
116! 1179 2013-06-14 05:57:58Z raasch
117! output of reference_state, use_reference renamed use_single_reference_value
118!
119! 1159 2013-05-21 11:58:22Z fricke
120! +use_cmax
121!
122! 1115 2013-03-26 18:16:16Z hoffmann
123! descriptions for Seifert-Beheng-cloud-physics-scheme added
124!
125! 1111 2013-03-08 23:54:10Z raasch
126! output of accelerator board information
127! ibc_p_b = 2 removed
128!
129! 1108 2013-03-05 07:03:32Z raasch
130! bugfix for r1106
131!
132! 1106 2013-03-04 05:31:38Z raasch
133! some format changes for coupled runs
134!
135! 1092 2013-02-02 11:24:22Z raasch
136! unused variables removed
137!
138! 1036 2012-10-22 13:43:42Z raasch
139! code put under GPL (PALM 3.9)
140!
141! 1031 2012-10-19 14:35:30Z raasch
142! output of netCDF data format modified
143!
144! 1015 2012-09-27 09:23:24Z raasch
145! output of Adjustment of mixing length to the Prandtl mixing length at first
146! grid point above ground removed
147!
148! 1003 2012-09-14 14:35:53Z raasch
149! output of information about equal/unequal subdomain size removed
150!
151! 1001 2012-09-13 14:08:46Z raasch
152! all actions concerning leapfrog- and upstream-spline-scheme removed
153!
154! 978 2012-08-09 08:28:32Z fricke
155! -km_damp_max, outflow_damping_width
156! +pt_damping_factor, pt_damping_width
157! +z0h
158!
159! 964 2012-07-26 09:14:24Z raasch
160! output of profil-related quantities removed
161!
162! 940 2012-07-09 14:31:00Z raasch
163! Output in case of simulations for pure neutral stratification (no pt-equation
164! solved)
165!
166! 927 2012-06-06 19:15:04Z raasch
167! output of masking_method for mg-solver
168!
169! 868 2012-03-28 12:21:07Z raasch
170! translation velocity in Galilean transformation changed to 0.6 * ug
171!
172! 833 2012-02-22 08:55:55Z maronga
173! Adjusted format for leaf area density
174!
175! 828 2012-02-21 12:00:36Z raasch
176! output of dissipation_classes + radius_classes
177!
178! 825 2012-02-19 03:03:44Z raasch
179! Output of cloud physics parameters/quantities complemented and restructured
180!
181! Revision 1.1  1997/08/11 06:17:20  raasch
182! Initial revision
183!
184!
185! Description:
186! ------------
187! Writing a header with all important information about the actual run.
188! This subroutine is called three times, two times at the beginning
189! (writing information on files RUN_CONTROL and HEADER) and one time at the
190! end of the run, then writing additional information about CPU-usage on file
191! header.
192!-----------------------------------------------------------------------------!
193
194    USE arrays_3d,                                                             &
195        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
196       
197    USE control_parameters
198       
199    USE cloud_parameters,                                                      &
200        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
201               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
202       
203    USE cpulog,                                                                &
204        ONLY:  log_point_s
205       
206    USE dvrp_variables,                                                        &
207        ONLY:  use_seperate_pe_for_dvrp_output
208       
209    USE grid_variables,                                                        &
210        ONLY:  dx, dy
211       
212    USE indices,                                                               &
213        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
214               nys_mg, nzt, nzt_mg
215       
216    USE kinds
217   
218    USE land_surface_model_mod,                                                &
219        ONLY:  conserve_water_content, dewfall, land_surface, nzb_soil,        &
220               nzt_soil, root_fraction, soil_moisture, soil_temperature,       &
221               soil_type, soil_type_name, veg_type, veg_type_name, zs
222 
223    USE model_1d,                                                              &
224        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
225       
226    USE particle_attributes,                                                   &
227        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
228               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
229               dt_write_particle_data, end_time_prel,                          &
230               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
231               minimum_tailpoint_distance, number_of_particle_groups,          &
232               particle_advection, particle_advection_start,                   &
233               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
234               pst, radius, radius_classes, random_start_position,             &
235               seed_follows_topography,                                        &
236               total_number_of_particles, use_particle_tails,                  &
237               use_sgs_for_particles, total_number_of_tails,                   &
238               vertical_particle_advection, write_particle_statistics
239       
240    USE pegrid
241
242    USE plant_canopy_model_mod,                                                &
243        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
244               canopy_mode, cthf, lad, lad_surface, lad_vertical_gradient,     &
245               lad_vertical_gradient_level, lad_vertical_gradient_level_ind,   &
246               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
247               plant_canopy
248
249    USE radiation_model_mod,                                                   &
250        ONLY:  albedo, albedo_type, albedo_type_name, constant_albedo,         &
251               day_init, dt_radiation, lambda, lw_radiation, net_radiation,    &
252               radiation, radiation_scheme, sw_radiation, time_utc_init
253   
254    USE spectrum,                                                              &
255        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
256               spectra_direction
257
258    IMPLICIT NONE
259
260    CHARACTER (LEN=1)  ::  prec                !:
261   
262    CHARACTER (LEN=2)  ::  do2d_mode           !:
263   
264    CHARACTER (LEN=5)  ::  section_chr         !:
265   
266    CHARACTER (LEN=10) ::  coor_chr            !:
267    CHARACTER (LEN=10) ::  host_chr            !:
268   
269    CHARACTER (LEN=16) ::  begin_chr           !:
270   
271    CHARACTER (LEN=26) ::  ver_rev             !:
272   
273    CHARACTER (LEN=40) ::  output_format       !:
274   
275    CHARACTER (LEN=70) ::  char1               !:
276    CHARACTER (LEN=70) ::  char2               !:
277    CHARACTER (LEN=70) ::  dopr_chr            !:
278    CHARACTER (LEN=70) ::  do2d_xy             !:
279    CHARACTER (LEN=70) ::  do2d_xz             !:
280    CHARACTER (LEN=70) ::  do2d_yz             !:
281    CHARACTER (LEN=70) ::  do3d_chr            !:
282    CHARACTER (LEN=70) ::  domask_chr          !:
283    CHARACTER (LEN=70) ::  run_classification  !:
284   
285    CHARACTER (LEN=85) ::  roben               !:
286    CHARACTER (LEN=85) ::  runten              !:
287   
288    CHARACTER (LEN=86) ::  coordinates         !:
289    CHARACTER (LEN=86) ::  gradients           !:
290    CHARACTER (LEN=86) ::  leaf_area_density   !:
291    CHARACTER (LEN=86) ::  roots               !:
292    CHARACTER (LEN=86) ::  slices              !:
293    CHARACTER (LEN=86) ::  temperatures        !:
294    CHARACTER (LEN=86) ::  ugcomponent         !:
295    CHARACTER (LEN=86) ::  vgcomponent         !:
296
297    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
298
299    INTEGER(iwp) ::  av        !:
300    INTEGER(iwp) ::  bh        !:
301    INTEGER(iwp) ::  blx       !:
302    INTEGER(iwp) ::  bly       !:
303    INTEGER(iwp) ::  bxl       !:
304    INTEGER(iwp) ::  bxr       !:
305    INTEGER(iwp) ::  byn       !:
306    INTEGER(iwp) ::  bys       !:
307    INTEGER(iwp) ::  ch        !:
308    INTEGER(iwp) ::  count     !:
309    INTEGER(iwp) ::  cwx       !:
310    INTEGER(iwp) ::  cwy       !:
311    INTEGER(iwp) ::  cxl       !:
312    INTEGER(iwp) ::  cxr       !:
313    INTEGER(iwp) ::  cyn       !:
314    INTEGER(iwp) ::  cys       !:
315    INTEGER(iwp) ::  dim       !:
316    INTEGER(iwp) ::  i         !:
317    INTEGER(iwp) ::  io        !:
318    INTEGER(iwp) ::  j         !:
319    INTEGER(iwp) ::  k         !:
320    INTEGER(iwp) ::  l         !:
321    INTEGER(iwp) ::  ll        !:
322    INTEGER(iwp) ::  mpi_type  !:
323   
324    REAL(wp) ::  canopy_height                    !: canopy height (in m)
325    REAL(wp) ::  cpuseconds_per_simulated_second  !:
326
327!
328!-- Open the output file. At the end of the simulation, output is directed
329!-- to unit 19.
330    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
331         .NOT. simulated_time_at_begin /= simulated_time )  THEN
332       io = 15   !  header output on file RUN_CONTROL
333    ELSE
334       io = 19   !  header output on file HEADER
335    ENDIF
336    CALL check_open( io )
337
338!
339!-- At the end of the run, output file (HEADER) will be rewritten with
340!-- new information
341    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
342
343!
344!-- Determine kind of model run
345    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
346       run_classification = '3D - restart run'
347    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
348       run_classification = '3D - run with cyclic fill of 3D - prerun data'
349    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
350       run_classification = '3D - run without 1D - prerun'
351    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
352       run_classification = '3D - run with 1D - prerun'
353    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
354       run_classification = '3D - run initialized by user'
355    ELSE
356       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
357       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
358    ENDIF
359    IF ( ocean )  THEN
360       run_classification = 'ocean - ' // run_classification
361    ELSE
362       run_classification = 'atmosphere - ' // run_classification
363    ENDIF
364
365!
366!-- Run-identification, date, time, host
367    host_chr = host(1:10)
368    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
369    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
370    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
371#if defined( __mpi2 )
372       mpi_type = 2
373#else
374       mpi_type = 1
375#endif
376       WRITE ( io, 101 )  mpi_type, coupling_mode
377    ENDIF
378#if defined( __parallel )
379    IF ( coupling_start_time /= 0.0_wp )  THEN
380       IF ( coupling_start_time > simulated_time_at_begin )  THEN
381          WRITE ( io, 109 )
382       ELSE
383          WRITE ( io, 114 )
384       ENDIF
385    ENDIF
386#endif
387    IF ( ensemble_member_nr /= 0 )  THEN
388       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
389                       ADJUSTR( host_chr ), ensemble_member_nr
390    ELSE
391       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
392                       ADJUSTR( host_chr )
393    ENDIF
394#if defined( __parallel )
395    IF ( npex == -1  .AND.  npey == -1 )  THEN
396       char1 = 'calculated'
397    ELSE
398       char1 = 'predefined'
399    ENDIF
400    IF ( threads_per_task == 1 )  THEN
401       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
402    ELSE
403       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
404                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
405    ENDIF
406    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
407    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
408           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
409         npex == -1  .AND.  pdims(2) == 1 )                      &
410    THEN
411       WRITE ( io, 106 )
412    ELSEIF ( pdims(2) == 1 )  THEN
413       WRITE ( io, 107 )  'x'
414    ELSEIF ( pdims(1) == 1 )  THEN
415       WRITE ( io, 107 )  'y'
416    ENDIF
417    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
418    IF ( numprocs /= maximum_parallel_io_streams )  THEN
419       WRITE ( io, 108 )  maximum_parallel_io_streams
420    ENDIF
421#else
422    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
423#endif
424    WRITE ( io, 99 )
425
426!
427!-- Numerical schemes
428    WRITE ( io, 110 )
429    IF ( psolver(1:7) == 'poisfft' )  THEN
430       WRITE ( io, 111 )  TRIM( fft_method )
431       IF ( transpose_compute_overlap )  WRITE( io, 115 )
432    ELSEIF ( psolver == 'sor' )  THEN
433       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
434    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
435       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
436       IF ( mg_cycles == -1 )  THEN
437          WRITE ( io, 140 )  residual_limit
438       ELSE
439          WRITE ( io, 141 )  mg_cycles
440       ENDIF
441       IF ( mg_switch_to_pe0_level == 0 )  THEN
442          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
443                             nzt_mg(1)
444       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
445          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
446                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
447                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
448                             nzt_mg(mg_switch_to_pe0_level),    &
449                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
450                             nzt_mg(1)
451       ENDIF
452       IF ( masking_method )  WRITE ( io, 144 )
453    ENDIF
454    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
455    THEN
456       WRITE ( io, 142 )
457    ENDIF
458
459    IF ( momentum_advec == 'pw-scheme' )  THEN
460       WRITE ( io, 113 )
461    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
462       WRITE ( io, 503 )
463    ENDIF
464    IF ( scalar_advec == 'pw-scheme' )  THEN
465       WRITE ( io, 116 )
466    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
467       WRITE ( io, 504 )
468    ELSEIF ( scalar_advec == 'ws-scheme-mono' )  THEN
469       WRITE ( io, 513 )
470    ELSE
471       WRITE ( io, 118 )
472    ENDIF
473
474    WRITE ( io, 139 )  TRIM( loop_optimization )
475
476    IF ( galilei_transformation )  THEN
477       IF ( use_ug_for_galilei_tr )  THEN
478          char1 = '0.6 * geostrophic wind'
479       ELSE
480          char1 = 'mean wind in model domain'
481       ENDIF
482       IF ( simulated_time_at_begin == simulated_time )  THEN
483          char2 = 'at the start of the run'
484       ELSE
485          char2 = 'at the end of the run'
486       ENDIF
487       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
488                          advected_distance_x/1000.0_wp,                       &
489                          advected_distance_y/1000.0_wp
490    ENDIF
491    WRITE ( io, 122 )  timestep_scheme
492    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
493    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
494       IF ( .NOT. ocean )  THEN
495          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
496               rayleigh_damping_factor
497       ELSE
498          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
499               rayleigh_damping_factor
500       ENDIF
501    ENDIF
502    IF ( neutral )  WRITE ( io, 131 )  pt_surface
503    IF ( humidity )  THEN
504       IF ( .NOT. cloud_physics )  THEN
505          WRITE ( io, 129 )
506       ELSE
507          WRITE ( io, 130 )
508       ENDIF
509    ENDIF
510    IF ( passive_scalar )  WRITE ( io, 134 )
511    IF ( conserve_volume_flow )  THEN
512       WRITE ( io, 150 )  conserve_volume_flow_mode
513       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
514          WRITE ( io, 151 )  u_bulk, v_bulk
515       ENDIF
516    ELSEIF ( dp_external )  THEN
517       IF ( dp_smooth )  THEN
518          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
519       ELSE
520          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
521       ENDIF
522    ENDIF
523    WRITE ( io, 99 )
524
525!
526!-- Runtime and timestep information
527    WRITE ( io, 200 )
528    IF ( .NOT. dt_fixed )  THEN
529       WRITE ( io, 201 )  dt_max, cfl_factor
530    ELSE
531       WRITE ( io, 202 )  dt
532    ENDIF
533    WRITE ( io, 203 )  simulated_time_at_begin, end_time
534
535    IF ( time_restart /= 9999999.9_wp  .AND. &
536         simulated_time_at_begin == simulated_time )  THEN
537       IF ( dt_restart == 9999999.9_wp )  THEN
538          WRITE ( io, 204 )  ' Restart at:       ',time_restart
539       ELSE
540          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
541       ENDIF
542    ENDIF
543
544    IF ( simulated_time_at_begin /= simulated_time )  THEN
545       i = MAX ( log_point_s(10)%counts, 1 )
546       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
547          cpuseconds_per_simulated_second = 0.0_wp
548       ELSE
549          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
550                                            ( simulated_time -    &
551                                              simulated_time_at_begin )
552       ENDIF
553       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
554                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
555                          cpuseconds_per_simulated_second
556       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
557          IF ( dt_restart == 9999999.9_wp )  THEN
558             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
559          ELSE
560             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
561          ENDIF
562       ENDIF
563    ENDIF
564
565
566!
567!-- Start time for coupled runs, if independent precursor runs for atmosphere
568!-- and ocean are used or have been used. In this case, coupling_start_time
569!-- defines the time when the coupling is switched on.
570    IF ( coupling_start_time /= 0.0_wp )  THEN
571       WRITE ( io, 207 )  coupling_start_time
572    ENDIF
573
574!
575!-- Computational grid
576    IF ( .NOT. ocean )  THEN
577       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
578       IF ( dz_stretch_level_index < nzt+1 )  THEN
579          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
580                             dz_stretch_factor, dz_max
581       ENDIF
582    ELSE
583       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
584       IF ( dz_stretch_level_index > 0 )  THEN
585          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
586                             dz_stretch_factor, dz_max
587       ENDIF
588    ENDIF
589    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
590                       MIN( nnz+2, nzt+2 )
591    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
592
593!
594!-- Large scale forcing and nudging
595    WRITE ( io, 160 )
596    IF ( large_scale_forcing )  THEN
597       WRITE ( io, 162 )
598       WRITE ( io, 163 )
599
600       IF ( large_scale_subsidence )  THEN
601          IF ( .NOT. use_subsidence_tendencies )  THEN
602             WRITE ( io, 164 )
603          ELSE
604             WRITE ( io, 165 )
605          ENDIF
606       ENDIF
607
608       IF ( bc_pt_b == 'dirichlet' )  THEN
609          WRITE ( io, 180 )
610       ELSEIF ( bc_pt_b == 'neumann' )  THEN
611          WRITE ( io, 181 )
612       ENDIF
613
614       IF ( bc_q_b == 'dirichlet' )  THEN
615          WRITE ( io, 182 )
616       ELSEIF ( bc_q_b == 'neumann' )  THEN
617          WRITE ( io, 183 )
618       ENDIF
619
620       WRITE ( io, 167 )
621       IF ( nudging )  THEN
622          WRITE ( io, 170 )
623       ENDIF
624    ELSE
625       WRITE ( io, 161 )
626       WRITE ( io, 171 )
627    ENDIF
628    IF ( large_scale_subsidence )  THEN
629       WRITE ( io, 168 )
630       WRITE ( io, 169 )
631    ENDIF
632
633!
634!-- Profile for the large scale vertial velocity
635!-- Building output strings, starting with surface value
636    IF ( large_scale_subsidence )  THEN
637       temperatures = '   0.0'
638       gradients = '------'
639       slices = '     0'
640       coordinates = '   0.0'
641       i = 1
642       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
643
644          WRITE (coor_chr,'(E10.2,7X)')  &
645                                w_subs(subs_vertical_gradient_level_i(i))
646          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
647
648          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
649          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
650
651          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
652          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
653
654          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
655          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
656
657          IF ( i == 10 )  THEN
658             EXIT
659          ELSE
660             i = i + 1
661          ENDIF
662
663       ENDDO
664
665 
666       IF ( .NOT. large_scale_forcing )  THEN
667          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
668                             TRIM( gradients ), TRIM( slices )
669       ENDIF
670
671
672    ENDIF
673
674!-- Profile of the geostrophic wind (component ug)
675!-- Building output strings
676    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
677    gradients = '------'
678    slices = '     0'
679    coordinates = '   0.0'
680    i = 1
681    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
682     
683       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
684       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
685
686       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
687       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
688
689       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
690       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
691
692       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
693       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
694
695       IF ( i == 10 )  THEN
696          EXIT
697       ELSE
698          i = i + 1
699       ENDIF
700
701    ENDDO
702
703    IF ( .NOT. large_scale_forcing )  THEN
704       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
705                          TRIM( gradients ), TRIM( slices )
706    ENDIF
707
708!-- Profile of the geostrophic wind (component vg)
709!-- Building output strings
710    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
711    gradients = '------'
712    slices = '     0'
713    coordinates = '   0.0'
714    i = 1
715    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
716
717       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
718       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
719
720       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
721       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
722
723       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
724       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
725
726       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
727       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
728
729       IF ( i == 10 )  THEN
730          EXIT
731       ELSE
732          i = i + 1
733       ENDIF
734 
735    ENDDO
736
737    IF ( .NOT. large_scale_forcing )  THEN
738       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
739                          TRIM( gradients ), TRIM( slices )
740    ENDIF
741
742!
743!-- Topography
744    WRITE ( io, 270 )  topography
745    SELECT CASE ( TRIM( topography ) )
746
747       CASE ( 'flat' )
748          ! no actions necessary
749
750       CASE ( 'single_building' )
751          blx = INT( building_length_x / dx )
752          bly = INT( building_length_y / dy )
753          bh  = INT( building_height / dz )
754
755          IF ( building_wall_left == 9999999.9_wp )  THEN
756             building_wall_left = ( nx + 1 - blx ) / 2 * dx
757          ENDIF
758          bxl = INT ( building_wall_left / dx + 0.5_wp )
759          bxr = bxl + blx
760
761          IF ( building_wall_south == 9999999.9_wp )  THEN
762             building_wall_south = ( ny + 1 - bly ) / 2 * dy
763          ENDIF
764          bys = INT ( building_wall_south / dy + 0.5_wp )
765          byn = bys + bly
766
767          WRITE ( io, 271 )  building_length_x, building_length_y, &
768                             building_height, bxl, bxr, bys, byn
769
770       CASE ( 'single_street_canyon' )
771          ch  = NINT( canyon_height / dz )
772          IF ( canyon_width_x /= 9999999.9_wp )  THEN
773!
774!--          Street canyon in y direction
775             cwx = NINT( canyon_width_x / dx )
776             IF ( canyon_wall_left == 9999999.9_wp )  THEN
777                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
778             ENDIF
779             cxl = NINT( canyon_wall_left / dx )
780             cxr = cxl + cwx
781             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
782
783          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
784!
785!--          Street canyon in x direction
786             cwy = NINT( canyon_width_y / dy )
787             IF ( canyon_wall_south == 9999999.9_wp )  THEN
788                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
789             ENDIF
790             cys = NINT( canyon_wall_south / dy )
791             cyn = cys + cwy
792             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
793          ENDIF
794
795    END SELECT
796
797    IF ( TRIM( topography ) /= 'flat' )  THEN
798       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
799          IF ( TRIM( topography ) == 'single_building' .OR.  &
800               TRIM( topography ) == 'single_street_canyon' )  THEN
801             WRITE ( io, 278 )
802          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
803             WRITE ( io, 279 )
804          ENDIF
805       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
806          WRITE ( io, 278 )
807       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
808          WRITE ( io, 279 )
809       ENDIF
810    ENDIF
811
812    IF ( plant_canopy )  THEN
813   
814       canopy_height = pch_index * dz
815
816       WRITE ( io, 280 )  canopy_mode, canopy_height, pch_index,               &
817                          canopy_drag_coeff
818       IF ( passive_scalar )  THEN
819          WRITE ( io, 281 )  leaf_scalar_exch_coeff,                           &
820                             leaf_surface_conc
821       ENDIF
822
823!
824!--    Heat flux at the top of vegetation
825       WRITE ( io, 282 )  cthf
826
827!
828!--    Leaf area density profile, calculated either from given vertical
829!--    gradients or from beta probability density function.
830       IF (  .NOT.  calc_beta_lad_profile )  THEN
831
832!--       Building output strings, starting with surface value
833          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
834          gradients = '------'
835          slices = '     0'
836          coordinates = '   0.0'
837          i = 1
838          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i) /= -9999 )
839
840             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
841             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
842 
843             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
844             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
845
846             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
847             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
848
849             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
850             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
851
852             i = i + 1
853          ENDDO
854
855          WRITE ( io, 283 )  TRIM( coordinates ), TRIM( leaf_area_density ),              &
856                             TRIM( gradients ), TRIM( slices )
857
858       ELSE
859       
860          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
861          coordinates = '   0.0'
862         
863          DO  k = 1, pch_index
864
865             WRITE (coor_chr,'(F7.2)')  lad(k)
866             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
867 
868             WRITE (coor_chr,'(F7.1)')  zu(k)
869             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
870
871          ENDDO       
872
873          WRITE ( io, 284 ) TRIM( coordinates ), TRIM( leaf_area_density ), alpha_lad,    &
874                            beta_lad, lai_beta
875
876       ENDIF 
877
878    ENDIF
879
880
881    IF ( land_surface )  THEN
882
883       temperatures = ''
884       gradients    = '' ! use for humidity here
885       coordinates  = '' ! use for height
886       roots        = '' ! use for root fraction
887       slices       = '' ! use for index
888
889       i = 1
890       DO i = nzb_soil, nzt_soil
891          WRITE (coor_chr,'(F10.2,7X)') soil_temperature(i)
892          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
893
894          WRITE (coor_chr,'(F10.2,7X)') soil_moisture(i)
895          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
896
897          WRITE (coor_chr,'(F10.2,7X)')  - zs(i)
898          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
899
900          WRITE (coor_chr,'(F10.2,7X)')  root_fraction(i)
901          roots = TRIM( roots ) // ' '  // TRIM( coor_chr )
902
903          WRITE (coor_chr,'(I10,7X)')  i
904          slices = TRIM( slices ) // ' '  // TRIM( coor_chr )
905
906
907       ENDDO
908
909!
910!--    Write land surface model header
911       WRITE( io, 419 )
912       IF ( conserve_water_content )  THEN
913          WRITE( io, 440 )
914       ELSE
915          WRITE( io, 441 )
916       ENDIF
917
918       IF ( dewfall )  THEN
919          WRITE( io, 442 )
920       ELSE
921          WRITE( io, 443 )
922       ENDIF
923
924       WRITE( io, 438 ) veg_type_name(veg_type), soil_type_name(soil_type)
925       WRITE( io, 439 ) TRIM( coordinates ), TRIM( temperatures ),             &
926                        TRIM( gradients ), TRIM( roots ), TRIM( slices )
927
928
929    ENDIF
930
931    IF ( radiation )  THEN
932!
933!--    Write radiation model header
934       WRITE( io, 444 )
935
936       IF ( radiation_scheme == "constant" )  THEN
937          WRITE( io, 445 ) net_radiation
938       ELSEIF ( radiation_scheme == "clear-sky" )  THEN
939          WRITE( io, 446 )
940       ELSEIF ( radiation_scheme == "rrtmg" )  THEN
941          WRITE( io, 447 )
942          IF ( .NOT. lw_radiation )  WRITE( io, 458 )
943          IF ( .NOT. sw_radiation )  WRITE( io, 459 )
944       ENDIF
945
946       IF ( albedo_type == 0 )  THEN
947          WRITE( io, 448 ) albedo
948       ELSE
949          WRITE( io, 456 ) albedo_type_name(albedo_type)
950       ENDIF
951       IF ( constant_albedo )  THEN
952          WRITE( io, 457 )
953       ENDIF
954       WRITE( io, 449 ) dt_radiation
955    ENDIF
956
957
958!
959!-- Boundary conditions
960    IF ( ibc_p_b == 0 )  THEN
961       runten = 'p(0)     = 0      |'
962    ELSEIF ( ibc_p_b == 1 )  THEN
963       runten = 'p(0)     = p(1)   |'
964    ENDIF
965    IF ( ibc_p_t == 0 )  THEN
966       roben  = 'p(nzt+1) = 0      |'
967    ELSE
968       roben  = 'p(nzt+1) = p(nzt) |'
969    ENDIF
970
971    IF ( ibc_uv_b == 0 )  THEN
972       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
973    ELSE
974       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
975    ENDIF
976    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
977       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
978    ELSEIF ( ibc_uv_t == 0 )  THEN
979       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
980    ELSE
981       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
982    ENDIF
983
984    IF ( ibc_pt_b == 0 )  THEN
985       IF ( land_surface )  THEN
986          runten = TRIM( runten ) // ' pt(0)     = from soil model'
987       ELSE
988          runten = TRIM( runten ) // ' pt(0)     = pt_surface'
989       ENDIF
990    ELSEIF ( ibc_pt_b == 1 )  THEN
991       runten = TRIM( runten ) // ' pt(0)     = pt(1)'
992    ELSEIF ( ibc_pt_b == 2 )  THEN
993       runten = TRIM( runten ) // ' pt(0)     = from coupled model'
994    ENDIF
995    IF ( ibc_pt_t == 0 )  THEN
996       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
997    ELSEIF( ibc_pt_t == 1 )  THEN
998       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
999    ELSEIF( ibc_pt_t == 2 )  THEN
1000       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
1001
1002    ENDIF
1003
1004    WRITE ( io, 300 )  runten, roben
1005
1006    IF ( .NOT. constant_diffusion )  THEN
1007       IF ( ibc_e_b == 1 )  THEN
1008          runten = 'e(0)     = e(1)'
1009       ELSE
1010          runten = 'e(0)     = e(1) = (u*/0.1)**2'
1011       ENDIF
1012       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
1013
1014       WRITE ( io, 301 )  'e', runten, roben       
1015
1016    ENDIF
1017
1018    IF ( ocean )  THEN
1019       runten = 'sa(0)    = sa(1)'
1020       IF ( ibc_sa_t == 0 )  THEN
1021          roben =  'sa(nzt+1) = sa_surface'
1022       ELSE
1023          roben =  'sa(nzt+1) = sa(nzt)'
1024       ENDIF
1025       WRITE ( io, 301 ) 'sa', runten, roben
1026    ENDIF
1027
1028    IF ( humidity )  THEN
1029       IF ( ibc_q_b == 0 )  THEN
1030          IF ( land_surface )  THEN
1031             runten = 'q(0)     = from soil model'
1032          ELSE
1033             runten = 'q(0)     = q_surface'
1034          ENDIF
1035
1036       ELSE
1037          runten = 'q(0)     = q(1)'
1038       ENDIF
1039       IF ( ibc_q_t == 0 )  THEN
1040          roben =  'q(nzt)   = q_top'
1041       ELSE
1042          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
1043       ENDIF
1044       WRITE ( io, 301 ) 'q', runten, roben
1045    ENDIF
1046
1047    IF ( passive_scalar )  THEN
1048       IF ( ibc_q_b == 0 )  THEN
1049          runten = 's(0)     = s_surface'
1050       ELSE
1051          runten = 's(0)     = s(1)'
1052       ENDIF
1053       IF ( ibc_q_t == 0 )  THEN
1054          roben =  's(nzt)   = s_top'
1055       ELSE
1056          roben =  's(nzt)   = s(nzt-1) + ds/dz'
1057       ENDIF
1058       WRITE ( io, 301 ) 's', runten, roben
1059    ENDIF
1060
1061    IF ( use_surface_fluxes )  THEN
1062       WRITE ( io, 303 )
1063       IF ( constant_heatflux )  THEN
1064          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1065             WRITE ( io, 306 )  shf(0,0)
1066          ELSE
1067             WRITE ( io, 306 )  surface_heatflux
1068          ENDIF
1069          IF ( random_heatflux )  WRITE ( io, 307 )
1070       ENDIF
1071       IF ( humidity  .AND.  constant_waterflux )  THEN
1072          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1073             WRITE ( io, 311 ) qsws(0,0)
1074          ELSE
1075             WRITE ( io, 311 ) surface_waterflux
1076          ENDIF
1077       ENDIF
1078       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1079          WRITE ( io, 313 ) surface_waterflux
1080       ENDIF
1081    ENDIF
1082
1083    IF ( use_top_fluxes )  THEN
1084       WRITE ( io, 304 )
1085       IF ( coupling_mode == 'uncoupled' )  THEN
1086          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
1087          IF ( constant_top_heatflux )  THEN
1088             WRITE ( io, 306 )  top_heatflux
1089          ENDIF
1090       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1091          WRITE ( io, 316 )
1092       ENDIF
1093       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1094          WRITE ( io, 309 )  top_salinityflux
1095       ENDIF
1096       IF ( humidity  .OR.  passive_scalar )  THEN
1097          WRITE ( io, 315 )
1098       ENDIF
1099    ENDIF
1100
1101    IF ( prandtl_layer )  THEN
1102       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
1103                          z0h_factor*roughness_length, kappa, &
1104                          rif_min, rif_max
1105       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
1106       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
1107          WRITE ( io, 312 )
1108       ENDIF
1109       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1110          WRITE ( io, 314 )
1111       ENDIF
1112    ELSE
1113       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
1114          WRITE ( io, 310 )  rif_min, rif_max
1115       ENDIF
1116    ENDIF
1117
1118    WRITE ( io, 317 )  bc_lr, bc_ns
1119    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1120       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
1121       IF ( turbulent_inflow )  THEN
1122          IF ( .NOT. recycling_yshift ) THEN
1123             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1124                                inflow_damping_height, inflow_damping_width
1125          ELSE
1126             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1127                                inflow_damping_height, inflow_damping_width
1128          END IF
1129       ENDIF
1130    ENDIF
1131
1132!
1133!-- Initial Profiles
1134    WRITE ( io, 321 )
1135!
1136!-- Initial wind profiles
1137    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1138
1139!
1140!-- Initial temperature profile
1141!-- Building output strings, starting with surface temperature
1142    WRITE ( temperatures, '(F6.2)' )  pt_surface
1143    gradients = '------'
1144    slices = '     0'
1145    coordinates = '   0.0'
1146    i = 1
1147    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1148
1149       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1150       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1151
1152       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1153       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1154
1155       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1156       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1157
1158       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1159       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1160
1161       IF ( i == 10 )  THEN
1162          EXIT
1163       ELSE
1164          i = i + 1
1165       ENDIF
1166
1167    ENDDO
1168
1169    IF ( .NOT. nudging )  THEN
1170       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1171                          TRIM( gradients ), TRIM( slices )
1172    ELSE
1173       WRITE ( io, 428 ) 
1174    ENDIF
1175
1176!
1177!-- Initial humidity profile
1178!-- Building output strings, starting with surface humidity
1179    IF ( humidity  .OR.  passive_scalar )  THEN
1180       WRITE ( temperatures, '(E8.1)' )  q_surface
1181       gradients = '--------'
1182       slices = '       0'
1183       coordinates = '     0.0'
1184       i = 1
1185       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1186         
1187          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1188          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1189
1190          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1191          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1192         
1193          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1194          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1195         
1196          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1197          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1198
1199          IF ( i == 10 )  THEN
1200             EXIT
1201          ELSE
1202             i = i + 1
1203          ENDIF
1204
1205       ENDDO
1206
1207       IF ( humidity )  THEN
1208          IF ( .NOT. nudging )  THEN
1209             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1210                                TRIM( gradients ), TRIM( slices )
1211          ENDIF
1212       ELSE
1213          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1214                             TRIM( gradients ), TRIM( slices )
1215       ENDIF
1216    ENDIF
1217
1218!
1219!-- Initial salinity profile
1220!-- Building output strings, starting with surface salinity
1221    IF ( ocean )  THEN
1222       WRITE ( temperatures, '(F6.2)' )  sa_surface
1223       gradients = '------'
1224       slices = '     0'
1225       coordinates = '   0.0'
1226       i = 1
1227       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1228
1229          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1230          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1231
1232          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1233          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1234
1235          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1236          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1237
1238          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1239          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1240
1241          IF ( i == 10 )  THEN
1242             EXIT
1243          ELSE
1244             i = i + 1
1245          ENDIF
1246
1247       ENDDO
1248
1249       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1250                          TRIM( gradients ), TRIM( slices )
1251    ENDIF
1252
1253
1254!
1255!-- Listing of 1D-profiles
1256    WRITE ( io, 325 )  dt_dopr_listing
1257    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1258       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1259    ENDIF
1260
1261!
1262!-- DATA output
1263    WRITE ( io, 330 )
1264    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1265       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1266    ENDIF
1267
1268!
1269!-- 1D-profiles
1270    dopr_chr = 'Profile:'
1271    IF ( dopr_n /= 0 )  THEN
1272       WRITE ( io, 331 )
1273
1274       output_format = ''
1275       output_format = output_format_netcdf
1276       WRITE ( io, 344 )  output_format
1277
1278       DO  i = 1, dopr_n
1279          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1280          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1281             WRITE ( io, 332 )  dopr_chr
1282             dopr_chr = '       :'
1283          ENDIF
1284       ENDDO
1285
1286       IF ( dopr_chr /= '' )  THEN
1287          WRITE ( io, 332 )  dopr_chr
1288       ENDIF
1289       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1290       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1291    ENDIF
1292
1293!
1294!-- 2D-arrays
1295    DO  av = 0, 1
1296
1297       i = 1
1298       do2d_xy = ''
1299       do2d_xz = ''
1300       do2d_yz = ''
1301       DO  WHILE ( do2d(av,i) /= ' ' )
1302
1303          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1304          do2d_mode = do2d(av,i)(l-1:l)
1305
1306          SELECT CASE ( do2d_mode )
1307             CASE ( 'xy' )
1308                ll = LEN_TRIM( do2d_xy )
1309                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1310             CASE ( 'xz' )
1311                ll = LEN_TRIM( do2d_xz )
1312                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1313             CASE ( 'yz' )
1314                ll = LEN_TRIM( do2d_yz )
1315                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1316          END SELECT
1317
1318          i = i + 1
1319
1320       ENDDO
1321
1322       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1323              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1324              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1325
1326          IF (  av == 0 )  THEN
1327             WRITE ( io, 334 )  ''
1328          ELSE
1329             WRITE ( io, 334 )  '(time-averaged)'
1330          ENDIF
1331
1332          IF ( do2d_at_begin )  THEN
1333             begin_chr = 'and at the start'
1334          ELSE
1335             begin_chr = ''
1336          ENDIF
1337
1338          output_format = ''
1339          output_format = output_format_netcdf
1340          WRITE ( io, 344 )  output_format
1341
1342          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1343             i = 1
1344             slices = '/'
1345             coordinates = '/'
1346!
1347!--          Building strings with index and coordinate information of the
1348!--          slices
1349             DO  WHILE ( section(i,1) /= -9999 )
1350
1351                WRITE (section_chr,'(I5)')  section(i,1)
1352                section_chr = ADJUSTL( section_chr )
1353                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1354
1355                IF ( section(i,1) == -1 )  THEN
1356                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1357                ELSE
1358                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1359                ENDIF
1360                coor_chr = ADJUSTL( coor_chr )
1361                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1362
1363                i = i + 1
1364             ENDDO
1365             IF ( av == 0 )  THEN
1366                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1367                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1368                                   TRIM( coordinates )
1369                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1370                   WRITE ( io, 339 )  skip_time_do2d_xy
1371                ENDIF
1372             ELSE
1373                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1374                                   TRIM( begin_chr ), averaging_interval, &
1375                                   dt_averaging_input, 'k', TRIM( slices ), &
1376                                   TRIM( coordinates )
1377                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1378                   WRITE ( io, 339 )  skip_time_data_output_av
1379                ENDIF
1380             ENDIF
1381             IF ( netcdf_data_format > 4 )  THEN
1382                WRITE ( io, 352 )  ntdim_2d_xy(av)
1383             ELSE
1384                WRITE ( io, 353 )
1385             ENDIF
1386          ENDIF
1387
1388          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1389             i = 1
1390             slices = '/'
1391             coordinates = '/'
1392!
1393!--          Building strings with index and coordinate information of the
1394!--          slices
1395             DO  WHILE ( section(i,2) /= -9999 )
1396
1397                WRITE (section_chr,'(I5)')  section(i,2)
1398                section_chr = ADJUSTL( section_chr )
1399                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1400
1401                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1402                coor_chr = ADJUSTL( coor_chr )
1403                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1404
1405                i = i + 1
1406             ENDDO
1407             IF ( av == 0 )  THEN
1408                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1409                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1410                                   TRIM( coordinates )
1411                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1412                   WRITE ( io, 339 )  skip_time_do2d_xz
1413                ENDIF
1414             ELSE
1415                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1416                                   TRIM( begin_chr ), averaging_interval, &
1417                                   dt_averaging_input, 'j', TRIM( slices ), &
1418                                   TRIM( coordinates )
1419                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1420                   WRITE ( io, 339 )  skip_time_data_output_av
1421                ENDIF
1422             ENDIF
1423             IF ( netcdf_data_format > 4 )  THEN
1424                WRITE ( io, 352 )  ntdim_2d_xz(av)
1425             ELSE
1426                WRITE ( io, 353 )
1427             ENDIF
1428          ENDIF
1429
1430          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1431             i = 1
1432             slices = '/'
1433             coordinates = '/'
1434!
1435!--          Building strings with index and coordinate information of the
1436!--          slices
1437             DO  WHILE ( section(i,3) /= -9999 )
1438
1439                WRITE (section_chr,'(I5)')  section(i,3)
1440                section_chr = ADJUSTL( section_chr )
1441                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1442
1443                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1444                coor_chr = ADJUSTL( coor_chr )
1445                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1446
1447                i = i + 1
1448             ENDDO
1449             IF ( av == 0 )  THEN
1450                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1451                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1452                                   TRIM( coordinates )
1453                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1454                   WRITE ( io, 339 )  skip_time_do2d_yz
1455                ENDIF
1456             ELSE
1457                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1458                                   TRIM( begin_chr ), averaging_interval, &
1459                                   dt_averaging_input, 'i', TRIM( slices ), &
1460                                   TRIM( coordinates )
1461                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1462                   WRITE ( io, 339 )  skip_time_data_output_av
1463                ENDIF
1464             ENDIF
1465             IF ( netcdf_data_format > 4 )  THEN
1466                WRITE ( io, 352 )  ntdim_2d_yz(av)
1467             ELSE
1468                WRITE ( io, 353 )
1469             ENDIF
1470          ENDIF
1471
1472       ENDIF
1473
1474    ENDDO
1475
1476!
1477!-- 3d-arrays
1478    DO  av = 0, 1
1479
1480       i = 1
1481       do3d_chr = ''
1482       DO  WHILE ( do3d(av,i) /= ' ' )
1483
1484          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1485          i = i + 1
1486
1487       ENDDO
1488
1489       IF ( do3d_chr /= '' )  THEN
1490          IF ( av == 0 )  THEN
1491             WRITE ( io, 336 )  ''
1492          ELSE
1493             WRITE ( io, 336 )  '(time-averaged)'
1494          ENDIF
1495
1496          output_format = output_format_netcdf
1497          WRITE ( io, 344 )  output_format
1498
1499          IF ( do3d_at_begin )  THEN
1500             begin_chr = 'and at the start'
1501          ELSE
1502             begin_chr = ''
1503          ENDIF
1504          IF ( av == 0 )  THEN
1505             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1506                                zu(nz_do3d), nz_do3d
1507          ELSE
1508             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1509                                TRIM( begin_chr ), averaging_interval, &
1510                                dt_averaging_input, zu(nz_do3d), nz_do3d
1511          ENDIF
1512
1513          IF ( netcdf_data_format > 4 )  THEN
1514             WRITE ( io, 352 )  ntdim_3d(av)
1515          ELSE
1516             WRITE ( io, 353 )
1517          ENDIF
1518
1519          IF ( av == 0 )  THEN
1520             IF ( skip_time_do3d /= 0.0_wp )  THEN
1521                WRITE ( io, 339 )  skip_time_do3d
1522             ENDIF
1523          ELSE
1524             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1525                WRITE ( io, 339 )  skip_time_data_output_av
1526             ENDIF
1527          ENDIF
1528
1529       ENDIF
1530
1531    ENDDO
1532
1533!
1534!-- masked arrays
1535    IF ( masks > 0 )  WRITE ( io, 345 )  &
1536         mask_scale_x, mask_scale_y, mask_scale_z
1537    DO  mid = 1, masks
1538       DO  av = 0, 1
1539
1540          i = 1
1541          domask_chr = ''
1542          DO  WHILE ( domask(mid,av,i) /= ' ' )
1543             domask_chr = TRIM( domask_chr ) // ' ' //  &
1544                          TRIM( domask(mid,av,i) ) // ','
1545             i = i + 1
1546          ENDDO
1547
1548          IF ( domask_chr /= '' )  THEN
1549             IF ( av == 0 )  THEN
1550                WRITE ( io, 346 )  '', mid
1551             ELSE
1552                WRITE ( io, 346 )  ' (time-averaged)', mid
1553             ENDIF
1554
1555             output_format = output_format_netcdf
1556!--          Parallel output not implemented for mask data, hence
1557!--          output_format must be adjusted.
1558             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1559             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1560             WRITE ( io, 344 )  output_format
1561
1562             IF ( av == 0 )  THEN
1563                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1564             ELSE
1565                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1566                                   averaging_interval, dt_averaging_input
1567             ENDIF
1568
1569             IF ( av == 0 )  THEN
1570                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1571                   WRITE ( io, 339 )  skip_time_domask(mid)
1572                ENDIF
1573             ELSE
1574                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1575                   WRITE ( io, 339 )  skip_time_data_output_av
1576                ENDIF
1577             ENDIF
1578!
1579!--          output locations
1580             DO  dim = 1, 3
1581                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1582                   count = 0
1583                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1584                      count = count + 1
1585                   ENDDO
1586                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1587                                      mask(mid,dim,:count)
1588                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1589                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1590                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1591                   WRITE ( io, 350 )  dir(dim), dir(dim)
1592                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1593                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1594                                      mask_loop(mid,dim,1:2)
1595                ELSE
1596                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1597                                      mask_loop(mid,dim,1:3)
1598                ENDIF
1599             ENDDO
1600          ENDIF
1601
1602       ENDDO
1603    ENDDO
1604
1605!
1606!-- Timeseries
1607    IF ( dt_dots /= 9999999.9_wp )  THEN
1608       WRITE ( io, 340 )
1609
1610       output_format = output_format_netcdf
1611       WRITE ( io, 344 )  output_format
1612       WRITE ( io, 341 )  dt_dots
1613    ENDIF
1614
1615#if defined( __dvrp_graphics )
1616!
1617!-- Dvrp-output
1618    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1619       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1620                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1621       i = 1
1622       l = 0
1623       m = 0
1624       DO WHILE ( mode_dvrp(i) /= ' ' )
1625          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1626             READ ( mode_dvrp(i), '(10X,I2)' )  j
1627             l = l + 1
1628             IF ( do3d(0,j) /= ' ' )  THEN
1629                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1630                                   isosurface_color(:,l)
1631             ENDIF
1632          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1633             READ ( mode_dvrp(i), '(6X,I2)' )  j
1634             m = m + 1
1635             IF ( do2d(0,j) /= ' ' )  THEN
1636                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1637                                   slicer_range_limits_dvrp(:,m)
1638             ENDIF
1639          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1640             WRITE ( io, 363 )  dvrp_psize
1641             IF ( particle_dvrpsize /= 'none' )  THEN
1642                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1643                                   dvrpsize_interval
1644             ENDIF
1645             IF ( particle_color /= 'none' )  THEN
1646                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1647                                   color_interval
1648             ENDIF
1649          ENDIF
1650          i = i + 1
1651       ENDDO
1652
1653       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1654                          superelevation_y, superelevation, clip_dvrp_l, &
1655                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1656
1657       IF ( TRIM( topography ) /= 'flat' )  THEN
1658          WRITE ( io, 366 )  topography_color
1659          IF ( cluster_size > 1 )  THEN
1660             WRITE ( io, 367 )  cluster_size
1661          ENDIF
1662       ENDIF
1663
1664    ENDIF
1665#endif
1666
1667#if defined( __spectra )
1668!
1669!-- Spectra output
1670    IF ( dt_dosp /= 9999999.9_wp )  THEN
1671       WRITE ( io, 370 )
1672
1673       output_format = output_format_netcdf
1674       WRITE ( io, 344 )  output_format
1675       WRITE ( io, 371 )  dt_dosp
1676       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
1677       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1678                          ( spectra_direction(i), i = 1,10 ),  &
1679                          ( comp_spectra_level(i), i = 1,100 ), &
1680                          ( plot_spectra_level(i), i = 1,100 ), &
1681                          averaging_interval_sp, dt_averaging_input_pr
1682    ENDIF
1683#endif
1684
1685    WRITE ( io, 99 )
1686
1687!
1688!-- Physical quantities
1689    WRITE ( io, 400 )
1690
1691!
1692!-- Geostrophic parameters
1693    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1694       WRITE ( io, 417 )  lambda
1695    ENDIF
1696    WRITE ( io, 410 )  phi, omega, f, fs
1697
1698!
1699!-- Other quantities
1700    WRITE ( io, 411 )  g
1701    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1702       WRITE ( io, 418 )  day_init, time_utc_init
1703    ENDIF
1704
1705    WRITE ( io, 412 )  TRIM( reference_state )
1706    IF ( use_single_reference_value )  THEN
1707       IF ( ocean )  THEN
1708          WRITE ( io, 413 )  prho_reference
1709       ELSE
1710          WRITE ( io, 414 )  pt_reference
1711       ENDIF
1712    ENDIF
1713
1714!
1715!-- Cloud physics parameters
1716    IF ( cloud_physics )  THEN
1717       WRITE ( io, 415 )
1718       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1719       IF ( icloud_scheme == 0 )  THEN
1720          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1721          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1722       ENDIF
1723    ENDIF
1724
1725!
1726!-- Cloud physcis parameters / quantities / numerical methods
1727    WRITE ( io, 430 )
1728    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1729       WRITE ( io, 431 )
1730    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1731       WRITE ( io, 432 )
1732       IF ( cloud_top_radiation )  WRITE ( io, 132 )
1733       IF ( icloud_scheme == 1 )  THEN
1734          IF ( precipitation )  WRITE ( io, 133 )
1735       ELSEIF ( icloud_scheme == 0 )  THEN
1736          IF ( drizzle )  WRITE ( io, 506 )
1737          IF ( precipitation )  THEN
1738             WRITE ( io, 505 )
1739             IF ( turbulence )  WRITE ( io, 507 )
1740             IF ( ventilation_effect )  WRITE ( io, 508 )
1741             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1742          ENDIF
1743       ENDIF
1744    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1745       WRITE ( io, 433 )
1746       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1747       IF ( collision_kernel /= 'none' )  THEN
1748          WRITE ( io, 435 )  TRIM( collision_kernel )
1749          IF ( collision_kernel(6:9) == 'fast' )  THEN
1750             WRITE ( io, 436 )  radius_classes, dissipation_classes
1751          ENDIF
1752       ELSE
1753          WRITE ( io, 437 )
1754       ENDIF
1755    ENDIF
1756
1757!
1758!-- LES / turbulence parameters
1759    WRITE ( io, 450 )
1760
1761!--
1762! ... LES-constants used must still be added here
1763!--
1764    IF ( constant_diffusion )  THEN
1765       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1766                          prandtl_number
1767    ENDIF
1768    IF ( .NOT. constant_diffusion)  THEN
1769       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1770       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1771       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1772    ENDIF
1773
1774!
1775!-- Special actions during the run
1776    WRITE ( io, 470 )
1777    IF ( create_disturbances )  THEN
1778       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1779                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1780                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1781       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1782          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1783       ELSE
1784          WRITE ( io, 473 )  disturbance_energy_limit
1785       ENDIF
1786       WRITE ( io, 474 )  TRIM( random_generator )
1787    ENDIF
1788    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1789       WRITE ( io, 475 )  pt_surface_initial_change
1790    ENDIF
1791    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1792       WRITE ( io, 476 )  q_surface_initial_change       
1793    ENDIF
1794    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1795       WRITE ( io, 477 )  q_surface_initial_change       
1796    ENDIF
1797
1798    IF ( particle_advection )  THEN
1799!
1800!--    Particle attributes
1801       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1802                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1803                          end_time_prel
1804       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1805       IF ( random_start_position )  WRITE ( io, 481 )
1806       IF ( seed_follows_topography )  WRITE ( io, 496 )
1807       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1808       WRITE ( io, 495 )  total_number_of_particles
1809       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1810          WRITE ( io, 483 )  maximum_number_of_tailpoints
1811          IF ( minimum_tailpoint_distance /= 0 )  THEN
1812             WRITE ( io, 484 )  total_number_of_tails,      &
1813                                minimum_tailpoint_distance, &
1814                                maximum_tailpoint_age
1815          ENDIF
1816       ENDIF
1817       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1818          WRITE ( io, 485 )  dt_write_particle_data
1819          IF ( netcdf_data_format > 1 )  THEN
1820             output_format = 'netcdf (64 bit offset) and binary'
1821          ELSE
1822             output_format = 'netcdf and binary'
1823          ENDIF
1824          WRITE ( io, 344 )  output_format
1825       ENDIF
1826       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1827       IF ( write_particle_statistics )  WRITE ( io, 486 )
1828
1829       WRITE ( io, 487 )  number_of_particle_groups
1830
1831       DO  i = 1, number_of_particle_groups
1832          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1833             WRITE ( io, 490 )  i, 0.0_wp
1834             WRITE ( io, 492 )
1835          ELSE
1836             WRITE ( io, 490 )  i, radius(i)
1837             IF ( density_ratio(i) /= 0.0_wp )  THEN
1838                WRITE ( io, 491 )  density_ratio(i)
1839             ELSE
1840                WRITE ( io, 492 )
1841             ENDIF
1842          ENDIF
1843          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1844                             pdx(i), pdy(i), pdz(i)
1845          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1846       ENDDO
1847
1848    ENDIF
1849
1850
1851!
1852!-- Parameters of 1D-model
1853    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1854       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1855                          mixing_length_1d, dissipation_1d
1856       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1857          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1858       ENDIF
1859    ENDIF
1860
1861!
1862!-- User-defined information
1863    CALL user_header( io )
1864
1865    WRITE ( io, 99 )
1866
1867!
1868!-- Write buffer contents to disc immediately
1869    CALL local_flush( io )
1870
1871!
1872!-- Here the FORMATs start
1873
1874 99 FORMAT (1X,78('-'))
1875100 FORMAT (/1X,'******************************',4X,44('-')/        &
1876            1X,'* ',A,' *',4X,A/                               &
1877            1X,'******************************',4X,44('-'))
1878101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1879            35X,42('-'))
1880102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1881            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1882            ' Run on host:        ',A10)
1883#if defined( __parallel )
1884103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1885              ')',1X,A)
1886104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1887              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1888105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1889106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1890            35X,'because the job is running on an SMP-cluster')
1891107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1892108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1893109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1894            35X,42('-'))
1895114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1896            35X,'independent precursor runs'/             &
1897            35X,42('-'))
1898117 FORMAT (' Accelerator boards / node:  ',I2)
1899#endif
1900110 FORMAT (/' Numerical Schemes:'/ &
1901             ' -----------------'/)
1902111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1903112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1904            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1905113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1906                  ' or Upstream')
1907115 FORMAT ('     FFT and transpositions are overlapping')
1908116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1909                  ' or Upstream')
1910118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1911119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1912            '     translation velocity = ',A/ &
1913            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1914120 FORMAT (' Accelerator boards: ',8X,I2)
1915122 FORMAT (' --> Time differencing scheme: ',A)
1916123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1917            '     maximum damping coefficient: ',F5.3, ' 1/s')
1918129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1919130 FORMAT (' --> Additional prognostic equation for the total water content')
1920131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1921                  F6.2, ' K assumed')
1922132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1923            '     effective emissivity scheme')
1924133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1925134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1926135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1927                  A,'-cycle)'/ &
1928            '     number of grid levels:                   ',I2/ &
1929            '     Gauss-Seidel red/black iterations:       ',I2)
1930136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1931                  I3,')')
1932137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1933            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1934                  I3,')'/ &
1935            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1936                  I3,')')
1937139 FORMAT (' --> Loop optimization method: ',A)
1938140 FORMAT ('     maximum residual allowed:                ',E10.3)
1939141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1940142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1941                  'step')
1942143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1943                  'kinetic energy')
1944144 FORMAT ('     masking method is used')
1945150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1946                  'conserved'/ &
1947            '     using the ',A,' mode')
1948151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1949152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1950           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1951           /'     starting from dp_level_b =', F8.3, 'm', A /)
1952160 FORMAT (//' Large scale forcing and nudging:'/ &
1953              ' -------------------------------'/)
1954161 FORMAT (' --> No large scale forcing from external is used (default) ')
1955162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1956163 FORMAT ('     - large scale advection tendencies ')
1957164 FORMAT ('     - large scale subsidence velocity w_subs ')
1958165 FORMAT ('     - large scale subsidence tendencies ')
1959167 FORMAT ('     - and geostrophic wind components ug and vg')
1960168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1961                  'prognostic equation(s) for')
1962169 FORMAT ('     the scalar(s) only')
1963170 FORMAT (' --> Nudging is used')
1964171 FORMAT (' --> No nudging is used (default) ')
1965180 FORMAT ('     - prescribed surface values for temperature')
1966181 FORMAT ('     - prescribed surface fluxes for temperature')
1967182 FORMAT ('     - prescribed surface values for humidity')
1968183 FORMAT ('     - prescribed surface fluxes for humidity')
1969200 FORMAT (//' Run time and time step information:'/ &
1970             ' ----------------------------------'/)
1971201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1972             '    CFL-factor: ',F4.2)
1973202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1974203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1975             ' End time:            ',F9.3,' s')
1976204 FORMAT ( A,F9.3,' s')
1977205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1978206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1979             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1980               '  ',F9.3,' s'/                                                    &
1981             '                                      per second of simulated tim', &
1982               'e: ',F9.3,' s')
1983207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1984250 FORMAT (//' Computational grid and domain size:'/ &
1985              ' ----------------------------------'// &
1986              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1987              ' m    dz =    ',F7.3,' m'/ &
1988              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1989              ' m  z(u) = ',F10.3,' m'/)
1990252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1991              ' factor: ',F5.3/ &
1992            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1993254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1994            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1995260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1996             ' degrees')
1997270 FORMAT (//' Topography information:'/ &
1998              ' ----------------------'// &
1999              1X,'Topography: ',A)
2000271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
2001              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
2002                ' / ',I4)
2003272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
2004              ' direction' / &
2005              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
2006              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
2007278 FORMAT (' Topography grid definition convention:'/ &
2008            ' cell edge (staggered grid points'/  &
2009            ' (u in x-direction, v in y-direction))' /)
2010279 FORMAT (' Topography grid definition convention:'/ &
2011            ' cell center (scalar grid points)' /)
2012280 FORMAT (//' Vegetation canopy (drag) model:'/ &
2013              ' ------------------------------'// &
2014              ' Canopy mode: ', A / &
2015              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
2016              ' Leaf drag coefficient: ',F6.2 /)
2017281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
2018              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
2019282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
2020283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
2021              ' Height:              ',A,'  m'/ &
2022              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2023              ' Gradient:            ',A,'  m**2/m**4'/ &
2024              ' Gridpoint:           ',A)
2025284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
2026              ' Height:              ',A,'  m'/ &
2027              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2028              ' Coefficient alpha: ',F6.2 / &
2029              ' Coefficient beta: ',F6.2 / &
2030              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
2031               
2032300 FORMAT (//' Boundary conditions:'/ &
2033             ' -------------------'// &
2034             '                     p                    uv             ', &
2035             '                     pt'// &
2036             ' B. bound.: ',A/ &
2037             ' T. bound.: ',A)
2038301 FORMAT (/'                     ',A// &
2039             ' B. bound.: ',A/ &
2040             ' T. bound.: ',A)
2041303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
2042304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
2043305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
2044               'computational u,v-level:'// &
2045             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
2046             ' m   kappa = ',F4.2/ &
2047             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2048306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
2049307 FORMAT ('       Heatflux has a random normal distribution')
2050308 FORMAT ('       Predefined surface temperature')
2051309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
2052310 FORMAT (//'    1D-Model:'// &
2053             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2054311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
2055312 FORMAT ('       Predefined surface humidity')
2056313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
2057314 FORMAT ('       Predefined scalar value at the surface')
2058315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
2059316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
2060                    'atmosphere model')
2061317 FORMAT (//' Lateral boundaries:'/ &
2062            '       left/right:  ',A/    &
2063            '       north/south: ',A)
2064318 FORMAT (/'       use_cmax: ',L1 / &
2065            '       pt damping layer width = ',F8.2,' m, pt ', &
2066                    'damping factor = ',F6.4)
2067319 FORMAT ('       turbulence recycling at inflow switched on'/ &
2068            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2069            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
2070320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
2071            '                                          v: ',F9.6,' m**2/s**2')
2072321 FORMAT (//' Initial profiles:'/ &
2073              ' ----------------')
2074322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2075            '       y shift of the recycled inflow turbulence switched on'/ &
2076            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2077            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/q)
2078325 FORMAT (//' List output:'/ &
2079             ' -----------'//  &
2080            '    1D-Profiles:'/    &
2081            '       Output every             ',F8.2,' s')
2082326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
2083            '       Averaging input every    ',F8.2,' s')
2084330 FORMAT (//' Data output:'/ &
2085             ' -----------'/)
2086331 FORMAT (/'    1D-Profiles:')
2087332 FORMAT (/'       ',A)
2088333 FORMAT ('       Output every             ',F8.2,' s',/ &
2089            '       Time averaged over       ',F8.2,' s'/ &
2090            '       Averaging input every    ',F8.2,' s')
2091334 FORMAT (/'    2D-Arrays',A,':')
2092335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2093            '       Output every             ',F8.2,' s  ',A/ &
2094            '       Cross sections at ',A1,' = ',A/ &
2095            '       scalar-coordinates:   ',A,' m'/)
2096336 FORMAT (/'    3D-Arrays',A,':')
2097337 FORMAT (/'       Arrays: ',A/ &
2098            '       Output every             ',F8.2,' s  ',A/ &
2099            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2100339 FORMAT ('       No output during initial ',F8.2,' s')
2101340 FORMAT (/'    Time series:')
2102341 FORMAT ('       Output every             ',F8.2,' s'/)
2103342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2104            '       Output every             ',F8.2,' s  ',A/ &
2105            '       Time averaged over       ',F8.2,' s'/ &
2106            '       Averaging input every    ',F8.2,' s'/ &
2107            '       Cross sections at ',A1,' = ',A/ &
2108            '       scalar-coordinates:   ',A,' m'/)
2109343 FORMAT (/'       Arrays: ',A/ &
2110            '       Output every             ',F8.2,' s  ',A/ &
2111            '       Time averaged over       ',F8.2,' s'/ &
2112            '       Averaging input every    ',F8.2,' s'/ &
2113            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2114344 FORMAT ('       Output format: ',A/)
2115345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2116            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2117            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2118            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2119346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2120347 FORMAT ('       Variables: ',A/ &
2121            '       Output every             ',F8.2,' s')
2122348 FORMAT ('       Variables: ',A/ &
2123            '       Output every             ',F8.2,' s'/ &
2124            '       Time averaged over       ',F8.2,' s'/ &
2125            '       Averaging input every    ',F8.2,' s')
2126349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2127            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2128            13('       ',8(F8.2,',')/) )
2129350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2130            'all gridpoints along ',A,'-direction (default).' )
2131351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2132            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2133            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
2134352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2135353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
2136#if defined( __dvrp_graphics )
2137360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2138            '       Output every      ',F7.1,' s'/ &
2139            '       Output mode:      ',A/ &
2140            '       Host / User:      ',A,' / ',A/ &
2141            '       Directory:        ',A// &
2142            '       The sequence contains:')
2143361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2144            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2145362 FORMAT (/'       Slicer plane ',A/ &
2146            '       Slicer limits: [',F6.2,',',F6.2,']')
2147363 FORMAT (/'       Particles'/ &
2148            '          particle size:  ',F7.2,' m')
2149364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
2150                       F6.2,',',F6.2,']')
2151365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
2152            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2153                     ')'/ &
2154            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2155            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
2156366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2157367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
2158#endif
2159#if defined( __spectra )
2160370 FORMAT ('    Spectra:')
2161371 FORMAT ('       Output every ',F7.1,' s'/)
2162372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
2163            '       Directions: ', 10(A5,',')/                         &
2164            '       height levels  k = ', 20(I3,',')/                  &
2165            '                          ', 20(I3,',')/                  &
2166            '                          ', 20(I3,',')/                  &
2167            '                          ', 20(I3,',')/                  &
2168            '                          ', 19(I3,','),I3,'.'/           &
2169            '       height levels selected for standard plot:'/        &
2170            '                      k = ', 20(I3,',')/                  &
2171            '                          ', 20(I3,',')/                  &
2172            '                          ', 20(I3,',')/                  &
2173            '                          ', 20(I3,',')/                  &
2174            '                          ', 19(I3,','),I3,'.'/           &
2175            '       Time averaged over ', F7.1, ' s,' /                &
2176            '       Profiles for the time averaging are taken every ', &
2177                    F6.1,' s')
2178#endif
2179400 FORMAT (//' Physical quantities:'/ &
2180              ' -------------------'/)
2181410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
2182            '    Angular velocity    :   omega  = ',E9.3,' rad/s'/  &
2183            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2184            '                            f*     = ',F9.6,' 1/s')
2185411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
2186412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2187413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2188414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2189415 FORMAT (/' Cloud physics parameters:'/ &
2190             ' ------------------------'/)
2191416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2192            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2193            '    Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
2194            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2195            '    Vapourization heat :   L_v   = ',E8.2,' J/kg')
2196417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2197418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2198            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2199419 FORMAT (//' Land surface model information:'/ &
2200              ' ------------------------------'/)
2201420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2202            '       Height:        ',A,'  m'/ &
2203            '       Temperature:   ',A,'  K'/ &
2204            '       Gradient:      ',A,'  K/100m'/ &
2205            '       Gridpoint:     ',A)
2206421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2207            '       Height:      ',A,'  m'/ &
2208            '       Humidity:    ',A,'  kg/kg'/ &
2209            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2210            '       Gridpoint:   ',A)
2211422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2212            '       Height:                  ',A,'  m'/ &
2213            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2214            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2215            '       Gridpoint:               ',A)
2216423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2217            '       Height:      ',A,'  m'/ &
2218            '       ug:          ',A,'  m/s'/ &
2219            '       Gradient:    ',A,'  1/100s'/ &
2220            '       Gridpoint:   ',A)
2221424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2222            '       Height:      ',A,'  m'/ &
2223            '       vg:          ',A,'  m/s'/ &
2224            '       Gradient:    ',A,'  1/100s'/ &
2225            '       Gridpoint:   ',A)
2226425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2227            '       Height:     ',A,'  m'/ &
2228            '       Salinity:   ',A,'  psu'/ &
2229            '       Gradient:   ',A,'  psu/100m'/ &
2230            '       Gridpoint:  ',A)
2231426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2232            '       Height:      ',A,'  m'/ &
2233            '       w_subs:      ',A,'  m/s'/ &
2234            '       Gradient:    ',A,'  (m/s)/100m'/ &
2235            '       Gridpoint:   ',A)
2236427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2237                  ' profiles')
2238428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2239             '    NUDGING_DATA')
2240430 FORMAT (//' Cloud physics quantities / methods:'/ &
2241              ' ----------------------------------'/)
2242431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2243                 'on)')
2244432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2245            '    total water content is used.'/ &
2246            '    Condensation is parameterized via 0% - or 100% scheme.')
2247433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2248                 'icle model')
2249434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2250                 ' droplets < 1.0E-6 m')
2251435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2252436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2253                    'are used'/ &
2254            '          number of radius classes:       ',I3,'    interval ', &
2255                       '[1.0E-6,2.0E-4] m'/ &
2256            '          number of dissipation classes:   ',I2,'    interval ', &
2257                       '[0,1000] cm**2/s**3')
2258437 FORMAT ('    Droplet collision is switched off')
2259438 FORMAT (' --> Land surface type  : ',A,/ &
2260            ' --> Soil porosity type : ',A)
2261439 FORMAT (/'    Initial soil temperature and moisture profile:'// &
2262            '       Height:        ',A,'  m'/ &
2263            '       Temperature:   ',A,'  K'/ &
2264            '       Moisture:      ',A,'  m**3/m**3'/ &
2265            '       Root fraction: ',A,'  '/ &
2266            '       Gridpoint:     ',A)
2267440 FORMAT (/' --> Dewfall is allowed (default)')
2268441 FORMAT (' --> Dewfall is inhibited')
2269442 FORMAT (' --> Soil bottom is closed (water content is conserved, default)')
2270443 FORMAT (' --> Soil bottom is open (water content is not conserved)')
2271444 FORMAT (//' Radiation model information:'/                                 &
2272              ' ----------------------------'/)
2273445 FORMAT (' --> Using constant net radiation: net_radiation = ', F6.2, '  W/m**2')
2274446 FORMAT (' --> Simple radiation scheme for clear sky is used (no clouds,',  &
2275                   ' default)')
2276447 FORMAT (' --> RRTMG scheme is used')
2277448 FORMAT (/'     User-specific surface albedo: albedo = ', F5.3)
2278449 FORMAT  ('     Timestep: dt_radiation = ', F5.2, '  s')
2279
2280450 FORMAT (//' LES / Turbulence quantities:'/ &
2281              ' ---------------------------'/)
2282451 FORMAT ('    Diffusion coefficients are constant:'/ &
2283            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2284453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2285454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2286455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2287456 FORMAT (/'    Albedo is set for land surface type: ', A)
2288457 FORMAT (/'    --> Albedo is fixed during the run')
2289458 FORMAT (/'    --> Longwave radiation is disabled')
2290459 FORMAT (/'    --> Shortwave radiation is disabled.')
2291470 FORMAT (//' Actions during the simulation:'/ &
2292              ' -----------------------------'/)
2293471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2294            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2295            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2296            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2297472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2298                 ' to i/j =',I4)
2299473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2300                 1X,F5.3, ' m**2/s**2')
2301474 FORMAT ('    Random number generator used    : ',A/)
2302475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2303                 'respectively, if'/ &
2304            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2305                 ' 3D-simulation'/)
2306476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2307                 'respectively, if the'/ &
2308            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2309                 ' the 3D-simulation'/)
2310477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2311                 'respectively, if the'/ &
2312            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2313                 ' the 3D-simulation'/)
2314480 FORMAT ('    Particles:'/ &
2315            '    ---------'// &
2316            '       Particle advection is active (switched on at t = ', F7.1, &
2317                    ' s)'/ &
2318            '       Start of new particle generations every  ',F6.1,' s'/ &
2319            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2320            '                            bottom:     ', A, ' top:         ', A/&
2321            '       Maximum particle age:                 ',F9.1,' s'/ &
2322            '       Advection stopped at t = ',F9.1,' s'/)
2323481 FORMAT ('       Particles have random start positions'/)
2324482 FORMAT ('          Particles are advected only horizontally'/)
2325483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2326484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2327            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2328            '            Maximum age of the end of the tail:  ',F8.2,' s')
2329485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2330486 FORMAT ('       Particle statistics are written on file'/)
2331487 FORMAT ('       Number of particle groups: ',I2/)
2332488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2333            '          minimum timestep for advection: ', F7.5/)
2334489 FORMAT ('       Number of particles simultaneously released at each ', &
2335                    'point: ', I5/)
2336490 FORMAT ('       Particle group ',I2,':'/ &
2337            '          Particle radius: ',E10.3, 'm')
2338491 FORMAT ('          Particle inertia is activated'/ &
2339            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2340492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2341493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2342            '                                         y:',F8.1,' - ',F8.1,' m'/&
2343            '                                         z:',F8.1,' - ',F8.1,' m'/&
2344            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2345                       ' m  dz = ',F8.1,' m'/)
2346494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2347                    F8.2,' s'/)
2348495 FORMAT ('       Number of particles in total domain: ',I10/)
2349496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2350                    'as relative to the given topography')
2351500 FORMAT (//' 1D-Model parameters:'/                           &
2352              ' -------------------'//                           &
2353            '    Simulation time:                   ',F8.1,' s'/ &
2354            '    Run-controll output every:         ',F8.1,' s'/ &
2355            '    Vertical profile output every:     ',F8.1,' s'/ &
2356            '    Mixing length calculation:         ',A/         &
2357            '    Dissipation calculation:           ',A/)
2358502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2359503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2360504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2361505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2362506 FORMAT ('    Drizzle parameterization via Stokes law')
2363507 FORMAT ('    Turbulence effects on precipitation process')
2364508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2365509 FORMAT ('    Slope limiter used for sedimentation process')
2366510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2367511 FORMAT ('    Sedimentation Courant number:                  '/&
2368            '                               C_s   = ',F3.1,'        ')
2369512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2370            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2371            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2372513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2373            '+ monotonic adjustment')
2374
2375
2376 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.