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

Last change on this file since 1784 was 1784, checked in by raasch, 8 years ago

last commit documented

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