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

Last change on this file since 1560 was 1560, checked in by keck, 9 years ago

implemented possibility of adding a y shift to the recycled inflow turbulence

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