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

Last change on this file since 1958 was 1958, checked in by suehring, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 86.5 KB
Line 
1!> @file header.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2016 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: header.f90 1958 2016-07-07 10:51:40Z suehring $
26!
27! 1957 2016-07-07 10:43:48Z suehring
28! flight module added
29!
30! 1931 2016-06-10 12:06:59Z suehring
31! Rename multigrid into multigrid_noopt
32!
33! 1902 2016-05-09 11:18:56Z suehring
34! Write information about masking_method only for multigrid solver
35!
36! 1849 2016-04-08 11:33:18Z hoffmann
37! Adapted for modularization of microphysics
38!
39! 1833 2016-04-07 14:23:03Z raasch
40! spectrum renamed spectra_mod, output of spectra related quantities moved to
41! spectra_mod
42!
43! 1831 2016-04-07 13:15:51Z hoffmann
44! turbulence renamed collision_turbulence,
45! drizzle renamed cloud_water_sedimentation
46!
47! 1826 2016-04-07 12:01:39Z maronga
48! Moved radiation model header output to the respective module.
49! Moved canopy model header output to the respective module.
50!
51! 1822 2016-04-07 07:49:42Z hoffmann
52! Tails removed. icloud_scheme replaced by microphysics_*
53!
54! 1817 2016-04-06 15:44:20Z maronga
55! Moved land_surface_model header output to the respective module.
56!
57! 1808 2016-04-05 19:44:00Z raasch
58! routine local_flush replaced by FORTRAN statement
59!
60! 1797 2016-03-21 16:50:28Z raasch
61! output of nesting datatransfer mode
62!
63! 1791 2016-03-11 10:41:25Z raasch
64! output of nesting informations of all domains
65!
66! 1788 2016-03-10 11:01:04Z maronga
67! Parameter dewfall removed
68!
69! 1786 2016-03-08 05:49:27Z raasch
70! cpp-direktives for spectra removed
71!
72! 1783 2016-03-06 18:36:17Z raasch
73! netcdf module and variable names changed, output of netcdf_deflate
74!
75! 1764 2016-02-28 12:45:19Z raasch
76! output of nesting informations
77!
78! 1697 2015-10-28 17:14:10Z raasch
79! small E- and F-FORMAT changes to avoid informative compiler messages about
80! insufficient field width
81!
82! 1691 2015-10-26 16:17:44Z maronga
83! Renamed prandtl_layer to constant_flux_layer, renames rif_min/rif_max to
84! zeta_min/zeta_max.
85!
86! 1682 2015-10-07 23:56:08Z knoop
87! Code annotations made doxygen readable
88!
89! 1675 2015-10-02 08:28:59Z gronemeier
90! Bugfix: Definition of topography grid levels
91!
92! 1660 2015-09-21 08:15:16Z gronemeier
93! Bugfix: Definition of building/street canyon height if vertical grid stretching
94!         starts below the maximum topography height.
95!
96! 1590 2015-05-08 13:56:27Z maronga
97! Bugfix: Added TRIM statements for character strings for LSM and radiation code
98!
99! 1585 2015-04-30 07:05:52Z maronga
100! Further output for radiation model(s).
101!
102! 1575 2015-03-27 09:56:27Z raasch
103! adjustments for psolver-queries, output of seed_follows_topography
104!
105! 1560 2015-03-06 10:48:54Z keck
106! output for recycling y shift
107!
108! 1557 2015-03-05 16:43:04Z suehring
109! output for monotonic limiter
110!
111! 1551 2015-03-03 14:18:16Z maronga
112! Added informal output for land surface model and radiation model. Removed typo.
113!
114! 1496 2014-12-02 17:25:50Z maronga
115! Renamed: "radiation -> "cloud_top_radiation"
116!
117! 1484 2014-10-21 10:53:05Z kanani
118! Changes due to new module structure of the plant canopy model:
119!   module plant_canopy_model_mod and output for new canopy model parameters
120!   (alpha_lad, beta_lad, lai_beta,...) added,
121!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
122!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
123!   learde renamed leaf_area_density.
124! Bugfix: DO-WHILE-loop for lad header information additionally restricted
125! by maximum number of gradient levels (currently 10)
126!
127! 1482 2014-10-18 12:34:45Z raasch
128! information about calculated or predefined virtual processor topology adjusted
129!
130! 1468 2014-09-24 14:06:57Z maronga
131! Adapted for use on up to 6-digit processor cores
132!
133! 1429 2014-07-15 12:53:45Z knoop
134! header exended to provide ensemble_member_nr if specified
135!
136! 1376 2014-04-26 11:21:22Z boeske
137! Correction of typos
138!
139! 1365 2014-04-22 15:03:56Z boeske
140! New section 'Large scale forcing and nudging':
141! output of large scale forcing and nudging information,
142! new section for initial profiles created
143!
144! 1359 2014-04-11 17:15:14Z hoffmann
145! dt_sort_particles removed
146!
147! 1353 2014-04-08 15:21:23Z heinze
148! REAL constants provided with KIND-attribute
149!
150! 1327 2014-03-21 11:00:16Z raasch
151! parts concerning iso2d and avs output removed,
152! -netcdf output queries
153!
154! 1324 2014-03-21 09:13:16Z suehring
155! Bugfix: module spectrum added
156!
157! 1322 2014-03-20 16:38:49Z raasch
158! REAL functions provided with KIND-attribute,
159! some REAL constants defined as wp-kind
160!
161! 1320 2014-03-20 08:40:49Z raasch
162! ONLY-attribute added to USE-statements,
163! kind-parameters added to all INTEGER and REAL declaration statements,
164! kinds are defined in new module kinds,
165! revision history before 2012 removed,
166! comment fields (!:) to be used for variable explanations added to
167! all variable declaration statements
168!
169! 1308 2014-03-13 14:58:42Z fricke
170! output of the fixed number of output time levels
171! output_format adjusted for masked data if netcdf_data_format > 5
172!
173! 1299 2014-03-06 13:15:21Z heinze
174! output for using large_scale subsidence in combination
175! with large_scale_forcing
176! reformatting, more detailed explanations
177!
178! 1241 2013-10-30 11:36:58Z heinze
179! output for nudging + large scale forcing from external file
180!
181! 1216 2013-08-26 09:31:42Z raasch
182! output for transpose_compute_overlap
183!
184! 1212 2013-08-15 08:46:27Z raasch
185! output for poisfft_hybrid removed
186!
187! 1179 2013-06-14 05:57:58Z raasch
188! output of reference_state, use_reference renamed use_single_reference_value
189!
190! 1159 2013-05-21 11:58:22Z fricke
191! +use_cmax
192!
193! 1115 2013-03-26 18:16:16Z hoffmann
194! descriptions for Seifert-Beheng-cloud-physics-scheme added
195!
196! 1111 2013-03-08 23:54:10Z raasch
197! output of accelerator board information
198! ibc_p_b = 2 removed
199!
200! 1108 2013-03-05 07:03:32Z raasch
201! bugfix for r1106
202!
203! 1106 2013-03-04 05:31:38Z raasch
204! some format changes for coupled runs
205!
206! 1092 2013-02-02 11:24:22Z raasch
207! unused variables removed
208!
209! 1036 2012-10-22 13:43:42Z raasch
210! code put under GPL (PALM 3.9)
211!
212! 1031 2012-10-19 14:35:30Z raasch
213! output of netCDF data format modified
214!
215! 1015 2012-09-27 09:23:24Z raasch
216! output of Adjustment of mixing length to the Prandtl mixing length at first
217! grid point above ground removed
218!
219! 1003 2012-09-14 14:35:53Z raasch
220! output of information about equal/unequal subdomain size removed
221!
222! 1001 2012-09-13 14:08:46Z raasch
223! all actions concerning leapfrog- and upstream-spline-scheme removed
224!
225! 978 2012-08-09 08:28:32Z fricke
226! -km_damp_max, outflow_damping_width
227! +pt_damping_factor, pt_damping_width
228! +z0h
229!
230! 964 2012-07-26 09:14:24Z raasch
231! output of profil-related quantities removed
232!
233! 940 2012-07-09 14:31:00Z raasch
234! Output in case of simulations for pure neutral stratification (no pt-equation
235! solved)
236!
237! 927 2012-06-06 19:15:04Z raasch
238! output of masking_method for mg-solver
239!
240! 868 2012-03-28 12:21:07Z raasch
241! translation velocity in Galilean transformation changed to 0.6 * ug
242!
243! 833 2012-02-22 08:55:55Z maronga
244! Adjusted format for leaf area density
245!
246! 828 2012-02-21 12:00:36Z raasch
247! output of dissipation_classes + radius_classes
248!
249! 825 2012-02-19 03:03:44Z raasch
250! Output of cloud physics parameters/quantities complemented and restructured
251!
252! Revision 1.1  1997/08/11 06:17:20  raasch
253! Initial revision
254!
255!
256! Description:
257! ------------
258!> Writing a header with all important information about the current run.
259!> This subroutine is called three times, two times at the beginning
260!> (writing information on files RUN_CONTROL and HEADER) and one time at the
261!> end of the run, then writing additional information about CPU-usage on file
262!> header.
263!-----------------------------------------------------------------------------!
264 SUBROUTINE header
265 
266
267    USE arrays_3d,                                                             &
268        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu, zw
269       
270    USE control_parameters
271       
272    USE cloud_parameters,                                                      &
273        ONLY:  cp, l_v, r_d
274
275    USE cpulog,                                                                &
276        ONLY:  log_point_s
277       
278    USE dvrp_variables,                                                        &
279        ONLY:  use_seperate_pe_for_dvrp_output
280       
281    USE flight_mod,                                                            &
282        ONLY:  flight_header
283       
284    USE grid_variables,                                                        &
285        ONLY:  dx, dy
286       
287    USE indices,                                                               &
288        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
289               nys_mg, nzt, nzt_mg
290       
291    USE kinds
292 
293    USE land_surface_model_mod,                                                &
294        ONLY: land_surface, lsm_header
295
296    USE microphysics_mod,                                                      &
297        ONLY:  cloud_water_sedimentation, collision_turbulence,                &
298               c_sedimentation, limiter_sedimentation, nc_const,               &
299               ventilation_effect
300
301    USE model_1d,                                                              &
302        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
303       
304    USE netcdf_interface,                                                      &
305        ONLY:  netcdf_data_format, netcdf_data_format_string, netcdf_deflate
306
307    USE particle_attributes,                                                   &
308        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
309               curvature_solution_effects,                                     &
310               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
311               dt_write_particle_data, end_time_prel,                          &
312               number_of_particle_groups, particle_advection,                  &
313               particle_advection_start,                                       &
314               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
315               pst, radius, radius_classes, random_start_position,             &
316               seed_follows_topography,                                        &
317               total_number_of_particles, use_sgs_for_particles,               &
318               vertical_particle_advection, write_particle_statistics
319       
320    USE pegrid
321
322    USE plant_canopy_model_mod,                                                &
323        ONLY:  pcm_header, plant_canopy
324
325    USE pmc_handle_communicator,                                               &
326        ONLY:  pmc_get_model_info
327
328    USE pmc_interface,                                                         &
329        ONLY:  nested_run, nesting_datatransfer_mode, nesting_mode
330
331    USE radiation_model_mod,                                                   &
332        ONLY:  radiation, radiation_header
333   
334    USE spectra_mod,                                                           &
335        ONLY:  calculate_spectra, spectra_header
336
337    IMPLICIT NONE
338
339    CHARACTER (LEN=1)  ::  prec                !<
340   
341    CHARACTER (LEN=2)  ::  do2d_mode           !<
342   
343    CHARACTER (LEN=5)  ::  section_chr         !<
344   
345    CHARACTER (LEN=10) ::  coor_chr            !<
346    CHARACTER (LEN=10) ::  host_chr            !<
347   
348    CHARACTER (LEN=16) ::  begin_chr           !<
349   
350    CHARACTER (LEN=26) ::  ver_rev             !<
351
352    CHARACTER (LEN=32) ::  cpl_name            !<
353   
354    CHARACTER (LEN=40) ::  output_format       !<
355   
356    CHARACTER (LEN=70) ::  char1               !<
357    CHARACTER (LEN=70) ::  char2               !<
358    CHARACTER (LEN=70) ::  dopr_chr            !<
359    CHARACTER (LEN=70) ::  do2d_xy             !<
360    CHARACTER (LEN=70) ::  do2d_xz             !<
361    CHARACTER (LEN=70) ::  do2d_yz             !<
362    CHARACTER (LEN=70) ::  do3d_chr            !<
363    CHARACTER (LEN=70) ::  domask_chr          !<
364    CHARACTER (LEN=70) ::  run_classification  !<
365   
366    CHARACTER (LEN=85) ::  r_upper             !<
367    CHARACTER (LEN=85) ::  r_lower             !<
368   
369    CHARACTER (LEN=86) ::  coordinates         !<
370    CHARACTER (LEN=86) ::  gradients           !<
371    CHARACTER (LEN=86) ::  slices              !<
372    CHARACTER (LEN=86) ::  temperatures        !<
373    CHARACTER (LEN=86) ::  ugcomponent         !<
374    CHARACTER (LEN=86) ::  vgcomponent         !<
375
376    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !<
377
378    INTEGER(iwp) ::  av             !<
379    INTEGER(iwp) ::  bh             !<
380    INTEGER(iwp) ::  blx            !<
381    INTEGER(iwp) ::  bly            !<
382    INTEGER(iwp) ::  bxl            !<
383    INTEGER(iwp) ::  bxr            !<
384    INTEGER(iwp) ::  byn            !<
385    INTEGER(iwp) ::  bys            !<
386    INTEGER(iwp) ::  ch             !<
387    INTEGER(iwp) ::  count          !<
388    INTEGER(iwp) ::  cpl_parent_id  !<
389    INTEGER(iwp) ::  cwx            !<
390    INTEGER(iwp) ::  cwy            !<
391    INTEGER(iwp) ::  cxl            !<
392    INTEGER(iwp) ::  cxr            !<
393    INTEGER(iwp) ::  cyn            !<
394    INTEGER(iwp) ::  cys            !<
395    INTEGER(iwp) ::  dim            !<
396    INTEGER(iwp) ::  i              !<
397    INTEGER(iwp) ::  io             !<
398    INTEGER(iwp) ::  j              !<
399    INTEGER(iwp) ::  k              !<
400    INTEGER(iwp) ::  l              !<
401    INTEGER(iwp) ::  ll             !<
402    INTEGER(iwp) ::  mpi_type       !<
403    INTEGER(iwp) ::  my_cpl_id      !<
404    INTEGER(iwp) ::  n              !<
405    INTEGER(iwp) ::  ncpl           !<
406    INTEGER(iwp) ::  npe_total      !<
407   
408
409    REAL(wp) ::  cpuseconds_per_simulated_second  !<
410    REAL(wp) ::  lower_left_coord_x               !< x-coordinate of nest domain
411    REAL(wp) ::  lower_left_coord_y               !< y-coordinate of nest domain
412
413!
414!-- Open the output file. At the end of the simulation, output is directed
415!-- to unit 19.
416    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
417         .NOT. simulated_time_at_begin /= simulated_time )  THEN
418       io = 15   !  header output on file RUN_CONTROL
419    ELSE
420       io = 19   !  header output on file HEADER
421    ENDIF
422    CALL check_open( io )
423
424!
425!-- At the end of the run, output file (HEADER) will be rewritten with
426!-- new information
427    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
428
429!
430!-- Determine kind of model run
431    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
432       run_classification = 'restart run'
433    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
434       run_classification = 'run with cyclic fill of 3D - prerun data'
435    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
436       run_classification = 'run without 1D - prerun'
437    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
438       run_classification = 'run with 1D - prerun'
439    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
440       run_classification = 'run initialized by user'
441    ELSE
442       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
443       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
444    ENDIF
445    IF ( nested_run )  run_classification = 'nested ' // run_classification
446    IF ( ocean )  THEN
447       run_classification = 'ocean - ' // run_classification
448    ELSE
449       run_classification = 'atmosphere - ' // run_classification
450    ENDIF
451
452!
453!-- Run-identification, date, time, host
454    host_chr = host(1:10)
455    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
456    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
457    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
458#if defined( __mpi2 )
459       mpi_type = 2
460#else
461       mpi_type = 1
462#endif
463       WRITE ( io, 101 )  mpi_type, coupling_mode
464    ENDIF
465#if defined( __parallel )
466    IF ( coupling_start_time /= 0.0_wp )  THEN
467       IF ( coupling_start_time > simulated_time_at_begin )  THEN
468          WRITE ( io, 109 )
469       ELSE
470          WRITE ( io, 114 )
471       ENDIF
472    ENDIF
473#endif
474    IF ( ensemble_member_nr /= 0 )  THEN
475       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
476                       ADJUSTR( host_chr ), ensemble_member_nr
477    ELSE
478       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
479                       ADJUSTR( host_chr )
480    ENDIF
481#if defined( __parallel )
482    IF ( npex == -1  .AND.  npey == -1 )  THEN
483       char1 = 'calculated'
484    ELSE
485       char1 = 'predefined'
486    ENDIF
487    IF ( threads_per_task == 1 )  THEN
488       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
489    ELSE
490       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
491                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
492    ENDIF
493    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
494    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
495           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
496         npex == -1  .AND.  pdims(2) == 1 )                      &
497    THEN
498       WRITE ( io, 106 )
499    ELSEIF ( pdims(2) == 1 )  THEN
500       WRITE ( io, 107 )  'x'
501    ELSEIF ( pdims(1) == 1 )  THEN
502       WRITE ( io, 107 )  'y'
503    ENDIF
504    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
505    IF ( numprocs /= maximum_parallel_io_streams )  THEN
506       WRITE ( io, 108 )  maximum_parallel_io_streams
507    ENDIF
508#else
509    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
510#endif
511
512!
513!-- Nesting informations
514    IF ( nested_run )  THEN
515
516       WRITE ( io, 600 )  TRIM( nesting_mode ),                                &
517                          TRIM( nesting_datatransfer_mode )
518       CALL pmc_get_model_info( ncpl = ncpl, cpl_id = my_cpl_id )
519
520       DO  n = 1, ncpl
521          CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,&
522                                   cpl_parent_id = cpl_parent_id,              &
523                                   lower_left_x = lower_left_coord_x,          &
524                                   lower_left_y = lower_left_coord_y,          &
525                                   npe_total = npe_total )
526          IF ( n == my_cpl_id )  THEN
527             char1 = '*'
528          ELSE
529             char1 = ' '
530          ENDIF
531          WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total,       &
532                             lower_left_coord_x, lower_left_coord_y,           &
533                             TRIM( cpl_name )
534       ENDDO
535    ENDIF
536    WRITE ( io, 99 )
537
538!
539!-- Numerical schemes
540    WRITE ( io, 110 )
541    IF ( psolver(1:7) == 'poisfft' )  THEN
542       WRITE ( io, 111 )  TRIM( fft_method )
543       IF ( transpose_compute_overlap )  WRITE( io, 115 )
544    ELSEIF ( psolver == 'sor' )  THEN
545       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
546    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
547       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
548       IF ( mg_cycles == -1 )  THEN
549          WRITE ( io, 140 )  residual_limit
550       ELSE
551          WRITE ( io, 141 )  mg_cycles
552       ENDIF
553       IF ( mg_switch_to_pe0_level == 0 )  THEN
554          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
555                             nzt_mg(1)
556       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
557          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
558                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
559                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
560                             nzt_mg(mg_switch_to_pe0_level),    &
561                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
562                             nzt_mg(1)
563       ENDIF
564       IF ( psolver == 'multigrid_noopt' .AND. masking_method )  WRITE ( io, 144 )
565    ENDIF
566    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
567    THEN
568       WRITE ( io, 142 )
569    ENDIF
570
571    IF ( momentum_advec == 'pw-scheme' )  THEN
572       WRITE ( io, 113 )
573    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
574       WRITE ( io, 503 )
575    ENDIF
576    IF ( scalar_advec == 'pw-scheme' )  THEN
577       WRITE ( io, 116 )
578    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
579       WRITE ( io, 504 )
580    ELSEIF ( scalar_advec == 'ws-scheme-mono' )  THEN
581       WRITE ( io, 513 )
582    ELSE
583       WRITE ( io, 118 )
584    ENDIF
585
586    WRITE ( io, 139 )  TRIM( loop_optimization )
587
588    IF ( galilei_transformation )  THEN
589       IF ( use_ug_for_galilei_tr )  THEN
590          char1 = '0.6 * geostrophic wind'
591       ELSE
592          char1 = 'mean wind in model domain'
593       ENDIF
594       IF ( simulated_time_at_begin == simulated_time )  THEN
595          char2 = 'at the start of the run'
596       ELSE
597          char2 = 'at the end of the run'
598       ENDIF
599       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
600                          advected_distance_x/1000.0_wp,                       &
601                          advected_distance_y/1000.0_wp
602    ENDIF
603    WRITE ( io, 122 )  timestep_scheme
604    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
605    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
606       IF ( .NOT. ocean )  THEN
607          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
608               rayleigh_damping_factor
609       ELSE
610          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
611               rayleigh_damping_factor
612       ENDIF
613    ENDIF
614    IF ( neutral )  WRITE ( io, 131 )  pt_surface
615    IF ( humidity )  THEN
616       IF ( .NOT. cloud_physics )  THEN
617          WRITE ( io, 129 )
618       ELSE
619          WRITE ( io, 130 )
620       ENDIF
621    ENDIF
622    IF ( passive_scalar )  WRITE ( io, 134 )
623    IF ( conserve_volume_flow )  THEN
624       WRITE ( io, 150 )  conserve_volume_flow_mode
625       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
626          WRITE ( io, 151 )  u_bulk, v_bulk
627       ENDIF
628    ELSEIF ( dp_external )  THEN
629       IF ( dp_smooth )  THEN
630          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
631       ELSE
632          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
633       ENDIF
634    ENDIF
635    WRITE ( io, 99 )
636
637!
638!-- Runtime and timestep information
639    WRITE ( io, 200 )
640    IF ( .NOT. dt_fixed )  THEN
641       WRITE ( io, 201 )  dt_max, cfl_factor
642    ELSE
643       WRITE ( io, 202 )  dt
644    ENDIF
645    WRITE ( io, 203 )  simulated_time_at_begin, end_time
646
647    IF ( time_restart /= 9999999.9_wp  .AND. &
648         simulated_time_at_begin == simulated_time )  THEN
649       IF ( dt_restart == 9999999.9_wp )  THEN
650          WRITE ( io, 204 )  ' Restart at:       ',time_restart
651       ELSE
652          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
653       ENDIF
654    ENDIF
655
656    IF ( simulated_time_at_begin /= simulated_time )  THEN
657       i = MAX ( log_point_s(10)%counts, 1 )
658       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
659          cpuseconds_per_simulated_second = 0.0_wp
660       ELSE
661          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
662                                            ( simulated_time -    &
663                                              simulated_time_at_begin )
664       ENDIF
665       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
666                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
667                          cpuseconds_per_simulated_second
668       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
669          IF ( dt_restart == 9999999.9_wp )  THEN
670             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
671          ELSE
672             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
673          ENDIF
674       ENDIF
675    ENDIF
676
677
678!
679!-- Start time for coupled runs, if independent precursor runs for atmosphere
680!-- and ocean are used or have been used. In this case, coupling_start_time
681!-- defines the time when the coupling is switched on.
682    IF ( coupling_start_time /= 0.0_wp )  THEN
683       WRITE ( io, 207 )  coupling_start_time
684    ENDIF
685
686!
687!-- Computational grid
688    IF ( .NOT. ocean )  THEN
689       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
690       IF ( dz_stretch_level_index < nzt+1 )  THEN
691          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
692                             dz_stretch_factor, dz_max
693       ENDIF
694    ELSE
695       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
696       IF ( dz_stretch_level_index > 0 )  THEN
697          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
698                             dz_stretch_factor, dz_max
699       ENDIF
700    ENDIF
701    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
702                       MIN( nnz+2, nzt+2 )
703    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
704
705!
706!-- Large scale forcing and nudging
707    WRITE ( io, 160 )
708    IF ( large_scale_forcing )  THEN
709       WRITE ( io, 162 )
710       WRITE ( io, 163 )
711
712       IF ( large_scale_subsidence )  THEN
713          IF ( .NOT. use_subsidence_tendencies )  THEN
714             WRITE ( io, 164 )
715          ELSE
716             WRITE ( io, 165 )
717          ENDIF
718       ENDIF
719
720       IF ( bc_pt_b == 'dirichlet' )  THEN
721          WRITE ( io, 180 )
722       ELSEIF ( bc_pt_b == 'neumann' )  THEN
723          WRITE ( io, 181 )
724       ENDIF
725
726       IF ( bc_q_b == 'dirichlet' )  THEN
727          WRITE ( io, 182 )
728       ELSEIF ( bc_q_b == 'neumann' )  THEN
729          WRITE ( io, 183 )
730       ENDIF
731
732       WRITE ( io, 167 )
733       IF ( nudging )  THEN
734          WRITE ( io, 170 )
735       ENDIF
736    ELSE
737       WRITE ( io, 161 )
738       WRITE ( io, 171 )
739    ENDIF
740    IF ( large_scale_subsidence )  THEN
741       WRITE ( io, 168 )
742       WRITE ( io, 169 )
743    ENDIF
744
745!
746!-- Profile for the large scale vertial velocity
747!-- Building output strings, starting with surface value
748    IF ( large_scale_subsidence )  THEN
749       temperatures = '   0.0'
750       gradients = '------'
751       slices = '     0'
752       coordinates = '   0.0'
753       i = 1
754       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
755
756          WRITE (coor_chr,'(E10.2,7X)')  &
757                                w_subs(subs_vertical_gradient_level_i(i))
758          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
759
760          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
761          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
762
763          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
764          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
765
766          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
767          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
768
769          IF ( i == 10 )  THEN
770             EXIT
771          ELSE
772             i = i + 1
773          ENDIF
774
775       ENDDO
776
777 
778       IF ( .NOT. large_scale_forcing )  THEN
779          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
780                             TRIM( gradients ), TRIM( slices )
781       ENDIF
782
783
784    ENDIF
785
786!-- Profile of the geostrophic wind (component ug)
787!-- Building output strings
788    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
789    gradients = '------'
790    slices = '     0'
791    coordinates = '   0.0'
792    i = 1
793    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
794     
795       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
796       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
797
798       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
799       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
800
801       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
802       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
803
804       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
805       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
806
807       IF ( i == 10 )  THEN
808          EXIT
809       ELSE
810          i = i + 1
811       ENDIF
812
813    ENDDO
814
815    IF ( .NOT. large_scale_forcing )  THEN
816       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
817                          TRIM( gradients ), TRIM( slices )
818    ENDIF
819
820!-- Profile of the geostrophic wind (component vg)
821!-- Building output strings
822    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
823    gradients = '------'
824    slices = '     0'
825    coordinates = '   0.0'
826    i = 1
827    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
828
829       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
830       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
831
832       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
833       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
834
835       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
836       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
837
838       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
839       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
840
841       IF ( i == 10 )  THEN
842          EXIT
843       ELSE
844          i = i + 1
845       ENDIF
846 
847    ENDDO
848
849    IF ( .NOT. large_scale_forcing )  THEN
850       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
851                          TRIM( gradients ), TRIM( slices )
852    ENDIF
853
854!
855!-- Topography
856    WRITE ( io, 270 )  topography
857    SELECT CASE ( TRIM( topography ) )
858
859       CASE ( 'flat' )
860          ! no actions necessary
861
862       CASE ( 'single_building' )
863          blx = INT( building_length_x / dx )
864          bly = INT( building_length_y / dy )
865          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
866          IF ( ABS( zw(bh  ) - building_height ) == &
867               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
868
869          IF ( building_wall_left == 9999999.9_wp )  THEN
870             building_wall_left = ( nx + 1 - blx ) / 2 * dx
871          ENDIF
872          bxl = INT ( building_wall_left / dx + 0.5_wp )
873          bxr = bxl + blx
874
875          IF ( building_wall_south == 9999999.9_wp )  THEN
876             building_wall_south = ( ny + 1 - bly ) / 2 * dy
877          ENDIF
878          bys = INT ( building_wall_south / dy + 0.5_wp )
879          byn = bys + bly
880
881          WRITE ( io, 271 )  building_length_x, building_length_y, &
882                             building_height, bxl, bxr, bys, byn
883
884       CASE ( 'single_street_canyon' )
885          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
886          IF ( ABS( zw(ch  ) - canyon_height ) == &
887               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
888          IF ( canyon_width_x /= 9999999.9_wp )  THEN
889!
890!--          Street canyon in y direction
891             cwx = NINT( canyon_width_x / dx )
892             IF ( canyon_wall_left == 9999999.9_wp )  THEN
893                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
894             ENDIF
895             cxl = NINT( canyon_wall_left / dx )
896             cxr = cxl + cwx
897             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
898
899          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
900!
901!--          Street canyon in x direction
902             cwy = NINT( canyon_width_y / dy )
903             IF ( canyon_wall_south == 9999999.9_wp )  THEN
904                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
905             ENDIF
906             cys = NINT( canyon_wall_south / dy )
907             cyn = cys + cwy
908             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
909          ENDIF
910
911    END SELECT
912
913    IF ( TRIM( topography ) /= 'flat' )  THEN
914       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
915          IF ( TRIM( topography ) == 'single_building' .OR.  &
916               TRIM( topography ) == 'single_street_canyon' )  THEN
917             WRITE ( io, 278 )
918          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
919             WRITE ( io, 279 )
920          ENDIF
921       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
922          WRITE ( io, 278 )
923       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
924          WRITE ( io, 279 )
925       ENDIF
926    ENDIF
927
928    IF ( plant_canopy )  CALL pcm_header ( io )
929
930    IF ( land_surface )  CALL lsm_header ( io )
931
932    IF ( radiation )  CALL radiation_header ( io )
933
934!
935!-- Boundary conditions
936    IF ( ibc_p_b == 0 )  THEN
937       r_lower = 'p(0)     = 0      |'
938    ELSEIF ( ibc_p_b == 1 )  THEN
939       r_lower = 'p(0)     = p(1)   |'
940    ENDIF
941    IF ( ibc_p_t == 0 )  THEN
942       r_upper  = 'p(nzt+1) = 0      |'
943    ELSE
944       r_upper  = 'p(nzt+1) = p(nzt) |'
945    ENDIF
946
947    IF ( ibc_uv_b == 0 )  THEN
948       r_lower = TRIM( r_lower ) // ' uv(0)     = -uv(1)                |'
949    ELSE
950       r_lower = TRIM( r_lower ) // ' uv(0)     = uv(1)                 |'
951    ENDIF
952    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
953       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = 0                     |'
954    ELSEIF ( ibc_uv_t == 0 )  THEN
955       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
956    ELSE
957       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = uv(nzt)               |'
958    ENDIF
959
960    IF ( ibc_pt_b == 0 )  THEN
961       IF ( land_surface )  THEN
962          r_lower = TRIM( r_lower ) // ' pt(0)     = from soil model'
963       ELSE
964          r_lower = TRIM( r_lower ) // ' pt(0)     = pt_surface'
965       ENDIF
966    ELSEIF ( ibc_pt_b == 1 )  THEN
967       r_lower = TRIM( r_lower ) // ' pt(0)     = pt(1)'
968    ELSEIF ( ibc_pt_b == 2 )  THEN
969       r_lower = TRIM( r_lower ) // ' pt(0)     = from coupled model'
970    ENDIF
971    IF ( ibc_pt_t == 0 )  THEN
972       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt_top'
973    ELSEIF( ibc_pt_t == 1 )  THEN
974       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt)'
975    ELSEIF( ibc_pt_t == 2 )  THEN
976       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
977
978    ENDIF
979
980    WRITE ( io, 300 )  r_lower, r_upper
981
982    IF ( .NOT. constant_diffusion )  THEN
983       IF ( ibc_e_b == 1 )  THEN
984          r_lower = 'e(0)     = e(1)'
985       ELSE
986          r_lower = 'e(0)     = e(1) = (u*/0.1)**2'
987       ENDIF
988       r_upper = 'e(nzt+1) = e(nzt) = e(nzt-1)'
989
990       WRITE ( io, 301 )  'e', r_lower, r_upper       
991
992    ENDIF
993
994    IF ( ocean )  THEN
995       r_lower = 'sa(0)    = sa(1)'
996       IF ( ibc_sa_t == 0 )  THEN
997          r_upper =  'sa(nzt+1) = sa_surface'
998       ELSE
999          r_upper =  'sa(nzt+1) = sa(nzt)'
1000       ENDIF
1001       WRITE ( io, 301 ) 'sa', r_lower, r_upper
1002    ENDIF
1003
1004    IF ( humidity )  THEN
1005       IF ( ibc_q_b == 0 )  THEN
1006          IF ( land_surface )  THEN
1007             r_lower = 'q(0)     = from soil model'
1008          ELSE
1009             r_lower = 'q(0)     = q_surface'
1010          ENDIF
1011
1012       ELSE
1013          r_lower = 'q(0)     = q(1)'
1014       ENDIF
1015       IF ( ibc_q_t == 0 )  THEN
1016          r_upper =  'q(nzt)   = q_top'
1017       ELSE
1018          r_upper =  'q(nzt)   = q(nzt-1) + dq/dz'
1019       ENDIF
1020       WRITE ( io, 301 ) 'q', r_lower, r_upper
1021    ENDIF
1022
1023    IF ( passive_scalar )  THEN
1024       IF ( ibc_q_b == 0 )  THEN
1025          r_lower = 's(0)     = s_surface'
1026       ELSE
1027          r_lower = 's(0)     = s(1)'
1028       ENDIF
1029       IF ( ibc_q_t == 0 )  THEN
1030          r_upper =  's(nzt)   = s_top'
1031       ELSE
1032          r_upper =  's(nzt)   = s(nzt-1) + ds/dz'
1033       ENDIF
1034       WRITE ( io, 301 ) 's', r_lower, r_upper
1035    ENDIF
1036
1037    IF ( use_surface_fluxes )  THEN
1038       WRITE ( io, 303 )
1039       IF ( constant_heatflux )  THEN
1040          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1041             WRITE ( io, 306 )  shf(0,0)
1042          ELSE
1043             WRITE ( io, 306 )  surface_heatflux
1044          ENDIF
1045          IF ( random_heatflux )  WRITE ( io, 307 )
1046       ENDIF
1047       IF ( humidity  .AND.  constant_waterflux )  THEN
1048          IF ( large_scale_forcing .AND. lsf_surf )  THEN
1049             WRITE ( io, 311 ) qsws(0,0)
1050          ELSE
1051             WRITE ( io, 311 ) surface_waterflux
1052          ENDIF
1053       ENDIF
1054       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
1055          WRITE ( io, 313 ) surface_waterflux
1056       ENDIF
1057    ENDIF
1058
1059    IF ( use_top_fluxes )  THEN
1060       WRITE ( io, 304 )
1061       IF ( coupling_mode == 'uncoupled' )  THEN
1062          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
1063          IF ( constant_top_heatflux )  THEN
1064             WRITE ( io, 306 )  top_heatflux
1065          ENDIF
1066       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1067          WRITE ( io, 316 )
1068       ENDIF
1069       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
1070          WRITE ( io, 309 )  top_salinityflux
1071       ENDIF
1072       IF ( humidity  .OR.  passive_scalar )  THEN
1073          WRITE ( io, 315 )
1074       ENDIF
1075    ENDIF
1076
1077    IF ( constant_flux_layer )  THEN
1078       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
1079                          z0h_factor*roughness_length, kappa,                  &
1080                          zeta_min, zeta_max
1081       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
1082       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
1083          WRITE ( io, 312 )
1084       ENDIF
1085       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
1086          WRITE ( io, 314 )
1087       ENDIF
1088    ELSE
1089       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
1090          WRITE ( io, 310 )  zeta_min, zeta_max
1091       ENDIF
1092    ENDIF
1093
1094    WRITE ( io, 317 )  bc_lr, bc_ns
1095    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1096       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
1097       IF ( turbulent_inflow )  THEN
1098          IF ( .NOT. recycling_yshift ) THEN
1099             WRITE ( io, 319 )  recycling_width, recycling_plane, &
1100                                inflow_damping_height, inflow_damping_width
1101          ELSE
1102             WRITE ( io, 322 )  recycling_width, recycling_plane, &
1103                                inflow_damping_height, inflow_damping_width
1104          END IF
1105       ENDIF
1106    ENDIF
1107
1108!
1109!-- Initial Profiles
1110    WRITE ( io, 321 )
1111!
1112!-- Initial wind profiles
1113    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1114
1115!
1116!-- Initial temperature profile
1117!-- Building output strings, starting with surface temperature
1118    WRITE ( temperatures, '(F6.2)' )  pt_surface
1119    gradients = '------'
1120    slices = '     0'
1121    coordinates = '   0.0'
1122    i = 1
1123    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1124
1125       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1126       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1127
1128       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1129       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1130
1131       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1132       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1133
1134       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1135       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1136
1137       IF ( i == 10 )  THEN
1138          EXIT
1139       ELSE
1140          i = i + 1
1141       ENDIF
1142
1143    ENDDO
1144
1145    IF ( .NOT. nudging )  THEN
1146       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1147                          TRIM( gradients ), TRIM( slices )
1148    ELSE
1149       WRITE ( io, 428 ) 
1150    ENDIF
1151
1152!
1153!-- Initial humidity profile
1154!-- Building output strings, starting with surface humidity
1155    IF ( humidity  .OR.  passive_scalar )  THEN
1156       WRITE ( temperatures, '(E8.1)' )  q_surface
1157       gradients = '--------'
1158       slices = '       0'
1159       coordinates = '     0.0'
1160       i = 1
1161       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1162         
1163          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1164          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1165
1166          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1167          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1168         
1169          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1170          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1171         
1172          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1173          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1174
1175          IF ( i == 10 )  THEN
1176             EXIT
1177          ELSE
1178             i = i + 1
1179          ENDIF
1180
1181       ENDDO
1182
1183       IF ( humidity )  THEN
1184          IF ( .NOT. nudging )  THEN
1185             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1186                                TRIM( gradients ), TRIM( slices )
1187          ENDIF
1188       ELSE
1189          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1190                             TRIM( gradients ), TRIM( slices )
1191       ENDIF
1192    ENDIF
1193
1194!
1195!-- Initial salinity profile
1196!-- Building output strings, starting with surface salinity
1197    IF ( ocean )  THEN
1198       WRITE ( temperatures, '(F6.2)' )  sa_surface
1199       gradients = '------'
1200       slices = '     0'
1201       coordinates = '   0.0'
1202       i = 1
1203       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1204
1205          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1206          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1207
1208          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1209          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1210
1211          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1212          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1213
1214          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1215          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1216
1217          IF ( i == 10 )  THEN
1218             EXIT
1219          ELSE
1220             i = i + 1
1221          ENDIF
1222
1223       ENDDO
1224
1225       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1226                          TRIM( gradients ), TRIM( slices )
1227    ENDIF
1228
1229
1230!
1231!-- Listing of 1D-profiles
1232    WRITE ( io, 325 )  dt_dopr_listing
1233    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1234       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1235    ENDIF
1236
1237!
1238!-- DATA output
1239    WRITE ( io, 330 )
1240    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1241       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1242    ENDIF
1243
1244!
1245!-- 1D-profiles
1246    dopr_chr = 'Profile:'
1247    IF ( dopr_n /= 0 )  THEN
1248       WRITE ( io, 331 )
1249
1250       output_format = ''
1251       output_format = netcdf_data_format_string
1252       IF ( netcdf_deflate == 0 )  THEN
1253          WRITE ( io, 344 )  output_format
1254       ELSE
1255          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1256       ENDIF
1257
1258       DO  i = 1, dopr_n
1259          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1260          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1261             WRITE ( io, 332 )  dopr_chr
1262             dopr_chr = '       :'
1263          ENDIF
1264       ENDDO
1265
1266       IF ( dopr_chr /= '' )  THEN
1267          WRITE ( io, 332 )  dopr_chr
1268       ENDIF
1269       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1270       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1271    ENDIF
1272
1273!
1274!-- 2D-arrays
1275    DO  av = 0, 1
1276
1277       i = 1
1278       do2d_xy = ''
1279       do2d_xz = ''
1280       do2d_yz = ''
1281       DO  WHILE ( do2d(av,i) /= ' ' )
1282
1283          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1284          do2d_mode = do2d(av,i)(l-1:l)
1285
1286          SELECT CASE ( do2d_mode )
1287             CASE ( 'xy' )
1288                ll = LEN_TRIM( do2d_xy )
1289                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1290             CASE ( 'xz' )
1291                ll = LEN_TRIM( do2d_xz )
1292                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1293             CASE ( 'yz' )
1294                ll = LEN_TRIM( do2d_yz )
1295                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1296          END SELECT
1297
1298          i = i + 1
1299
1300       ENDDO
1301
1302       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1303              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1304              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1305
1306          IF (  av == 0 )  THEN
1307             WRITE ( io, 334 )  ''
1308          ELSE
1309             WRITE ( io, 334 )  '(time-averaged)'
1310          ENDIF
1311
1312          IF ( do2d_at_begin )  THEN
1313             begin_chr = 'and at the start'
1314          ELSE
1315             begin_chr = ''
1316          ENDIF
1317
1318          output_format = ''
1319          output_format = netcdf_data_format_string
1320          IF ( netcdf_deflate == 0 )  THEN
1321             WRITE ( io, 344 )  output_format
1322          ELSE
1323             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1324          ENDIF
1325
1326          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1327             i = 1
1328             slices = '/'
1329             coordinates = '/'
1330!
1331!--          Building strings with index and coordinate information of the
1332!--          slices
1333             DO  WHILE ( section(i,1) /= -9999 )
1334
1335                WRITE (section_chr,'(I5)')  section(i,1)
1336                section_chr = ADJUSTL( section_chr )
1337                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1338
1339                IF ( section(i,1) == -1 )  THEN
1340                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1341                ELSE
1342                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1343                ENDIF
1344                coor_chr = ADJUSTL( coor_chr )
1345                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1346
1347                i = i + 1
1348             ENDDO
1349             IF ( av == 0 )  THEN
1350                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1351                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1352                                   TRIM( coordinates )
1353                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1354                   WRITE ( io, 339 )  skip_time_do2d_xy
1355                ENDIF
1356             ELSE
1357                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1358                                   TRIM( begin_chr ), averaging_interval, &
1359                                   dt_averaging_input, 'k', TRIM( slices ), &
1360                                   TRIM( coordinates )
1361                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1362                   WRITE ( io, 339 )  skip_time_data_output_av
1363                ENDIF
1364             ENDIF
1365             IF ( netcdf_data_format > 4 )  THEN
1366                WRITE ( io, 352 )  ntdim_2d_xy(av)
1367             ELSE
1368                WRITE ( io, 353 )
1369             ENDIF
1370          ENDIF
1371
1372          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1373             i = 1
1374             slices = '/'
1375             coordinates = '/'
1376!
1377!--          Building strings with index and coordinate information of the
1378!--          slices
1379             DO  WHILE ( section(i,2) /= -9999 )
1380
1381                WRITE (section_chr,'(I5)')  section(i,2)
1382                section_chr = ADJUSTL( section_chr )
1383                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1384
1385                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1386                coor_chr = ADJUSTL( coor_chr )
1387                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1388
1389                i = i + 1
1390             ENDDO
1391             IF ( av == 0 )  THEN
1392                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1393                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1394                                   TRIM( coordinates )
1395                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1396                   WRITE ( io, 339 )  skip_time_do2d_xz
1397                ENDIF
1398             ELSE
1399                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1400                                   TRIM( begin_chr ), averaging_interval, &
1401                                   dt_averaging_input, 'j', TRIM( slices ), &
1402                                   TRIM( coordinates )
1403                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1404                   WRITE ( io, 339 )  skip_time_data_output_av
1405                ENDIF
1406             ENDIF
1407             IF ( netcdf_data_format > 4 )  THEN
1408                WRITE ( io, 352 )  ntdim_2d_xz(av)
1409             ELSE
1410                WRITE ( io, 353 )
1411             ENDIF
1412          ENDIF
1413
1414          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1415             i = 1
1416             slices = '/'
1417             coordinates = '/'
1418!
1419!--          Building strings with index and coordinate information of the
1420!--          slices
1421             DO  WHILE ( section(i,3) /= -9999 )
1422
1423                WRITE (section_chr,'(I5)')  section(i,3)
1424                section_chr = ADJUSTL( section_chr )
1425                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1426
1427                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1428                coor_chr = ADJUSTL( coor_chr )
1429                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1430
1431                i = i + 1
1432             ENDDO
1433             IF ( av == 0 )  THEN
1434                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1435                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1436                                   TRIM( coordinates )
1437                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1438                   WRITE ( io, 339 )  skip_time_do2d_yz
1439                ENDIF
1440             ELSE
1441                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1442                                   TRIM( begin_chr ), averaging_interval, &
1443                                   dt_averaging_input, 'i', TRIM( slices ), &
1444                                   TRIM( coordinates )
1445                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1446                   WRITE ( io, 339 )  skip_time_data_output_av
1447                ENDIF
1448             ENDIF
1449             IF ( netcdf_data_format > 4 )  THEN
1450                WRITE ( io, 352 )  ntdim_2d_yz(av)
1451             ELSE
1452                WRITE ( io, 353 )
1453             ENDIF
1454          ENDIF
1455
1456       ENDIF
1457
1458    ENDDO
1459
1460!
1461!-- 3d-arrays
1462    DO  av = 0, 1
1463
1464       i = 1
1465       do3d_chr = ''
1466       DO  WHILE ( do3d(av,i) /= ' ' )
1467
1468          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1469          i = i + 1
1470
1471       ENDDO
1472
1473       IF ( do3d_chr /= '' )  THEN
1474          IF ( av == 0 )  THEN
1475             WRITE ( io, 336 )  ''
1476          ELSE
1477             WRITE ( io, 336 )  '(time-averaged)'
1478          ENDIF
1479
1480          output_format = netcdf_data_format_string
1481          IF ( netcdf_deflate == 0 )  THEN
1482             WRITE ( io, 344 )  output_format
1483          ELSE
1484             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1485          ENDIF
1486
1487          IF ( do3d_at_begin )  THEN
1488             begin_chr = 'and at the start'
1489          ELSE
1490             begin_chr = ''
1491          ENDIF
1492          IF ( av == 0 )  THEN
1493             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1494                                zu(nz_do3d), nz_do3d
1495          ELSE
1496             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1497                                TRIM( begin_chr ), averaging_interval, &
1498                                dt_averaging_input, zu(nz_do3d), nz_do3d
1499          ENDIF
1500
1501          IF ( netcdf_data_format > 4 )  THEN
1502             WRITE ( io, 352 )  ntdim_3d(av)
1503          ELSE
1504             WRITE ( io, 353 )
1505          ENDIF
1506
1507          IF ( av == 0 )  THEN
1508             IF ( skip_time_do3d /= 0.0_wp )  THEN
1509                WRITE ( io, 339 )  skip_time_do3d
1510             ENDIF
1511          ELSE
1512             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1513                WRITE ( io, 339 )  skip_time_data_output_av
1514             ENDIF
1515          ENDIF
1516
1517       ENDIF
1518
1519    ENDDO
1520
1521!
1522!-- masked arrays
1523    IF ( masks > 0 )  WRITE ( io, 345 )  &
1524         mask_scale_x, mask_scale_y, mask_scale_z
1525    DO  mid = 1, masks
1526       DO  av = 0, 1
1527
1528          i = 1
1529          domask_chr = ''
1530          DO  WHILE ( domask(mid,av,i) /= ' ' )
1531             domask_chr = TRIM( domask_chr ) // ' ' //  &
1532                          TRIM( domask(mid,av,i) ) // ','
1533             i = i + 1
1534          ENDDO
1535
1536          IF ( domask_chr /= '' )  THEN
1537             IF ( av == 0 )  THEN
1538                WRITE ( io, 346 )  '', mid
1539             ELSE
1540                WRITE ( io, 346 )  ' (time-averaged)', mid
1541             ENDIF
1542
1543             output_format = netcdf_data_format_string
1544!--          Parallel output not implemented for mask data, hence
1545!--          output_format must be adjusted.
1546             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1547             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1548             IF ( netcdf_deflate == 0 )  THEN
1549                WRITE ( io, 344 )  output_format
1550             ELSE
1551                WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1552             ENDIF
1553
1554             IF ( av == 0 )  THEN
1555                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1556             ELSE
1557                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1558                                   averaging_interval, dt_averaging_input
1559             ENDIF
1560
1561             IF ( av == 0 )  THEN
1562                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1563                   WRITE ( io, 339 )  skip_time_domask(mid)
1564                ENDIF
1565             ELSE
1566                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1567                   WRITE ( io, 339 )  skip_time_data_output_av
1568                ENDIF
1569             ENDIF
1570!
1571!--          output locations
1572             DO  dim = 1, 3
1573                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1574                   count = 0
1575                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1576                      count = count + 1
1577                   ENDDO
1578                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1579                                      mask(mid,dim,:count)
1580                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1581                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1582                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1583                   WRITE ( io, 350 )  dir(dim), dir(dim)
1584                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1585                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1586                                      mask_loop(mid,dim,1:2)
1587                ELSE
1588                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1589                                      mask_loop(mid,dim,1:3)
1590                ENDIF
1591             ENDDO
1592          ENDIF
1593
1594       ENDDO
1595    ENDDO
1596
1597!
1598!-- Timeseries
1599    IF ( dt_dots /= 9999999.9_wp )  THEN
1600       WRITE ( io, 340 )
1601
1602       output_format = netcdf_data_format_string
1603       IF ( netcdf_deflate == 0 )  THEN
1604          WRITE ( io, 344 )  output_format
1605       ELSE
1606          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1607       ENDIF
1608       WRITE ( io, 341 )  dt_dots
1609    ENDIF
1610
1611#if defined( __dvrp_graphics )
1612!
1613!-- Dvrp-output
1614    IF ( dt_dvrp /= 9999999.9_wp )  THEN
1615       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1616                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1617       i = 1
1618       l = 0
1619       m = 0
1620       DO WHILE ( mode_dvrp(i) /= ' ' )
1621          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1622             READ ( mode_dvrp(i), '(10X,I2)' )  j
1623             l = l + 1
1624             IF ( do3d(0,j) /= ' ' )  THEN
1625                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1626                                   isosurface_color(:,l)
1627             ENDIF
1628          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1629             READ ( mode_dvrp(i), '(6X,I2)' )  j
1630             m = m + 1
1631             IF ( do2d(0,j) /= ' ' )  THEN
1632                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1633                                   slicer_range_limits_dvrp(:,m)
1634             ENDIF
1635          ENDIF
1636          i = i + 1
1637       ENDDO
1638
1639       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1640                          superelevation_y, superelevation, clip_dvrp_l, &
1641                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1642
1643       IF ( TRIM( topography ) /= 'flat' )  THEN
1644          WRITE ( io, 366 )  topography_color
1645          IF ( cluster_size > 1 )  THEN
1646             WRITE ( io, 367 )  cluster_size
1647          ENDIF
1648       ENDIF
1649
1650    ENDIF
1651#endif
1652!
1653!-- Output of virtual flight information
1654    IF ( virtual_flight )  CALL flight_header( io )
1655
1656!
1657!-- Output of spectra related quantities
1658    IF ( calculate_spectra )  CALL spectra_header( io )
1659
1660    WRITE ( io, 99 )
1661
1662!
1663!-- Physical quantities
1664    WRITE ( io, 400 )
1665
1666!
1667!-- Geostrophic parameters
1668    WRITE ( io, 410 )  phi, omega, f, fs
1669
1670!
1671!-- Other quantities
1672    WRITE ( io, 411 )  g
1673
1674    WRITE ( io, 412 )  TRIM( reference_state )
1675    IF ( use_single_reference_value )  THEN
1676       IF ( ocean )  THEN
1677          WRITE ( io, 413 )  prho_reference
1678       ELSE
1679          WRITE ( io, 414 )  pt_reference
1680       ENDIF
1681    ENDIF
1682
1683!
1684!-- Cloud physics parameters
1685    IF ( cloud_physics )  THEN
1686       WRITE ( io, 415 )
1687       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1688       IF ( microphysics_seifert )  THEN
1689          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
1690          WRITE ( io, 511 ) c_sedimentation
1691       ENDIF
1692    ENDIF
1693
1694!
1695!-- Cloud physcis parameters / quantities / numerical methods
1696    WRITE ( io, 430 )
1697    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1698       WRITE ( io, 431 )
1699    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1700       WRITE ( io, 432 )
1701       IF ( cloud_top_radiation )  WRITE ( io, 132 )
1702       IF ( microphysics_kessler )  THEN
1703          WRITE ( io, 133 )
1704       ELSEIF ( microphysics_seifert )  THEN
1705          IF ( cloud_water_sedimentation )  WRITE ( io, 506 )
1706          WRITE ( io, 505 )
1707          IF ( collision_turbulence )  WRITE ( io, 507 )
1708          IF ( ventilation_effect )  WRITE ( io, 508 )
1709          IF ( limiter_sedimentation )  WRITE ( io, 509 )
1710       ENDIF
1711    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1712       WRITE ( io, 433 )
1713       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1714       IF ( collision_kernel /= 'none' )  THEN
1715          WRITE ( io, 435 )  TRIM( collision_kernel )
1716          IF ( collision_kernel(6:9) == 'fast' )  THEN
1717             WRITE ( io, 436 )  radius_classes, dissipation_classes
1718          ENDIF
1719       ELSE
1720          WRITE ( io, 437 )
1721       ENDIF
1722    ENDIF
1723
1724!
1725!-- LES / turbulence parameters
1726    WRITE ( io, 450 )
1727
1728!--
1729! ... LES-constants used must still be added here
1730!--
1731    IF ( constant_diffusion )  THEN
1732       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1733                          prandtl_number
1734    ENDIF
1735    IF ( .NOT. constant_diffusion)  THEN
1736       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1737       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1738       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1739    ENDIF
1740
1741!
1742!-- Special actions during the run
1743    WRITE ( io, 470 )
1744    IF ( create_disturbances )  THEN
1745       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1746                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1747                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1748       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1749          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1750       ELSE
1751          WRITE ( io, 473 )  disturbance_energy_limit
1752       ENDIF
1753       WRITE ( io, 474 )  TRIM( random_generator )
1754    ENDIF
1755    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1756       WRITE ( io, 475 )  pt_surface_initial_change
1757    ENDIF
1758    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1759       WRITE ( io, 476 )  q_surface_initial_change       
1760    ENDIF
1761    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1762       WRITE ( io, 477 )  q_surface_initial_change       
1763    ENDIF
1764
1765    IF ( particle_advection )  THEN
1766!
1767!--    Particle attributes
1768       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1769                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1770                          end_time_prel
1771       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1772       IF ( random_start_position )  WRITE ( io, 481 )
1773       IF ( seed_follows_topography )  WRITE ( io, 496 )
1774       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1775       WRITE ( io, 495 )  total_number_of_particles
1776       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
1777          WRITE ( io, 485 )  dt_write_particle_data
1778          IF ( netcdf_data_format > 1 )  THEN
1779             output_format = 'netcdf (64 bit offset) and binary'
1780          ELSE
1781             output_format = 'netcdf and binary'
1782          ENDIF
1783          IF ( netcdf_deflate == 0 )  THEN
1784             WRITE ( io, 344 )  output_format
1785          ELSE
1786             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1787          ENDIF
1788       ENDIF
1789       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
1790       IF ( write_particle_statistics )  WRITE ( io, 486 )
1791
1792       WRITE ( io, 487 )  number_of_particle_groups
1793
1794       DO  i = 1, number_of_particle_groups
1795          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
1796             WRITE ( io, 490 )  i, 0.0_wp
1797             WRITE ( io, 492 )
1798          ELSE
1799             WRITE ( io, 490 )  i, radius(i)
1800             IF ( density_ratio(i) /= 0.0_wp )  THEN
1801                WRITE ( io, 491 )  density_ratio(i)
1802             ELSE
1803                WRITE ( io, 492 )
1804             ENDIF
1805          ENDIF
1806          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1807                             pdx(i), pdy(i), pdz(i)
1808          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1809       ENDDO
1810
1811    ENDIF
1812
1813
1814!
1815!-- Parameters of 1D-model
1816    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1817       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1818                          mixing_length_1d, dissipation_1d
1819       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1820          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1821       ENDIF
1822    ENDIF
1823
1824!
1825!-- User-defined information
1826    CALL user_header( io )
1827
1828    WRITE ( io, 99 )
1829
1830!
1831!-- Write buffer contents to disc immediately
1832    FLUSH( io )
1833
1834!
1835!-- Here the FORMATs start
1836
1837 99 FORMAT (1X,78('-'))
1838100 FORMAT (/1X,'******************************',4X,44('-')/        &
1839            1X,'* ',A,' *',4X,A/                               &
1840            1X,'******************************',4X,44('-'))
1841101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1842            35X,42('-'))
1843102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1844            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1845            ' Run on host:        ',A10)
1846#if defined( __parallel )
1847103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1848              ')',1X,A)
1849104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1850              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1851105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1852106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1853            35X,'because the job is running on an SMP-cluster')
1854107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1855108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1856109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1857            35X,42('-'))
1858114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1859            35X,'independent precursor runs'/             &
1860            35X,42('-'))
1861117 FORMAT (' Accelerator boards / node:  ',I2)
1862#endif
1863110 FORMAT (/' Numerical Schemes:'/ &
1864             ' -----------------'/)
1865111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1866112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1867            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
1868113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1869                  ' or Upstream')
1870115 FORMAT ('     FFT and transpositions are overlapping')
1871116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1872                  ' or Upstream')
1873118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1874119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1875            '     translation velocity = ',A/ &
1876            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1877120 FORMAT (' Accelerator boards: ',8X,I2)
1878122 FORMAT (' --> Time differencing scheme: ',A)
1879123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1880            '     maximum damping coefficient:',F6.3, ' 1/s')
1881129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1882130 FORMAT (' --> Additional prognostic equation for the total water content')
1883131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1884                  F6.2, ' K assumed')
1885132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1886            '     effective emissivity scheme')
1887133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1888134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1889135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1890                  A,'-cycle)'/ &
1891            '     number of grid levels:                   ',I2/ &
1892            '     Gauss-Seidel red/black iterations:       ',I2)
1893136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1894                  I3,')')
1895137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1896            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1897                  I3,')'/ &
1898            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1899                  I3,')')
1900139 FORMAT (' --> Loop optimization method: ',A)
1901140 FORMAT ('     maximum residual allowed:                ',E10.3)
1902141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1903142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1904                  'step')
1905143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1906                  'kinetic energy')
1907144 FORMAT ('     masking method is used')
1908150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1909                  'conserved'/ &
1910            '     using the ',A,' mode')
1911151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1912152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1913           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1914           /'     starting from dp_level_b =', F8.3, 'm', A /)
1915160 FORMAT (//' Large scale forcing and nudging:'/ &
1916              ' -------------------------------'/)
1917161 FORMAT (' --> No large scale forcing from external is used (default) ')
1918162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1919163 FORMAT ('     - large scale advection tendencies ')
1920164 FORMAT ('     - large scale subsidence velocity w_subs ')
1921165 FORMAT ('     - large scale subsidence tendencies ')
1922167 FORMAT ('     - and geostrophic wind components ug and vg')
1923168 FORMAT (' --> Large-scale vertical motion is used in the ', &
1924                  'prognostic equation(s) for')
1925169 FORMAT ('     the scalar(s) only')
1926170 FORMAT (' --> Nudging is used')
1927171 FORMAT (' --> No nudging is used (default) ')
1928180 FORMAT ('     - prescribed surface values for temperature')
1929181 FORMAT ('     - prescribed surface fluxes for temperature')
1930182 FORMAT ('     - prescribed surface values for humidity')
1931183 FORMAT ('     - prescribed surface fluxes for humidity')
1932200 FORMAT (//' Run time and time step information:'/ &
1933             ' ----------------------------------'/)
1934201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1935             '    CFL-factor:',F5.2)
1936202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1937203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1938             ' End time:            ',F9.3,' s')
1939204 FORMAT ( A,F9.3,' s')
1940205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1941206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1942             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1943               '  ',F9.3,' s'/                                                    &
1944             '                                      per second of simulated tim', &
1945               'e: ',F9.3,' s')
1946207 FORMAT ( ' Coupling start time: ',F9.3,' s')
1947250 FORMAT (//' Computational grid and domain size:'/ &
1948              ' ----------------------------------'// &
1949              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1950              ' m    dz =    ',F7.3,' m'/ &
1951              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1952              ' m  z(u) = ',F10.3,' m'/)
1953252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1954              ' factor:',F6.3/ &
1955            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1956254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1957            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1958260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1959             ' degrees')
1960270 FORMAT (//' Topography information:'/ &
1961              ' ----------------------'// &
1962              1X,'Topography: ',A)
1963271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1964              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1965                ' / ',I4)
1966272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1967              ' direction' / &
1968              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1969              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1970278 FORMAT (' Topography grid definition convention:'/ &
1971            ' cell edge (staggered grid points'/  &
1972            ' (u in x-direction, v in y-direction))' /)
1973279 FORMAT (' Topography grid definition convention:'/ &
1974            ' cell center (scalar grid points)' /)
1975300 FORMAT (//' Boundary conditions:'/ &
1976             ' -------------------'// &
1977             '                     p                    uv             ', &
1978             '                     pt'// &
1979             ' B. bound.: ',A/ &
1980             ' T. bound.: ',A)
1981301 FORMAT (/'                     ',A// &
1982             ' B. bound.: ',A/ &
1983             ' T. bound.: ',A)
1984303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1985304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1986305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1987               'computational u,v-level:'// &
1988             '       zp = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
1989             ' m   kappa =',F5.2/ &
1990             '       Rif value range:   ',F8.2,' <= rif <=',F6.2)
1991306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1992307 FORMAT ('       Heatflux has a random normal distribution')
1993308 FORMAT ('       Predefined surface temperature')
1994309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1995310 FORMAT (//'    1D-Model:'// &
1996             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1997311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1998312 FORMAT ('       Predefined surface humidity')
1999313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
2000314 FORMAT ('       Predefined scalar value at the surface')
2001315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
2002316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
2003                    'atmosphere model')
2004317 FORMAT (//' Lateral boundaries:'/ &
2005            '       left/right:  ',A/    &
2006            '       north/south: ',A)
2007318 FORMAT (/'       use_cmax: ',L1 / &
2008            '       pt damping layer width = ',F8.2,' m, pt ', &
2009                    'damping factor =',F7.4)
2010319 FORMAT ('       turbulence recycling at inflow switched on'/ &
2011            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2012            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
2013320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
2014            '                                          v: ',F9.6,' m**2/s**2')
2015321 FORMAT (//' Initial profiles:'/ &
2016              ' ----------------')
2017322 FORMAT ('       turbulence recycling at inflow switched on'/ &
2018            '       y shift of the recycled inflow turbulence switched on'/ &
2019            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
2020            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
2021325 FORMAT (//' List output:'/ &
2022             ' -----------'//  &
2023            '    1D-Profiles:'/    &
2024            '       Output every             ',F8.2,' s')
2025326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
2026            '       Averaging input every    ',F8.2,' s')
2027330 FORMAT (//' Data output:'/ &
2028             ' -----------'/)
2029331 FORMAT (/'    1D-Profiles:')
2030332 FORMAT (/'       ',A)
2031333 FORMAT ('       Output every             ',F8.2,' s',/ &
2032            '       Time averaged over       ',F8.2,' s'/ &
2033            '       Averaging input every    ',F8.2,' s')
2034334 FORMAT (/'    2D-Arrays',A,':')
2035335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2036            '       Output every             ',F8.2,' s  ',A/ &
2037            '       Cross sections at ',A1,' = ',A/ &
2038            '       scalar-coordinates:   ',A,' m'/)
2039336 FORMAT (/'    3D-Arrays',A,':')
2040337 FORMAT (/'       Arrays: ',A/ &
2041            '       Output every             ',F8.2,' s  ',A/ &
2042            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2043339 FORMAT ('       No output during initial ',F8.2,' s')
2044340 FORMAT (/'    Time series:')
2045341 FORMAT ('       Output every             ',F8.2,' s'/)
2046342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
2047            '       Output every             ',F8.2,' s  ',A/ &
2048            '       Time averaged over       ',F8.2,' s'/ &
2049            '       Averaging input every    ',F8.2,' s'/ &
2050            '       Cross sections at ',A1,' = ',A/ &
2051            '       scalar-coordinates:   ',A,' m'/)
2052343 FORMAT (/'       Arrays: ',A/ &
2053            '       Output every             ',F8.2,' s  ',A/ &
2054            '       Time averaged over       ',F8.2,' s'/ &
2055            '       Averaging input every    ',F8.2,' s'/ &
2056            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
2057344 FORMAT ('       Output format: ',A/)
2058345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
2059            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
2060            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
2061            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
2062346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
2063347 FORMAT ('       Variables: ',A/ &
2064            '       Output every             ',F8.2,' s')
2065348 FORMAT ('       Variables: ',A/ &
2066            '       Output every             ',F8.2,' s'/ &
2067            '       Time averaged over       ',F8.2,' s'/ &
2068            '       Averaging input every    ',F8.2,' s')
2069349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2070            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
2071            13('       ',8(F8.2,',')/) )
2072350 FORMAT (/'       Output locations in ',A,'-direction: ', &
2073            'all gridpoints along ',A,'-direction (default).' )
2074351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
2075            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
2076            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
2077352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2078353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
2079354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
2080#if defined( __dvrp_graphics )
2081360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2082            '       Output every      ',F7.1,' s'/ &
2083            '       Output mode:      ',A/ &
2084            '       Host / User:      ',A,' / ',A/ &
2085            '       Directory:        ',A// &
2086            '       The sequence contains:')
2087361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2088            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2089362 FORMAT (/'       Slicer plane ',A/ &
2090            '       Slicer limits: [',F6.2,',',F6.2,']')
2091365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
2092            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2093                     ')'/ &
2094            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2095            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
2096366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2097367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
2098#endif
2099400 FORMAT (//' Physical quantities:'/ &
2100              ' -------------------'/)
2101410 FORMAT ('    Geograph. latitude  :   phi    = ',F4.1,' degr'/   &
2102            '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
2103            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
2104            '                            f*     = ',F9.6,' 1/s')
2105411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
2106412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2107413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2108414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
2109415 FORMAT (/' Cloud physics parameters:'/ &
2110             ' ------------------------'/)
2111416 FORMAT ('    Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
2112            '    Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2113            '    Density of air     :   rho_0 =',F6.3,' kg/m**3'/  &
2114            '    Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2115            '    Vapourization heat :   L_v   =',E9.2,' J/kg')
2116417 FORMAT ('    Geograph. longitude :   lambda = ',F4.1,' degr')
2117418 FORMAT (/'    Day of the year at model start :   day_init      =     ',I3 &
2118            /'    UTC time at model start        :   time_utc_init = ',F7.1' s')
2119420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2120            '       Height:        ',A,'  m'/ &
2121            '       Temperature:   ',A,'  K'/ &
2122            '       Gradient:      ',A,'  K/100m'/ &
2123            '       Gridpoint:     ',A)
2124421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2125            '       Height:      ',A,'  m'/ &
2126            '       Humidity:    ',A,'  kg/kg'/ &
2127            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2128            '       Gridpoint:   ',A)
2129422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2130            '       Height:                  ',A,'  m'/ &
2131            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2132            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2133            '       Gridpoint:               ',A)
2134423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2135            '       Height:      ',A,'  m'/ &
2136            '       ug:          ',A,'  m/s'/ &
2137            '       Gradient:    ',A,'  1/100s'/ &
2138            '       Gridpoint:   ',A)
2139424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2140            '       Height:      ',A,'  m'/ &
2141            '       vg:          ',A,'  m/s'/ &
2142            '       Gradient:    ',A,'  1/100s'/ &
2143            '       Gridpoint:   ',A)
2144425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2145            '       Height:     ',A,'  m'/ &
2146            '       Salinity:   ',A,'  psu'/ &
2147            '       Gradient:   ',A,'  psu/100m'/ &
2148            '       Gridpoint:  ',A)
2149426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2150            '       Height:      ',A,'  m'/ &
2151            '       w_subs:      ',A,'  m/s'/ &
2152            '       Gradient:    ',A,'  (m/s)/100m'/ &
2153            '       Gridpoint:   ',A)
2154427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2155                  ' profiles')
2156428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2157             '    NUDGING_DATA')
2158430 FORMAT (//' Cloud physics quantities / methods:'/ &
2159              ' ----------------------------------'/)
2160431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2161                 'on)')
2162432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2163            '    total water content is used.'/ &
2164            '    Condensation is parameterized via 0% - or 100% scheme.')
2165433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2166                 'icle model')
2167434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2168                 ' droplets < 1.0E-6 m')
2169435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
2170436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2171                    'are used'/ &
2172            '          number of radius classes:       ',I3,'    interval ', &
2173                       '[1.0E-6,2.0E-4] m'/ &
2174            '          number of dissipation classes:   ',I2,'    interval ', &
2175                       '[0,1000] cm**2/s**3')
2176437 FORMAT ('    Droplet collision is switched off')
2177450 FORMAT (//' LES / Turbulence quantities:'/ &
2178              ' ---------------------------'/)
2179451 FORMAT ('    Diffusion coefficients are constant:'/ &
2180            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2181453 FORMAT ('    Mixing length is limited to',F5.2,' * z')
2182454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2183455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
2184470 FORMAT (//' Actions during the simulation:'/ &
2185              ' -----------------------------'/)
2186471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2187            '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
2188            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2189            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
2190472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2191                 ' to i/j =',I4)
2192473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2193                 F6.3, ' m**2/s**2')
2194474 FORMAT ('    Random number generator used    : ',A/)
2195475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2196                 'respectively, if'/ &
2197            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2198                 ' 3D-simulation'/)
2199476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2200                 'respectively, if the'/ &
2201            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2202                 ' the 3D-simulation'/)
2203477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2204                 'respectively, if the'/ &
2205            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2206                 ' the 3D-simulation'/)
2207480 FORMAT ('    Particles:'/ &
2208            '    ---------'// &
2209            '       Particle advection is active (switched on at t = ', F7.1, &
2210                    ' s)'/ &
2211            '       Start of new particle generations every  ',F6.1,' s'/ &
2212            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2213            '                            bottom:     ', A, ' top:         ', A/&
2214            '       Maximum particle age:                 ',F9.1,' s'/ &
2215            '       Advection stopped at t = ',F9.1,' s'/)
2216481 FORMAT ('       Particles have random start positions'/)
2217482 FORMAT ('          Particles are advected only horizontally'/)
2218485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2219486 FORMAT ('       Particle statistics are written on file'/)
2220487 FORMAT ('       Number of particle groups: ',I2/)
2221488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2222            '          minimum timestep for advection:', F8.5/)
2223489 FORMAT ('       Number of particles simultaneously released at each ', &
2224                    'point: ', I5/)
2225490 FORMAT ('       Particle group ',I2,':'/ &
2226            '          Particle radius: ',E10.3, 'm')
2227491 FORMAT ('          Particle inertia is activated'/ &
2228            '             density_ratio (rho_fluid/rho_particle) =',F6.3/)
2229492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2230493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2231            '                                         y:',F8.1,' - ',F8.1,' m'/&
2232            '                                         z:',F8.1,' - ',F8.1,' m'/&
2233            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2234                       ' m  dz = ',F8.1,' m'/)
2235494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2236                    F8.2,' s'/)
2237495 FORMAT ('       Number of particles in total domain: ',I10/)
2238496 FORMAT ('       Initial vertical particle positions are interpreted ', &
2239                    'as relative to the given topography')
2240500 FORMAT (//' 1D-Model parameters:'/                           &
2241              ' -------------------'//                           &
2242            '    Simulation time:                   ',F8.1,' s'/ &
2243            '    Run-controll output every:         ',F8.1,' s'/ &
2244            '    Vertical profile output every:     ',F8.1,' s'/ &
2245            '    Mixing length calculation:         ',A/         &
2246            '    Dissipation calculation:           ',A/)
2247502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2248503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2249504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2250505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2251506 FORMAT ('    Cloud water sedimentation parameterization via Stokes law')
2252507 FORMAT ('    Turbulence effects on precipitation process')
2253508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2254509 FORMAT ('    Slope limiter used for sedimentation process')
2255510 FORMAT ('    Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2256511 FORMAT ('    Sedimentation Courant number:                  '/&
2257            '                               C_s   =',F4.1,'        ')
2258512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2259            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2260            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
2261513 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order ' // & 
2262            '+ monotonic adjustment')
2263600 FORMAT (/' Nesting informations:'/ &
2264            ' --------------------'/ &
2265            ' Nesting mode:                     ',A/ &
2266            ' Nesting-datatransfer mode:        ',A// &
2267            ' Nest id  parent  number   lower left coordinates   name'/ &
2268            ' (*=me)     id    of PEs      x (m)     y (m)' )
2269601 FORMAT (2X,A1,1X,I2.2,6X,I2.2,5X,I5,5X,F8.2,2X,F8.2,5X,A)
2270
2271 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.