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

Last change on this file since 1660 was 1660, checked in by gronemeier, 9 years ago

Bugfix: Definition of topography height in case of grid stretching

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