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

Last change on this file since 1697 was 1697, checked in by raasch, 9 years ago

FORTRAN an OpenMP errors removed
misplaced cpp-directive fixed
small E- and F-FORMAT changes to avoid informative compiler messages about insufficient field width

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