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

Last change on this file since 1557 was 1557, checked in by suehring, 9 years ago

Enable monotone advection for scalars in combination with fifth-order scheme using monotonic limiter.

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