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

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

last commit documented

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