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

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

bugfix in definition of character arrays within the LSM and radiation code

  • Property svn:keywords set to Id
File size: 91.5 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! Bugfix: Added TRIM statements for character strings for LSM and radiation code
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 1590 2015-05-08 13:56:27Z 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 ) TRIM( veg_type_name(veg_type) ),                       &
925                        TRIM (soil_type_name(soil_type) )
926       WRITE( io, 439 ) TRIM( coordinates ), TRIM( temperatures ),             &
927                        TRIM( gradients ), TRIM( roots ), TRIM( slices )
928
929
930    ENDIF
931
932    IF ( radiation )  THEN
933!
934!--    Write radiation model header
935       WRITE( io, 444 )
936
937       IF ( radiation_scheme == "constant" )  THEN
938          WRITE( io, 445 ) net_radiation
939       ELSEIF ( radiation_scheme == "clear-sky" )  THEN
940          WRITE( io, 446 )
941       ELSEIF ( radiation_scheme == "rrtmg" )  THEN
942          WRITE( io, 447 )
943          IF ( .NOT. lw_radiation )  WRITE( io, 458 )
944          IF ( .NOT. sw_radiation )  WRITE( io, 459 )
945       ENDIF
946
947       IF ( albedo_type == 0 )  THEN
948          WRITE( io, 448 ) albedo
949       ELSE
950          WRITE( io, 456 ) TRIM( albedo_type_name(albedo_type) )
951       ENDIF
952       IF ( constant_albedo )  THEN
953          WRITE( io, 457 )
954       ENDIF
955       WRITE( io, 449 ) dt_radiation
956    ENDIF
957
958
959!
960!-- Boundary conditions
961    IF ( ibc_p_b == 0 )  THEN
962       runten = 'p(0)     = 0      |'
963    ELSEIF ( ibc_p_b == 1 )  THEN
964       runten = 'p(0)     = p(1)   |'
965    ENDIF
966    IF ( ibc_p_t == 0 )  THEN
967       roben  = 'p(nzt+1) = 0      |'
968    ELSE
969       roben  = 'p(nzt+1) = p(nzt) |'
970    ENDIF
971
972    IF ( ibc_uv_b == 0 )  THEN
973       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
974    ELSE
975       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
976    ENDIF
977    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
978       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
979    ELSEIF ( ibc_uv_t == 0 )  THEN
980       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
981    ELSE
982       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
983    ENDIF
984
985    IF ( ibc_pt_b == 0 )  THEN
986       IF ( land_surface )  THEN
987          runten = TRIM( runten ) // ' pt(0)     = from soil model'
988       ELSE
989          runten = TRIM( runten ) // ' pt(0)     = pt_surface'
990       ENDIF
991    ELSEIF ( ibc_pt_b == 1 )  THEN
992       runten = TRIM( runten ) // ' pt(0)     = pt(1)'
993    ELSEIF ( ibc_pt_b == 2 )  THEN
994       runten = TRIM( runten ) // ' pt(0)     = from coupled model'
995    ENDIF
996    IF ( ibc_pt_t == 0 )  THEN
997       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
998    ELSEIF( ibc_pt_t == 1 )  THEN
999       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
1000    ELSEIF( ibc_pt_t == 2 )  THEN
1001       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
1002
1003    ENDIF
1004
1005    WRITE ( io, 300 )  runten, roben
1006
1007    IF ( .NOT. constant_diffusion )  THEN
1008       IF ( ibc_e_b == 1 )  THEN
1009          runten = 'e(0)     = e(1)'
1010       ELSE
1011          runten = 'e(0)     = e(1) = (u*/0.1)**2'
1012       ENDIF
1013       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
1014
1015       WRITE ( io, 301 )  'e', runten, roben       
1016
1017    ENDIF
1018
1019    IF ( ocean )  THEN
1020       runten = 'sa(0)    = sa(1)'
1021       IF ( ibc_sa_t == 0 )  THEN
1022          roben =  'sa(nzt+1) = sa_surface'
1023       ELSE
1024          roben =  'sa(nzt+1) = sa(nzt)'
1025       ENDIF
1026       WRITE ( io, 301 ) 'sa', runten, roben
1027    ENDIF
1028
1029    IF ( humidity )  THEN
1030       IF ( ibc_q_b == 0 )  THEN
1031          IF ( land_surface )  THEN
1032             runten = 'q(0)     = from soil model'
1033          ELSE
1034             runten = 'q(0)     = q_surface'
1035          ENDIF
1036
1037       ELSE
1038          runten = 'q(0)     = q(1)'
1039       ENDIF
1040       IF ( ibc_q_t == 0 )  THEN
1041          roben =  'q(nzt)   = q_top'
1042       ELSE
1043          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
1044       ENDIF
1045       WRITE ( io, 301 ) 'q', runten, roben
1046    ENDIF
1047
1048    IF ( passive_scalar )  THEN
1049       IF ( ibc_q_b == 0 )  THEN
1050          runten = 's(0)     = s_surface'
1051       ELSE
1052          runten = 's(0)     = s(1)'
1053       ENDIF
1054       IF ( ibc_q_t == 0 )  THEN
1055          roben =  's(nzt)   = s_top'
1056       ELSE
1057          roben =  's(nzt)   = s(nzt-1) + ds/dz'
1058       ENDIF
1059       WRITE ( io, 301 ) 's', runten, roben
1060    ENDIF
1061
1062    IF ( use_surface_fluxes )  THEN
1063       WRITE ( io, 303 )
1064       IF ( constant_heatflux )  THEN
1065          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1066             WRITE ( io, 306 )  shf(0,0)
1067          ELSE
1068             WRITE ( io, 306 )  surface_heatflux
1069          ENDIF
1070          IF ( random_heatflux )  WRITE ( io, 307 )
1071       ENDIF
1072       IF ( humidity  .AND.  constant_waterflux )  THEN
1073          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1074             WRITE ( io, 311 ) qsws(0,0)
1075          ELSE
1076             WRITE ( io, 311 ) surface_waterflux
1077          ENDIF
1078       ENDIF
1079       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1080          WRITE ( io, 313 ) surface_waterflux
1081       ENDIF
1082    ENDIF
1083
1084    IF ( use_top_fluxes )  THEN
1085       WRITE ( io, 304 )
1086       IF ( coupling_mode == 'uncoupled' )  THEN
1087          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
1088          IF ( constant_top_heatflux )  THEN
1089             WRITE ( io, 306 )  top_heatflux
1090          ENDIF
1091       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1092          WRITE ( io, 316 )
1093       ENDIF
1094       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1095          WRITE ( io, 309 )  top_salinityflux
1096       ENDIF
1097       IF ( humidity  .OR.  passive_scalar )  THEN
1098          WRITE ( io, 315 )
1099       ENDIF
1100    ENDIF
1101
1102    IF ( prandtl_layer )  THEN
1103       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
1104                          z0h_factor*roughness_length, kappa, &
1105                          rif_min, rif_max
1106       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
1107       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
1108          WRITE ( io, 312 )
1109       ENDIF
1110       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1111          WRITE ( io, 314 )
1112       ENDIF
1113    ELSE
1114       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
1115          WRITE ( io, 310 )  rif_min, rif_max
1116       ENDIF
1117    ENDIF
1118
1119    WRITE ( io, 317 )  bc_lr, bc_ns
1120    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1121       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
1122       IF ( turbulent_inflow )  THEN
1123          IF ( .NOT. recycling_yshift ) THEN
1124             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1125                                inflow_damping_height, inflow_damping_width
1126          ELSE
1127             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1128                                inflow_damping_height, inflow_damping_width
1129          END IF
1130       ENDIF
1131    ENDIF
1132
1133!
1134!-- Initial Profiles
1135    WRITE ( io, 321 )
1136!
1137!-- Initial wind profiles
1138    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1139
1140!
1141!-- Initial temperature profile
1142!-- Building output strings, starting with surface temperature
1143    WRITE ( temperatures, '(F6.2)' )  pt_surface
1144    gradients = '------'
1145    slices = '     0'
1146    coordinates = '   0.0'
1147    i = 1
1148    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1149
1150       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1151       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1152
1153       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1154       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1155
1156       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1157       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1158
1159       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1160       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1161
1162       IF ( i == 10 )  THEN
1163          EXIT
1164       ELSE
1165          i = i + 1
1166       ENDIF
1167
1168    ENDDO
1169
1170    IF ( .NOT. nudging )  THEN
1171       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1172                          TRIM( gradients ), TRIM( slices )
1173    ELSE
1174       WRITE ( io, 428 ) 
1175    ENDIF
1176
1177!
1178!-- Initial humidity profile
1179!-- Building output strings, starting with surface humidity
1180    IF ( humidity  .OR.  passive_scalar )  THEN
1181       WRITE ( temperatures, '(E8.1)' )  q_surface
1182       gradients = '--------'
1183       slices = '       0'
1184       coordinates = '     0.0'
1185       i = 1
1186       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1187         
1188          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1189          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1190
1191          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1192          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1193         
1194          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1195          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1196         
1197          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1198          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1199
1200          IF ( i == 10 )  THEN
1201             EXIT
1202          ELSE
1203             i = i + 1
1204          ENDIF
1205
1206       ENDDO
1207
1208       IF ( humidity )  THEN
1209          IF ( .NOT. nudging )  THEN
1210             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1211                                TRIM( gradients ), TRIM( slices )
1212          ENDIF
1213       ELSE
1214          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1215                             TRIM( gradients ), TRIM( slices )
1216       ENDIF
1217    ENDIF
1218
1219!
1220!-- Initial salinity profile
1221!-- Building output strings, starting with surface salinity
1222    IF ( ocean )  THEN
1223       WRITE ( temperatures, '(F6.2)' )  sa_surface
1224       gradients = '------'
1225       slices = '     0'
1226       coordinates = '   0.0'
1227       i = 1
1228       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1229
1230          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1231          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1232
1233          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1234          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1235
1236          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1237          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1238
1239          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1240          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1241
1242          IF ( i == 10 )  THEN
1243             EXIT
1244          ELSE
1245             i = i + 1
1246          ENDIF
1247
1248       ENDDO
1249
1250       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1251                          TRIM( gradients ), TRIM( slices )
1252    ENDIF
1253
1254
1255!
1256!-- Listing of 1D-profiles
1257    WRITE ( io, 325 )  dt_dopr_listing
1258    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1259       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1260    ENDIF
1261
1262!
1263!-- DATA output
1264    WRITE ( io, 330 )
1265    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1266       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1267    ENDIF
1268
1269!
1270!-- 1D-profiles
1271    dopr_chr = 'Profile:'
1272    IF ( dopr_n /= 0 )  THEN
1273       WRITE ( io, 331 )
1274
1275       output_format = ''
1276       output_format = output_format_netcdf
1277       WRITE ( io, 344 )  output_format
1278
1279       DO  i = 1, dopr_n
1280          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1281          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1282             WRITE ( io, 332 )  dopr_chr
1283             dopr_chr = '       :'
1284          ENDIF
1285       ENDDO
1286
1287       IF ( dopr_chr /= '' )  THEN
1288          WRITE ( io, 332 )  dopr_chr
1289       ENDIF
1290       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1291       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1292    ENDIF
1293
1294!
1295!-- 2D-arrays
1296    DO  av = 0, 1
1297
1298       i = 1
1299       do2d_xy = ''
1300       do2d_xz = ''
1301       do2d_yz = ''
1302       DO  WHILE ( do2d(av,i) /= ' ' )
1303
1304          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1305          do2d_mode = do2d(av,i)(l-1:l)
1306
1307          SELECT CASE ( do2d_mode )
1308             CASE ( 'xy' )
1309                ll = LEN_TRIM( do2d_xy )
1310                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1311             CASE ( 'xz' )
1312                ll = LEN_TRIM( do2d_xz )
1313                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1314             CASE ( 'yz' )
1315                ll = LEN_TRIM( do2d_yz )
1316                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1317          END SELECT
1318
1319          i = i + 1
1320
1321       ENDDO
1322
1323       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1324              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1325              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1326
1327          IF (  av == 0 )  THEN
1328             WRITE ( io, 334 )  ''
1329          ELSE
1330             WRITE ( io, 334 )  '(time-averaged)'
1331          ENDIF
1332
1333          IF ( do2d_at_begin )  THEN
1334             begin_chr = 'and at the start'
1335          ELSE
1336             begin_chr = ''
1337          ENDIF
1338
1339          output_format = ''
1340          output_format = output_format_netcdf
1341          WRITE ( io, 344 )  output_format
1342
1343          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1344             i = 1
1345             slices = '/'
1346             coordinates = '/'
1347!
1348!--          Building strings with index and coordinate information of the
1349!--          slices
1350             DO  WHILE ( section(i,1) /= -9999 )
1351
1352                WRITE (section_chr,'(I5)')  section(i,1)
1353                section_chr = ADJUSTL( section_chr )
1354                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1355
1356                IF ( section(i,1) == -1 )  THEN
1357                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1358                ELSE
1359                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1360                ENDIF
1361                coor_chr = ADJUSTL( coor_chr )
1362                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1363
1364                i = i + 1
1365             ENDDO
1366             IF ( av == 0 )  THEN
1367                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1368                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1369                                   TRIM( coordinates )
1370                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1371                   WRITE ( io, 339 )  skip_time_do2d_xy
1372                ENDIF
1373             ELSE
1374                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1375                                   TRIM( begin_chr ), averaging_interval, &
1376                                   dt_averaging_input, 'k', TRIM( slices ), &
1377                                   TRIM( coordinates )
1378                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1379                   WRITE ( io, 339 )  skip_time_data_output_av
1380                ENDIF
1381             ENDIF
1382             IF ( netcdf_data_format > 4 )  THEN
1383                WRITE ( io, 352 )  ntdim_2d_xy(av)
1384             ELSE
1385                WRITE ( io, 353 )
1386             ENDIF
1387          ENDIF
1388
1389          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1390             i = 1
1391             slices = '/'
1392             coordinates = '/'
1393!
1394!--          Building strings with index and coordinate information of the
1395!--          slices
1396             DO  WHILE ( section(i,2) /= -9999 )
1397
1398                WRITE (section_chr,'(I5)')  section(i,2)
1399                section_chr = ADJUSTL( section_chr )
1400                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1401
1402                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1403                coor_chr = ADJUSTL( coor_chr )
1404                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1405
1406                i = i + 1
1407             ENDDO
1408             IF ( av == 0 )  THEN
1409                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1410                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1411                                   TRIM( coordinates )
1412                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1413                   WRITE ( io, 339 )  skip_time_do2d_xz
1414                ENDIF
1415             ELSE
1416                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1417                                   TRIM( begin_chr ), averaging_interval, &
1418                                   dt_averaging_input, 'j', TRIM( slices ), &
1419                                   TRIM( coordinates )
1420                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1421                   WRITE ( io, 339 )  skip_time_data_output_av
1422                ENDIF
1423             ENDIF
1424             IF ( netcdf_data_format > 4 )  THEN
1425                WRITE ( io, 352 )  ntdim_2d_xz(av)
1426             ELSE
1427                WRITE ( io, 353 )
1428             ENDIF
1429          ENDIF
1430
1431          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1432             i = 1
1433             slices = '/'
1434             coordinates = '/'
1435!
1436!--          Building strings with index and coordinate information of the
1437!--          slices
1438             DO  WHILE ( section(i,3) /= -9999 )
1439
1440                WRITE (section_chr,'(I5)')  section(i,3)
1441                section_chr = ADJUSTL( section_chr )
1442                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1443
1444                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1445                coor_chr = ADJUSTL( coor_chr )
1446                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1447
1448                i = i + 1
1449             ENDDO
1450             IF ( av == 0 )  THEN
1451                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1452                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1453                                   TRIM( coordinates )
1454                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1455                   WRITE ( io, 339 )  skip_time_do2d_yz
1456                ENDIF
1457             ELSE
1458                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1459                                   TRIM( begin_chr ), averaging_interval, &
1460                                   dt_averaging_input, 'i', TRIM( slices ), &
1461                                   TRIM( coordinates )
1462                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1463                   WRITE ( io, 339 )  skip_time_data_output_av
1464                ENDIF
1465             ENDIF
1466             IF ( netcdf_data_format > 4 )  THEN
1467                WRITE ( io, 352 )  ntdim_2d_yz(av)
1468             ELSE
1469                WRITE ( io, 353 )
1470             ENDIF
1471          ENDIF
1472
1473       ENDIF
1474
1475    ENDDO
1476
1477!
1478!-- 3d-arrays
1479    DO  av = 0, 1
1480
1481       i = 1
1482       do3d_chr = ''
1483       DO  WHILE ( do3d(av,i) /= ' ' )
1484
1485          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1486          i = i + 1
1487
1488       ENDDO
1489
1490       IF ( do3d_chr /= '' )  THEN
1491          IF ( av == 0 )  THEN
1492             WRITE ( io, 336 )  ''
1493          ELSE
1494             WRITE ( io, 336 )  '(time-averaged)'
1495          ENDIF
1496
1497          output_format = output_format_netcdf
1498          WRITE ( io, 344 )  output_format
1499
1500          IF ( do3d_at_begin )  THEN
1501             begin_chr = 'and at the start'
1502          ELSE
1503             begin_chr = ''
1504          ENDIF
1505          IF ( av == 0 )  THEN
1506             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1507                                zu(nz_do3d), nz_do3d
1508          ELSE
1509             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1510                                TRIM( begin_chr ), averaging_interval, &
1511                                dt_averaging_input, zu(nz_do3d), nz_do3d
1512          ENDIF
1513
1514          IF ( netcdf_data_format > 4 )  THEN
1515             WRITE ( io, 352 )  ntdim_3d(av)
1516          ELSE
1517             WRITE ( io, 353 )
1518          ENDIF
1519
1520          IF ( av == 0 )  THEN
1521             IF ( skip_time_do3d /= 0.0_wp )  THEN
1522                WRITE ( io, 339 )  skip_time_do3d
1523             ENDIF
1524          ELSE
1525             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1526                WRITE ( io, 339 )  skip_time_data_output_av
1527             ENDIF
1528          ENDIF
1529
1530       ENDIF
1531
1532    ENDDO
1533
1534!
1535!-- masked arrays
1536    IF ( masks > 0 )  WRITE ( io, 345 )  &
1537         mask_scale_x, mask_scale_y, mask_scale_z
1538    DO  mid = 1, masks
1539       DO  av = 0, 1
1540
1541          i = 1
1542          domask_chr = ''
1543          DO  WHILE ( domask(mid,av,i) /= ' ' )
1544             domask_chr = TRIM( domask_chr ) // ' ' //  &
1545                          TRIM( domask(mid,av,i) ) // ','
1546             i = i + 1
1547          ENDDO
1548
1549          IF ( domask_chr /= '' )  THEN
1550             IF ( av == 0 )  THEN
1551                WRITE ( io, 346 )  '', mid
1552             ELSE
1553                WRITE ( io, 346 )  ' (time-averaged)', mid
1554             ENDIF
1555
1556             output_format = output_format_netcdf
1557!--          Parallel output not implemented for mask data, hence
1558!--          output_format must be adjusted.
1559             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1560             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1561             WRITE ( io, 344 )  output_format
1562
1563             IF ( av == 0 )  THEN
1564                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1565             ELSE
1566                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1567                                   averaging_interval, dt_averaging_input
1568             ENDIF
1569
1570             IF ( av == 0 )  THEN
1571                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1572                   WRITE ( io, 339 )  skip_time_domask(mid)
1573                ENDIF
1574             ELSE
1575                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1576                   WRITE ( io, 339 )  skip_time_data_output_av
1577                ENDIF
1578             ENDIF
1579!
1580!--          output locations
1581             DO  dim = 1, 3
1582                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1583                   count = 0
1584                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1585                      count = count + 1
1586                   ENDDO
1587                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1588                                      mask(mid,dim,:count)
1589                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1590                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1591                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1592                   WRITE ( io, 350 )  dir(dim), dir(dim)
1593                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1594                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1595                                      mask_loop(mid,dim,1:2)
1596                ELSE
1597                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1598                                      mask_loop(mid,dim,1:3)
1599                ENDIF
1600             ENDDO
1601          ENDIF
1602
1603       ENDDO
1604    ENDDO
1605
1606!
1607!-- Timeseries
1608    IF ( dt_dots /= 9999999.9_wp )  THEN
1609       WRITE ( io, 340 )
1610
1611       output_format = output_format_netcdf
1612       WRITE ( io, 344 )  output_format
1613       WRITE ( io, 341 )  dt_dots
1614    ENDIF
1615
1616#if defined( __dvrp_graphics )
1617!
1618!-- Dvrp-output
1619    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1620       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1621                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1622       i = 1
1623       l = 0
1624       m = 0
1625       DO WHILE ( mode_dvrp(i) /= ' ' )
1626          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1627             READ ( mode_dvrp(i), '(10X,I2)' )  j
1628             l = l + 1
1629             IF ( do3d(0,j) /= ' ' )  THEN
1630                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1631                                   isosurface_color(:,l)
1632             ENDIF
1633          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1634             READ ( mode_dvrp(i), '(6X,I2)' )  j
1635             m = m + 1
1636             IF ( do2d(0,j) /= ' ' )  THEN
1637                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1638                                   slicer_range_limits_dvrp(:,m)
1639             ENDIF
1640          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1641             WRITE ( io, 363 )  dvrp_psize
1642             IF ( particle_dvrpsize /= 'none' )  THEN
1643                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1644                                   dvrpsize_interval
1645             ENDIF
1646             IF ( particle_color /= 'none' )  THEN
1647                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1648                                   color_interval
1649             ENDIF
1650          ENDIF
1651          i = i + 1
1652       ENDDO
1653
1654       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1655                          superelevation_y, superelevation, clip_dvrp_l, &
1656                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1657
1658       IF ( TRIM( topography ) /= 'flat' )  THEN
1659          WRITE ( io, 366 )  topography_color
1660          IF ( cluster_size > 1 )  THEN
1661             WRITE ( io, 367 )  cluster_size
1662          ENDIF
1663       ENDIF
1664
1665    ENDIF
1666#endif
1667
1668#if defined( __spectra )
1669!
1670!-- Spectra output
1671    IF ( dt_dosp /= 9999999.9_wp )  THEN
1672       WRITE ( io, 370 )
1673
1674       output_format = output_format_netcdf
1675       WRITE ( io, 344 )  output_format
1676       WRITE ( io, 371 )  dt_dosp
1677       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
1678       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1679                          ( spectra_direction(i), i = 1,10 ),  &
1680                          ( comp_spectra_level(i), i = 1,100 ), &
1681                          ( plot_spectra_level(i), i = 1,100 ), &
1682                          averaging_interval_sp, dt_averaging_input_pr
1683    ENDIF
1684#endif
1685
1686    WRITE ( io, 99 )
1687
1688!
1689!-- Physical quantities
1690    WRITE ( io, 400 )
1691
1692!
1693!-- Geostrophic parameters
1694    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1695       WRITE ( io, 417 )  lambda
1696    ENDIF
1697    WRITE ( io, 410 )  phi, omega, f, fs
1698
1699!
1700!-- Other quantities
1701    WRITE ( io, 411 )  g
1702    IF ( radiation .AND. radiation_scheme /= 'constant' )  THEN
1703       WRITE ( io, 418 )  day_init, time_utc_init
1704    ENDIF
1705
1706    WRITE ( io, 412 )  TRIM( reference_state )
1707    IF ( use_single_reference_value )  THEN
1708       IF ( ocean )  THEN
1709          WRITE ( io, 413 )  prho_reference
1710       ELSE
1711          WRITE ( io, 414 )  pt_reference
1712       ENDIF
1713    ENDIF
1714
1715!
1716!-- Cloud physics parameters
1717    IF ( cloud_physics )  THEN
1718       WRITE ( io, 415 )
1719       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1720       IF ( icloud_scheme == 0 )  THEN
1721          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1722          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1723       ENDIF
1724    ENDIF
1725
1726!
1727!-- Cloud physcis parameters / quantities / numerical methods
1728    WRITE ( io, 430 )
1729    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1730       WRITE ( io, 431 )
1731    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1732       WRITE ( io, 432 )
1733       IF ( cloud_top_radiation )  WRITE ( io, 132 )
1734       IF ( icloud_scheme == 1 )  THEN
1735          IF ( precipitation )  WRITE ( io, 133 )
1736       ELSEIF ( icloud_scheme == 0 )  THEN
1737          IF ( drizzle )  WRITE ( io, 506 )
1738          IF ( precipitation )  THEN
1739             WRITE ( io, 505 )
1740             IF ( turbulence )  WRITE ( io, 507 )
1741             IF ( ventilation_effect )  WRITE ( io, 508 )
1742             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1743          ENDIF
1744       ENDIF
1745    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1746       WRITE ( io, 433 )
1747       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1748       IF ( collision_kernel /= 'none' )  THEN
1749          WRITE ( io, 435 )  TRIM( collision_kernel )
1750          IF ( collision_kernel(6:9) == 'fast' )  THEN
1751             WRITE ( io, 436 )  radius_classes, dissipation_classes
1752          ENDIF
1753       ELSE
1754          WRITE ( io, 437 )
1755       ENDIF
1756    ENDIF
1757
1758!
1759!-- LES / turbulence parameters
1760    WRITE ( io, 450 )
1761
1762!--
1763! ... LES-constants used must still be added here
1764!--
1765    IF ( constant_diffusion )  THEN
1766       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1767                          prandtl_number
1768    ENDIF
1769    IF ( .NOT. constant_diffusion)  THEN
1770       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1771       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1772       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1773    ENDIF
1774
1775!
1776!-- Special actions during the run
1777    WRITE ( io, 470 )
1778    IF ( create_disturbances )  THEN
1779       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1780                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1781                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1782       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1783          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1784       ELSE
1785          WRITE ( io, 473 )  disturbance_energy_limit
1786       ENDIF
1787       WRITE ( io, 474 )  TRIM( random_generator )
1788    ENDIF
1789    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1790       WRITE ( io, 475 )  pt_surface_initial_change
1791    ENDIF
1792    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1793       WRITE ( io, 476 )  q_surface_initial_change       
1794    ENDIF
1795    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1796       WRITE ( io, 477 )  q_surface_initial_change       
1797    ENDIF
1798
1799    IF ( particle_advection )  THEN
1800!
1801!--    Particle attributes
1802       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1803                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1804                          end_time_prel
1805       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1806       IF ( random_start_position )  WRITE ( io, 481 )
1807       IF ( seed_follows_topography )  WRITE ( io, 496 )
1808       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1809       WRITE ( io, 495 )  total_number_of_particles
1810       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1811          WRITE ( io, 483 )  maximum_number_of_tailpoints
1812          IF ( minimum_tailpoint_distance /= 0 )  THEN
1813             WRITE ( io, 484 )  total_number_of_tails,      &
1814                                minimum_tailpoint_distance, &
1815                                maximum_tailpoint_age
1816          ENDIF
1817       ENDIF
1818       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1819          WRITE ( io, 485 )  dt_write_particle_data
1820          IF ( netcdf_data_format > 1 )  THEN
1821             output_format = 'netcdf (64 bit offset) and binary'
1822          ELSE
1823             output_format = 'netcdf and binary'
1824          ENDIF
1825          WRITE ( io, 344 )  output_format
1826       ENDIF
1827       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1828       IF ( write_particle_statistics )  WRITE ( io, 486 )
1829
1830       WRITE ( io, 487 )  number_of_particle_groups
1831
1832       DO  i = 1, number_of_particle_groups
1833          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1834             WRITE ( io, 490 )  i, 0.0_wp
1835             WRITE ( io, 492 )
1836          ELSE
1837             WRITE ( io, 490 )  i, radius(i)
1838             IF ( density_ratio(i) /= 0.0_wp )  THEN
1839                WRITE ( io, 491 )  density_ratio(i)
1840             ELSE
1841                WRITE ( io, 492 )
1842             ENDIF
1843          ENDIF
1844          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1845                             pdx(i), pdy(i), pdz(i)
1846          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1847       ENDDO
1848
1849    ENDIF
1850
1851
1852!
1853!-- Parameters of 1D-model
1854    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1855       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1856                          mixing_length_1d, dissipation_1d
1857       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1858          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1859       ENDIF
1860    ENDIF
1861
1862!
1863!-- User-defined information
1864    CALL user_header( io )
1865
1866    WRITE ( io, 99 )
1867
1868!
1869!-- Write buffer contents to disc immediately
1870    CALL local_flush( io )
1871
1872!
1873!-- Here the FORMATs start
1874
1875 99 FORMAT (1X,78('-'))
1876100 FORMAT (/1X,'******************************',4X,44('-')/        &
1877            1X,'* ',A,' *',4X,A/                               &
1878            1X,'******************************',4X,44('-'))
1879101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1880            35X,42('-'))
1881102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1882            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1883            ' Run on host:        ',A10)
1884#if defined( __parallel )
1885103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1886              ')',1X,A)
1887104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1888              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1889105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1890106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1891            35X,'because the job is running on an SMP-cluster')
1892107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1893108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1894109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1895            35X,42('-'))
1896114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1897            35X,'independent precursor runs'/             &
1898            35X,42('-'))
1899117 FORMAT (' Accelerator boards / node:  ',I2)
1900#endif
1901110 FORMAT (/' Numerical Schemes:'/ &
1902             ' -----------------'/)
1903111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1904112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1905            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1906113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1907                  ' or Upstream')
1908115 FORMAT ('     FFT and transpositions are overlapping')
1909116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1910                  ' or Upstream')
1911118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1912119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1913            '     translation velocity = ',A/ &
1914            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1915120 FORMAT (' Accelerator boards: ',8X,I2)
1916122 FORMAT (' --> Time differencing scheme: ',A)
1917123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1918            '     maximum damping coefficient: ',F5.3, ' 1/s')
1919129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1920130 FORMAT (' --> Additional prognostic equation for the total water content')
1921131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1922                  F6.2, ' K assumed')
1923132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1924            '     effective emissivity scheme')
1925133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1926134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1927135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1928                  A,'-cycle)'/ &
1929            '     number of grid levels:                   ',I2/ &
1930            '     Gauss-Seidel red/black iterations:       ',I2)
1931136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1932                  I3,')')
1933137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1934            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1935                  I3,')'/ &
1936            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1937                  I3,')')
1938139 FORMAT (' --> Loop optimization method: ',A)
1939140 FORMAT ('     maximum residual allowed:                ',E10.3)
1940141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1941142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1942                  'step')
1943143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1944                  'kinetic energy')
1945144 FORMAT ('     masking method is used')
1946150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1947                  'conserved'/ &
1948            '     using the ',A,' mode')
1949151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1950152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1951           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1952           /'     starting from dp_level_b =', F8.3, 'm', A /)
1953160 FORMAT (//' Large scale forcing and nudging:'/ &
1954              ' -------------------------------'/)
1955161 FORMAT (' --> No large scale forcing from external is used (default) ')
1956162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1957163 FORMAT ('     - large scale advection tendencies ')
1958164 FORMAT ('     - large scale subsidence velocity w_subs ')
1959165 FORMAT ('     - large scale subsidence tendencies ')
1960167 FORMAT ('     - and geostrophic wind components ug and vg')
1961168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1962                  'prognostic equation(s) for')
1963169 FORMAT ('     the scalar(s) only')
1964170 FORMAT (' --> Nudging is used')
1965171 FORMAT (' --> No nudging is used (default) ')
1966180 FORMAT ('     - prescribed surface values for temperature')
1967181 FORMAT ('     - prescribed surface fluxes for temperature')
1968182 FORMAT ('     - prescribed surface values for humidity')
1969183 FORMAT ('     - prescribed surface fluxes for humidity')
1970200 FORMAT (//' Run time and time step information:'/ &
1971             ' ----------------------------------'/)
1972201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1973             '    CFL-factor: ',F4.2)
1974202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1975203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1976             ' End time:            ',F9.3,' s')
1977204 FORMAT ( A,F9.3,' s')
1978205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1979206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1980             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1981               '  ',F9.3,' s'/                                                    &
1982             '                                      per second of simulated tim', &
1983               'e: ',F9.3,' s')
1984207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1985250 FORMAT (//' Computational grid and domain size:'/ &
1986              ' ----------------------------------'// &
1987              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1988              ' m    dz =    ',F7.3,' m'/ &
1989              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1990              ' m  z(u) = ',F10.3,' m'/)
1991252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1992              ' factor: ',F5.3/ &
1993            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1994254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1995            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1996260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1997             ' degrees')
1998270 FORMAT (//' Topography information:'/ &
1999              ' ----------------------'// &
2000              1X,'Topography: ',A)
2001271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
2002              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
2003                ' / ',I4)
2004272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
2005              ' direction' / &
2006              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
2007              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
2008278 FORMAT (' Topography grid definition convention:'/ &
2009            ' cell edge (staggered grid points'/  &
2010            ' (u in x-direction, v in y-direction))' /)
2011279 FORMAT (' Topography grid definition convention:'/ &
2012            ' cell center (scalar grid points)' /)
2013280 FORMAT (//' Vegetation canopy (drag) model:'/ &
2014              ' ------------------------------'// &
2015              ' Canopy mode: ', A / &
2016              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
2017              ' Leaf drag coefficient: ',F6.2 /)
2018281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
2019              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
2020282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
2021283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
2022              ' Height:              ',A,'  m'/ &
2023              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2024              ' Gradient:            ',A,'  m**2/m**4'/ &
2025              ' Gridpoint:           ',A)
2026284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
2027              ' Height:              ',A,'  m'/ &
2028              ' Leaf area density:   ',A,'  m**2/m**3'/ &
2029              ' Coefficient alpha: ',F6.2 / &
2030              ' Coefficient beta: ',F6.2 / &
2031              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
2032               
2033300 FORMAT (//' Boundary conditions:'/ &
2034             ' -------------------'// &
2035             '                     p                    uv             ', &
2036             '                     pt'// &
2037             ' B. bound.: ',A/ &
2038             ' T. bound.: ',A)
2039301 FORMAT (/'                     ',A// &
2040             ' B. bound.: ',A/ &
2041             ' T. bound.: ',A)
2042303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
2043304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
2044305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
2045               'computational u,v-level:'// &
2046             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
2047             ' m   kappa = ',F4.2/ &
2048             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2049306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
2050307 FORMAT ('       Heatflux has a random normal distribution')
2051308 FORMAT ('       Predefined surface temperature')
2052309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
2053310 FORMAT (//'    1D-Model:'// &
2054             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
2055311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
2056312 FORMAT ('       Predefined surface humidity')
2057313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
2058314 FORMAT ('       Predefined scalar value at the surface')
2059315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
2060316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
2061                    'atmosphere model')
2062317 FORMAT (//' Lateral boundaries:'/ &
2063            '       left/right:  ',A/    &
2064            '       north/south: ',A)
2065318 FORMAT (/'       use_cmax: ',L1 / &
2066            '       pt damping layer width = ',F8.2,' m, pt ', &
2067                    'damping factor = ',F6.4)
2068319 FORMAT ('       turbulence recycling at inflow switched on'/ &
2069            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2070            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
2071320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
2072            '                                          v: ',F9.6,' m**2/s**2')
2073321 FORMAT (//' Initial profiles:'/ &
2074              ' ----------------')
2075322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2076            '       y shift of the recycled inflow turbulence switched on'/ &
2077            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2078            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/q)
2079325 FORMAT (//' List output:'/ &
2080             ' -----------'//  &
2081            '    1D-Profiles:'/    &
2082            '       Output every             ',F8.2,' s')
2083326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
2084            '       Averaging input every    ',F8.2,' s')
2085330 FORMAT (//' Data output:'/ &
2086             ' -----------'/)
2087331 FORMAT (/'    1D-Profiles:')
2088332 FORMAT (/'       ',A)
2089333 FORMAT ('       Output every             ',F8.2,' s',/ &
2090            '       Time averaged over       ',F8.2,' s'/ &
2091            '       Averaging input every    ',F8.2,' s')
2092334 FORMAT (/'    2D-Arrays',A,':')
2093335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2094            '       Output every             ',F8.2,' s  ',A/ &
2095            '       Cross sections at ',A1,' = ',A/ &
2096            '       scalar-coordinates:   ',A,' m'/)
2097336 FORMAT (/'    3D-Arrays',A,':')
2098337 FORMAT (/'       Arrays: ',A/ &
2099            '       Output every             ',F8.2,' s  ',A/ &
2100            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2101339 FORMAT ('       No output during initial ',F8.2,' s')
2102340 FORMAT (/'    Time series:')
2103341 FORMAT ('       Output every             ',F8.2,' s'/)
2104342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2105            '       Output every             ',F8.2,' s  ',A/ &
2106            '       Time averaged over       ',F8.2,' s'/ &
2107            '       Averaging input every    ',F8.2,' s'/ &
2108            '       Cross sections at ',A1,' = ',A/ &
2109            '       scalar-coordinates:   ',A,' m'/)
2110343 FORMAT (/'       Arrays: ',A/ &
2111            '       Output every             ',F8.2,' s  ',A/ &
2112            '       Time averaged over       ',F8.2,' s'/ &
2113            '       Averaging input every    ',F8.2,' s'/ &
2114            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2115344 FORMAT ('       Output format: ',A/)
2116345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2117            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2118            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2119            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2120346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2121347 FORMAT ('       Variables: ',A/ &
2122            '       Output every             ',F8.2,' s')
2123348 FORMAT ('       Variables: ',A/ &
2124            '       Output every             ',F8.2,' s'/ &
2125            '       Time averaged over       ',F8.2,' s'/ &
2126            '       Averaging input every    ',F8.2,' s')
2127349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2128            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2129            13('       ',8(F8.2,',')/) )
2130350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2131            'all gridpoints along ',A,'-direction (default).' )
2132351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2133            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2134            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
2135352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2136353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
2137#if defined( __dvrp_graphics )
2138360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2139            '       Output every      ',F7.1,' s'/ &
2140            '       Output mode:      ',A/ &
2141            '       Host / User:      ',A,' / ',A/ &
2142            '       Directory:        ',A// &
2143            '       The sequence contains:')
2144361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2145            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2146362 FORMAT (/'       Slicer plane ',A/ &
2147            '       Slicer limits: [',F6.2,',',F6.2,']')
2148363 FORMAT (/'       Particles'/ &
2149            '          particle size:  ',F7.2,' m')
2150364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
2151                       F6.2,',',F6.2,']')
2152365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
2153            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2154                     ')'/ &
2155            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2156            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
2157366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2158367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
2159#endif
2160#if defined( __spectra )
2161370 FORMAT ('    Spectra:')
2162371 FORMAT ('       Output every ',F7.1,' s'/)
2163372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
2164            '       Directions: ', 10(A5,',')/                         &
2165            '       height levels  k = ', 20(I3,',')/                  &
2166            '                          ', 20(I3,',')/                  &
2167            '                          ', 20(I3,',')/                  &
2168            '                          ', 20(I3,',')/                  &
2169            '                          ', 19(I3,','),I3,'.'/           &
2170            '       height levels selected for standard plot:'/        &
2171            '                      k = ', 20(I3,',')/                  &
2172            '                          ', 20(I3,',')/                  &
2173            '                          ', 20(I3,',')/                  &
2174            '                          ', 20(I3,',')/                  &
2175            '                          ', 19(I3,','),I3,'.'/           &
2176            '       Time averaged over ', F7.1, ' s,' /                &
2177            '       Profiles for the time averaging are taken every ', &
2178                    F6.1,' s')
2179#endif
2180400 FORMAT (//' Physical quantities:'/ &
2181              ' -------------------'/)
2182410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
2183            '    Angular velocity    :   omega  = ',E9.3,' rad/s'/  &
2184            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2185            '                            f*     = ',F9.6,' 1/s')
2186411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
2187412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2188413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2189414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2190415 FORMAT (/' Cloud physics parameters:'/ &
2191             ' ------------------------'/)
2192416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2193            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2194            '    Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
2195            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2196            '    Vapourization heat :   L_v   = ',E8.2,' J/kg')
2197417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2198418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2199            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2200419 FORMAT (//' Land surface model information:'/ &
2201              ' ------------------------------'/)
2202420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2203            '       Height:        ',A,'  m'/ &
2204            '       Temperature:   ',A,'  K'/ &
2205            '       Gradient:      ',A,'  K/100m'/ &
2206            '       Gridpoint:     ',A)
2207421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2208            '       Height:      ',A,'  m'/ &
2209            '       Humidity:    ',A,'  kg/kg'/ &
2210            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2211            '       Gridpoint:   ',A)
2212422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2213            '       Height:                  ',A,'  m'/ &
2214            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2215            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2216            '       Gridpoint:               ',A)
2217423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2218            '       Height:      ',A,'  m'/ &
2219            '       ug:          ',A,'  m/s'/ &
2220            '       Gradient:    ',A,'  1/100s'/ &
2221            '       Gridpoint:   ',A)
2222424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2223            '       Height:      ',A,'  m'/ &
2224            '       vg:          ',A,'  m/s'/ &
2225            '       Gradient:    ',A,'  1/100s'/ &
2226            '       Gridpoint:   ',A)
2227425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2228            '       Height:     ',A,'  m'/ &
2229            '       Salinity:   ',A,'  psu'/ &
2230            '       Gradient:   ',A,'  psu/100m'/ &
2231            '       Gridpoint:  ',A)
2232426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2233            '       Height:      ',A,'  m'/ &
2234            '       w_subs:      ',A,'  m/s'/ &
2235            '       Gradient:    ',A,'  (m/s)/100m'/ &
2236            '       Gridpoint:   ',A)
2237427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2238                  ' profiles')
2239428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2240             '    NUDGING_DATA')
2241430 FORMAT (//' Cloud physics quantities / methods:'/ &
2242              ' ----------------------------------'/)
2243431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2244                 'on)')
2245432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2246            '    total water content is used.'/ &
2247            '    Condensation is parameterized via 0% - or 100% scheme.')
2248433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2249                 'icle model')
2250434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2251                 ' droplets < 1.0E-6 m')
2252435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2253436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2254                    'are used'/ &
2255            '          number of radius classes:       ',I3,'    interval ', &
2256                       '[1.0E-6,2.0E-4] m'/ &
2257            '          number of dissipation classes:   ',I2,'    interval ', &
2258                       '[0,1000] cm**2/s**3')
2259437 FORMAT ('    Droplet collision is switched off')
2260438 FORMAT (' --> Land surface type  : ',A,/ &
2261            ' --> Soil porosity type : ',A)
2262439 FORMAT (/'    Initial soil temperature and moisture profile:'// &
2263            '       Height:        ',A,'  m'/ &
2264            '       Temperature:   ',A,'  K'/ &
2265            '       Moisture:      ',A,'  m**3/m**3'/ &
2266            '       Root fraction: ',A,'  '/ &
2267            '       Gridpoint:     ',A)
2268440 FORMAT (/' --> Dewfall is allowed (default)')
2269441 FORMAT (' --> Dewfall is inhibited')
2270442 FORMAT (' --> Soil bottom is closed (water content is conserved, default)')
2271443 FORMAT (' --> Soil bottom is open (water content is not conserved)')
2272444 FORMAT (//' Radiation model information:'/                                 &
2273              ' ----------------------------'/)
2274445 FORMAT (' --> Using constant net radiation: net_radiation = ', F6.2, '  W/m**2')
2275446 FORMAT (' --> Simple radiation scheme for clear sky is used (no clouds,',  &
2276                   ' default)')
2277447 FORMAT (' --> RRTMG scheme is used')
2278448 FORMAT (/'     User-specific surface albedo: albedo = ', F5.3)
2279449 FORMAT  ('     Timestep: dt_radiation = ', F5.2, '  s')
2280
2281450 FORMAT (//' LES / Turbulence quantities:'/ &
2282              ' ---------------------------'/)
2283451 FORMAT ('    Diffusion coefficients are constant:'/ &
2284            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2285453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2286454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2287455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2288456 FORMAT (/'    Albedo is set for land surface type: ', A)
2289457 FORMAT (/'    --> Albedo is fixed during the run')
2290458 FORMAT (/'    --> Longwave radiation is disabled')
2291459 FORMAT (/'    --> Shortwave radiation is disabled.')
2292470 FORMAT (//' Actions during the simulation:'/ &
2293              ' -----------------------------'/)
2294471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2295            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2296            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2297            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2298472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2299                 ' to i/j =',I4)
2300473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2301                 1X,F5.3, ' m**2/s**2')
2302474 FORMAT ('    Random number generator used    : ',A/)
2303475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2304                 'respectively, if'/ &
2305            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2306                 ' 3D-simulation'/)
2307476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2308                 'respectively, if the'/ &
2309            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2310                 ' the 3D-simulation'/)
2311477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2312                 'respectively, if the'/ &
2313            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2314                 ' the 3D-simulation'/)
2315480 FORMAT ('    Particles:'/ &
2316            '    ---------'// &
2317            '       Particle advection is active (switched on at t = ', F7.1, &
2318                    ' s)'/ &
2319            '       Start of new particle generations every  ',F6.1,' s'/ &
2320            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2321            '                            bottom:     ', A, ' top:         ', A/&
2322            '       Maximum particle age:                 ',F9.1,' s'/ &
2323            '       Advection stopped at t = ',F9.1,' s'/)
2324481 FORMAT ('       Particles have random start positions'/)
2325482 FORMAT ('          Particles are advected only horizontally'/)
2326483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2327484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2328            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2329            '            Maximum age of the end of the tail:  ',F8.2,' s')
2330485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2331486 FORMAT ('       Particle statistics are written on file'/)
2332487 FORMAT ('       Number of particle groups: ',I2/)
2333488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2334            '          minimum timestep for advection: ', F7.5/)
2335489 FORMAT ('       Number of particles simultaneously released at each ', &
2336                    'point: ', I5/)
2337490 FORMAT ('       Particle group ',I2,':'/ &
2338            '          Particle radius: ',E10.3, 'm')
2339491 FORMAT ('          Particle inertia is activated'/ &
2340            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2341492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2342493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2343            '                                         y:',F8.1,' - ',F8.1,' m'/&
2344            '                                         z:',F8.1,' - ',F8.1,' m'/&
2345            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2346                       ' m  dz = ',F8.1,' m'/)
2347494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2348                    F8.2,' s'/)
2349495 FORMAT ('       Number of particles in total domain: ',I10/)
2350496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2351                    'as relative to the given topography')
2352500 FORMAT (//' 1D-Model parameters:'/                           &
2353              ' -------------------'//                           &
2354            '    Simulation time:                   ',F8.1,' s'/ &
2355            '    Run-controll output every:         ',F8.1,' s'/ &
2356            '    Vertical profile output every:     ',F8.1,' s'/ &
2357            '    Mixing length calculation:         ',A/         &
2358            '    Dissipation calculation:           ',A/)
2359502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2360503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2361504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2362505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2363506 FORMAT ('    Drizzle parameterization via Stokes law')
2364507 FORMAT ('    Turbulence effects on precipitation process')
2365508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2366509 FORMAT ('    Slope limiter used for sedimentation process')
2367510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2368511 FORMAT ('    Sedimentation Courant number:                  '/&
2369            '                               C_s   = ',F3.1,'        ')
2370512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2371            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2372            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2373513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2374            '+ monotonic adjustment')
2375
2376
2377 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.