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

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

Added support for RRTMG radiation code

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