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

Last change on this file since 1213 was 1213, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 78.5 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!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
[254]20! Current revisions:
[1]21! -----------------
[941]22!
[1213]23!
[392]24! Former revisions:
25! -----------------
26! $Id: header.f90 1213 2013-08-15 09:03:50Z raasch $
27!
[1213]28! 1212 2013-08-15 08:46:27Z raasch
29! output for poisfft_hybrid removed
30!
[1182]31! 1179 2013-06-14 05:57:58Z raasch
32! output of reference_state, use_reference renamed use_single_reference_value
33!
[1160]34! 1159 2013-05-21 11:58:22Z fricke
35! +use_cmax
36!
[1116]37! 1115 2013-03-26 18:16:16Z hoffmann
38! descriptions for Seifert-Beheng-cloud-physics-scheme added
39!
[1112]40! 1111 2013-03-08 23:54:10Z raasch
41! output of accelerator board information
42! ibc_p_b = 2 removed
43!
[1109]44! 1108 2013-03-05 07:03:32Z raasch
45! bugfix for r1106
46!
[1107]47! 1106 2013-03-04 05:31:38Z raasch
48! some format changes for coupled runs
49!
[1093]50! 1092 2013-02-02 11:24:22Z raasch
51! unused variables removed
52!
[1037]53! 1036 2012-10-22 13:43:42Z raasch
54! code put under GPL (PALM 3.9)
55!
[1035]56! 1031 2012-10-19 14:35:30Z raasch
57! output of netCDF data format modified
58!
[1017]59! 1015 2012-09-27 09:23:24Z raasch
60! output of Aajustment of mixing length to the Prandtl mixing length at first
61! grid point above ground removed
62!
[1004]63! 1003 2012-09-14 14:35:53Z raasch
64! output of information about equal/unequal subdomain size removed
65!
[1002]66! 1001 2012-09-13 14:08:46Z raasch
67! all actions concerning leapfrog- and upstream-spline-scheme removed
68!
[979]69! 978 2012-08-09 08:28:32Z fricke
70! -km_damp_max, outflow_damping_width
71! +pt_damping_factor, pt_damping_width
72! +z0h
73!
[965]74! 964 2012-07-26 09:14:24Z raasch
75! output of profil-related quantities removed
76!
[941]77! 940 2012-07-09 14:31:00Z raasch
78! Output in case of simulations for pure neutral stratification (no pt-equation
79! solved)
80!
[928]81! 927 2012-06-06 19:15:04Z raasch
82! output of masking_method for mg-solver
83!
[869]84! 868 2012-03-28 12:21:07Z raasch
85! translation velocity in Galilean transformation changed to 0.6 * ug
86!
[834]87! 833 2012-02-22 08:55:55Z maronga
88! Adjusted format for leaf area density
89!
[829]90! 828 2012-02-21 12:00:36Z raasch
91! output of dissipation_classes + radius_classes
92!
[826]93! 825 2012-02-19 03:03:44Z raasch
94! Output of cloud physics parameters/quantities complemented and restructured
95!
[768]96! 767 2011-10-14 06:39:12Z raasch
97! Output of given initial u,v-profiles
98!
[760]99! 759 2011-09-15 13:58:31Z raasch
100! output of maximum number of parallel io streams
101!
[708]102! 707 2011-03-29 11:39:40Z raasch
103! bc_lr/ns replaced by bc_lr/ns_cyc
104!
[668]105! 667 2010-12-23 12:06:00Z suehring/gryschka
106! Output of advection scheme.
107! Modified output of Prandtl-layer height.
108!
[581]109! 580 2010-10-05 13:59:11Z heinze
110! Renaming of ws_vertical_gradient to subs_vertical_gradient,
111! ws_vertical_gradient_level to subs_vertical_gradient_level and
112! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
113!
[494]114! 493 2010-03-01 08:30:24Z raasch
115! NetCDF data output format extendend for NetCDF4/HDF5
116!
[482]117! 449 2010-02-02 11:23:59Z raasch
118! +large scale vertical motion (subsidence/ascent)
119! Bugfix: index problem concerning gradient_level indices removed
120!
[449]121! 410 2009-12-04 17:05:40Z letzel
122! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
[493]123! mask_scale|_x|y|z, masks, skip_time_domask
[449]124!
[392]125! 346 2009-07-06 10:13:41Z raasch
[328]126! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
[291]127! Coupling with independent precursor runs.
[254]128! Output of messages replaced by message handling routine.
[336]129! Output of several additional dvr parameters
[240]130! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
[241]131! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
132! dp_smooth, dpdxy, u_bulk, v_bulk
[256]133! topography_grid_convention moved from user_header
[292]134! small bugfix concerning 3d 64bit netcdf output format
[1]135!
[226]136! 206 2008-10-13 14:59:11Z raasch
137! Bugfix: error in zu index in case of section_xy = -1
138!
[200]139! 198 2008-09-17 08:55:28Z raasch
140! Format adjustments allowing output of larger revision numbers
141!
[198]142! 197 2008-09-16 15:29:03Z raasch
143! allow 100 spectra levels instead of 10 for consistency with
144! define_netcdf_header,
145! bugfix in the output of the characteristic levels of potential temperature,
146! geostrophic wind, scalar concentration, humidity and leaf area density,
147! output of turbulence recycling informations
148!
[139]149! 138 2007-11-28 10:03:58Z letzel
150! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
151! Allow two instead of one digit to specify isosurface and slicer variables.
152! Output of sorting frequency of particles
153!
[110]154! 108 2007-08-24 15:10:38Z letzel
155! Output of informations for coupled model runs (boundary conditions etc.)
156! + output of momentumfluxes at the top boundary
157! Rayleigh damping for ocean, e_init
158!
[98]159! 97 2007-06-21 08:23:15Z raasch
160! Adjustments for the ocean version.
161! use_pt_reference renamed use_reference
162!
[90]163! 87 2007-05-22 15:46:47Z raasch
164! Bugfix: output of use_upstream_for_tke
165!
[83]166! 82 2007-04-16 15:40:52Z raasch
167! Preprocessor strings for different linux clusters changed to "lc",
168! routine local_flush is used for buffer flushing
169!
[77]170! 76 2007-03-29 00:58:32Z raasch
171! Output of netcdf_64bit_3d, particles-package is now part of the default code,
172! output of the loop optimization method, moisture renamed humidity,
173! output of subversion revision number
174!
[39]175! 19 2007-02-23 04:53:48Z raasch
176! Output of scalar flux applied at top boundary
177!
[3]178! RCS Log replace by Id keyword, revision history cleaned up
179!
[1]180! Revision 1.63  2006/08/22 13:53:13  raasch
181! Output of dz_max
182!
183! Revision 1.1  1997/08/11 06:17:20  raasch
184! Initial revision
185!
186!
187! Description:
188! ------------
189! Writing a header with all important informations about the actual run.
190! This subroutine is called three times, two times at the beginning
191! (writing information on files RUN_CONTROL and HEADER) and one time at the
192! end of the run, then writing additional information about CPU-usage on file
193! header.
[411]194!-----------------------------------------------------------------------------!
[1]195
196    USE arrays_3d
197    USE control_parameters
198    USE cloud_parameters
199    USE cpulog
200    USE dvrp_variables
201    USE grid_variables
202    USE indices
203    USE model_1d
204    USE particle_attributes
205    USE pegrid
[411]206    USE subsidence_mod
[1]207    USE spectrum
208
209    IMPLICIT NONE
210
211    CHARACTER (LEN=1)  ::  prec
212    CHARACTER (LEN=2)  ::  do2d_mode
213    CHARACTER (LEN=5)  ::  section_chr
214    CHARACTER (LEN=10) ::  coor_chr, host_chr
215    CHARACTER (LEN=16) ::  begin_chr
[1106]216    CHARACTER (LEN=26) ::  ver_rev
[1]217    CHARACTER (LEN=40) ::  output_format
[167]218    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
[1]219                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
[410]220                           domask_chr, run_classification
[167]221    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
222                           temperatures, ugcomponent, vgcomponent
[1]223    CHARACTER (LEN=85) ::  roben, runten
224
[410]225    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
226
227    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
[1092]228                cxl, cxr, cyn, cys, dim, i, io, j, l, ll, mpi_type
[1]229    REAL    ::  cpuseconds_per_simulated_second
230
231!
232!-- Open the output file. At the end of the simulation, output is directed
233!-- to unit 19.
234    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
235         .NOT. simulated_time_at_begin /= simulated_time )  THEN
236       io = 15   !  header output on file RUN_CONTROL
237    ELSE
238       io = 19   !  header output on file HEADER
239    ENDIF
240    CALL check_open( io )
241
242!
243!-- At the end of the run, output file (HEADER) will be rewritten with
244!-- new informations
245    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
246
247!
248!-- Determine kind of model run
249    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
250       run_classification = '3D - restart run'
[328]251    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
252       run_classification = '3D - run with cyclic fill of 3D - prerun data'
[147]253    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
254       run_classification = '3D - run without 1D - prerun'
[197]255    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[147]256       run_classification = '3D - run with 1D - prerun'
[197]257    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
258       run_classification = '3D - run initialized by user'
[1]259    ELSE
[254]260       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
261       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
[1]262    ENDIF
[97]263    IF ( ocean )  THEN
264       run_classification = 'ocean - ' // run_classification
265    ELSE
266       run_classification = 'atmosphere - ' // run_classification
267    ENDIF
[1]268
269!
270!-- Run-identification, date, time, host
271    host_chr = host(1:10)
[75]272    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
[102]273    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
[291]274    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
275#if defined( __mpi2 )
276       mpi_type = 2
277#else
278       mpi_type = 1
279#endif
280       WRITE ( io, 101 )  mpi_type, coupling_mode
281    ENDIF
[1108]282#if defined( __parallel )
[1106]283    IF ( coupling_start_time /= 0.0 )  THEN
284       IF ( coupling_start_time > simulated_time_at_begin )  THEN
285          WRITE ( io, 109 )
286       ELSE
287          WRITE ( io, 114 )
288       ENDIF
289    ENDIF
[1108]290#endif
[102]291    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
292                       ADJUSTR( host_chr )
[1]293#if defined( __parallel )
294    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
295       char1 = 'calculated'
296    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
297               host(1:2) == 'lc' )  .AND.                          &
298             npex == -1  .AND.  pdims(2) == 1 )  THEN
299       char1 = 'forced'
300    ELSE
301       char1 = 'predefined'
302    ENDIF
303    IF ( threads_per_task == 1 )  THEN
[102]304       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
[1]305    ELSE
[102]306       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
[1]307                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
308    ENDIF
[1111]309    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
[1]310    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
311           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
312         npex == -1  .AND.  pdims(2) == 1 )                      &
313    THEN
[102]314       WRITE ( io, 106 )
[1]315    ELSEIF ( pdims(2) == 1 )  THEN
[102]316       WRITE ( io, 107 )  'x'
[1]317    ELSEIF ( pdims(1) == 1 )  THEN
[102]318       WRITE ( io, 107 )  'y'
[1]319    ENDIF
[102]320    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
[759]321    IF ( numprocs /= maximum_parallel_io_streams )  THEN
322       WRITE ( io, 108 )  maximum_parallel_io_streams
323    ENDIF
[1111]324#else
325    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
[1]326#endif
327    WRITE ( io, 99 )
328
329!
330!-- Numerical schemes
331    WRITE ( io, 110 )
332    IF ( psolver(1:7) == 'poisfft' )  THEN
333       WRITE ( io, 111 )  TRIM( fft_method )
334    ELSEIF ( psolver == 'sor' )  THEN
335       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
336    ELSEIF ( psolver == 'multigrid' )  THEN
337       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
338       IF ( mg_cycles == -1 )  THEN
339          WRITE ( io, 140 )  residual_limit
340       ELSE
341          WRITE ( io, 141 )  mg_cycles
342       ENDIF
343       IF ( mg_switch_to_pe0_level == 0 )  THEN
344          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
345                             nzt_mg(1)
[197]346       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
[1]347          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
348                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
349                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
350                             nzt_mg(mg_switch_to_pe0_level),    &
351                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
352                             nzt_mg(1)
353       ENDIF
[927]354       IF ( masking_method )  WRITE ( io, 144 )
[1]355    ENDIF
356    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
357    THEN
358       WRITE ( io, 142 )
359    ENDIF
360
361    IF ( momentum_advec == 'pw-scheme' )  THEN
362       WRITE ( io, 113 )
[667]363    ELSEIF (momentum_advec == 'ws-scheme' ) THEN
364       WRITE ( io, 503 )
[1]365    ENDIF
366    IF ( scalar_advec == 'pw-scheme' )  THEN
367       WRITE ( io, 116 )
[667]368    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
369       WRITE ( io, 504 )
[1]370    ELSE
371       WRITE ( io, 118 )
372    ENDIF
[63]373
374    WRITE ( io, 139 )  TRIM( loop_optimization )
375
[1]376    IF ( galilei_transformation )  THEN
377       IF ( use_ug_for_galilei_tr )  THEN
[868]378          char1 = '0.6 * geostrophic wind'
[1]379       ELSE
380          char1 = 'mean wind in model domain'
381       ENDIF
382       IF ( simulated_time_at_begin == simulated_time )  THEN
383          char2 = 'at the start of the run'
384       ELSE
385          char2 = 'at the end of the run'
386       ENDIF
387       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
388                          advected_distance_x/1000.0, advected_distance_y/1000.0
389    ENDIF
[1001]390    WRITE ( io, 122 )  timestep_scheme
[87]391    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
[1]392    IF ( rayleigh_damping_factor /= 0.0 )  THEN
[108]393       IF ( .NOT. ocean )  THEN
394          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
395               rayleigh_damping_factor
396       ELSE
397          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
398               rayleigh_damping_factor
399       ENDIF
[1]400    ENDIF
[940]401    IF ( neutral )  WRITE ( io, 131 )  pt_surface
[75]402    IF ( humidity )  THEN
[1]403       IF ( .NOT. cloud_physics )  THEN
404          WRITE ( io, 129 )
405       ELSE
406          WRITE ( io, 130 )
407       ENDIF
408    ENDIF
409    IF ( passive_scalar )  WRITE ( io, 134 )
[240]410    IF ( conserve_volume_flow )  THEN
[241]411       WRITE ( io, 150 )  conserve_volume_flow_mode
412       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
413          WRITE ( io, 151 )  u_bulk, v_bulk
414       ENDIF
[240]415    ELSEIF ( dp_external )  THEN
416       IF ( dp_smooth )  THEN
[241]417          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
[240]418       ELSE
[241]419          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
[240]420       ENDIF
421    ENDIF
[411]422    IF ( large_scale_subsidence )  THEN
423        WRITE ( io, 153 )
424        WRITE ( io, 154 )
425    ENDIF
[1]426    WRITE ( io, 99 )
427
428!
429!-- Runtime and timestep informations
430    WRITE ( io, 200 )
431    IF ( .NOT. dt_fixed )  THEN
432       WRITE ( io, 201 )  dt_max, cfl_factor
433    ELSE
434       WRITE ( io, 202 )  dt
435    ENDIF
436    WRITE ( io, 203 )  simulated_time_at_begin, end_time
437
438    IF ( time_restart /= 9999999.9  .AND. &
439         simulated_time_at_begin == simulated_time )  THEN
440       IF ( dt_restart == 9999999.9 )  THEN
441          WRITE ( io, 204 )  ' Restart at:       ',time_restart
442       ELSE
443          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
444       ENDIF
445    ENDIF
446
447    IF ( simulated_time_at_begin /= simulated_time )  THEN
448       i = MAX ( log_point_s(10)%counts, 1 )
449       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
450          cpuseconds_per_simulated_second = 0.0
451       ELSE
452          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
453                                            ( simulated_time -    &
454                                              simulated_time_at_begin )
455       ENDIF
456       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
457                          log_point_s(10)%sum / REAL( i ),     &
458                          cpuseconds_per_simulated_second
459       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
460          IF ( dt_restart == 9999999.9 )  THEN
[1106]461             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
[1]462          ELSE
[1106]463             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
[1]464          ENDIF
465       ENDIF
466    ENDIF
467
468!
[291]469!-- Start time for coupled runs, if independent precursor runs for atmosphere
[1106]470!-- and ocean are used or have been used. In this case, coupling_start_time
471!-- defines the time when the coupling is switched on.
[291]472    IF ( coupling_start_time /= 0.0 )  THEN
[1106]473       WRITE ( io, 207 )  coupling_start_time
[291]474    ENDIF
475
476!
[1]477!-- Computational grid
[94]478    IF ( .NOT. ocean )  THEN
479       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
480       IF ( dz_stretch_level_index < nzt+1 )  THEN
481          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
482                             dz_stretch_factor, dz_max
483       ENDIF
484    ELSE
485       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
486       IF ( dz_stretch_level_index > 0 )  THEN
487          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
488                             dz_stretch_factor, dz_max
489       ENDIF
[1]490    ENDIF
491    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
492                       MIN( nnz+2, nzt+2 )
493    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
494
495!
496!-- Topography
497    WRITE ( io, 270 )  topography
498    SELECT CASE ( TRIM( topography ) )
499
500       CASE ( 'flat' )
501          ! no actions necessary
502
503       CASE ( 'single_building' )
504          blx = INT( building_length_x / dx )
505          bly = INT( building_length_y / dy )
506          bh  = INT( building_height / dz )
507
508          IF ( building_wall_left == 9999999.9 )  THEN
509             building_wall_left = ( nx + 1 - blx ) / 2 * dx
510          ENDIF
511          bxl = INT ( building_wall_left / dx + 0.5 )
512          bxr = bxl + blx
513
514          IF ( building_wall_south == 9999999.9 )  THEN
515             building_wall_south = ( ny + 1 - bly ) / 2 * dy
516          ENDIF
517          bys = INT ( building_wall_south / dy + 0.5 )
518          byn = bys + bly
519
520          WRITE ( io, 271 )  building_length_x, building_length_y, &
521                             building_height, bxl, bxr, bys, byn
522
[240]523       CASE ( 'single_street_canyon' )
524          ch  = NINT( canyon_height / dz )
525          IF ( canyon_width_x /= 9999999.9 )  THEN
526!
527!--          Street canyon in y direction
528             cwx = NINT( canyon_width_x / dx )
529             IF ( canyon_wall_left == 9999999.9 )  THEN
530                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
531             ENDIF
532             cxl = NINT( canyon_wall_left / dx )
533             cxr = cxl + cwx
534             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
535
536          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
537!
538!--          Street canyon in x direction
539             cwy = NINT( canyon_width_y / dy )
540             IF ( canyon_wall_south == 9999999.9 )  THEN
541                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
542             ENDIF
543             cys = NINT( canyon_wall_south / dy )
544             cyn = cys + cwy
545             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
546          ENDIF
547
[1]548    END SELECT
549
[256]550    IF ( TRIM( topography ) /= 'flat' )  THEN
551       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
552          IF ( TRIM( topography ) == 'single_building' .OR.  &
553               TRIM( topography ) == 'single_street_canyon' )  THEN
554             WRITE ( io, 278 )
555          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
556             WRITE ( io, 279 )
557          ENDIF
558       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
559          WRITE ( io, 278 )
560       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
561          WRITE ( io, 279 )
562       ENDIF
563    ENDIF
564
[138]565    IF ( plant_canopy ) THEN
566
567       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
[153]568       IF ( passive_scalar ) THEN
569          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
570                            leaf_surface_concentration
571       ENDIF
[138]572
[1]573!
[153]574!--    Heat flux at the top of vegetation
575       WRITE ( io, 282 ) cthf
576
577!
[138]578!--    Leaf area density profile
579!--    Building output strings, starting with surface value
[833]580       WRITE ( learde, '(F6.4)' )  lad_surface
[138]581       gradients = '------'
582       slices = '     0'
583       coordinates = '   0.0'
584       i = 1
585       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
586
587          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
588          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
589
590          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
591          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
592
593          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
594          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
595
596          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
597          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
598
599          i = i + 1
600       ENDDO
601
[153]602       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
[138]603                          TRIM( gradients ), TRIM( slices )
604
605    ENDIF
606
607!
[1]608!-- Boundary conditions
609    IF ( ibc_p_b == 0 )  THEN
610       runten = 'p(0)     = 0      |'
611    ELSEIF ( ibc_p_b == 1 )  THEN
612       runten = 'p(0)     = p(1)   |'
613    ENDIF
614    IF ( ibc_p_t == 0 )  THEN
615       roben  = 'p(nzt+1) = 0      |'
616    ELSE
617       roben  = 'p(nzt+1) = p(nzt) |'
618    ENDIF
619
620    IF ( ibc_uv_b == 0 )  THEN
621       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
622    ELSE
623       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
624    ENDIF
[132]625    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
626       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
627    ELSEIF ( ibc_uv_t == 0 )  THEN
[1]628       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
629    ELSE
630       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
631    ENDIF
632
633    IF ( ibc_pt_b == 0 )  THEN
634       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
[102]635    ELSEIF ( ibc_pt_b == 1 )  THEN
[1]636       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
[102]637    ELSEIF ( ibc_pt_b == 2 )  THEN
638       runten = TRIM( runten ) // ' pt(0) = from coupled model'
[1]639    ENDIF
640    IF ( ibc_pt_t == 0 )  THEN
[19]641       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
642    ELSEIF( ibc_pt_t == 1 )  THEN
643       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
644    ELSEIF( ibc_pt_t == 2 )  THEN
645       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
[667]646
[1]647    ENDIF
648
649    WRITE ( io, 300 )  runten, roben
650
651    IF ( .NOT. constant_diffusion )  THEN
652       IF ( ibc_e_b == 1 )  THEN
653          runten = 'e(0)     = e(1)'
654       ELSE
655          runten = 'e(0)     = e(1) = (u*/0.1)**2'
656       ENDIF
657       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
658
[97]659       WRITE ( io, 301 )  'e', runten, roben       
[1]660
661    ENDIF
662
[97]663    IF ( ocean )  THEN
664       runten = 'sa(0)    = sa(1)'
665       IF ( ibc_sa_t == 0 )  THEN
666          roben =  'sa(nzt+1) = sa_surface'
[1]667       ELSE
[97]668          roben =  'sa(nzt+1) = sa(nzt)'
[1]669       ENDIF
[97]670       WRITE ( io, 301 ) 'sa', runten, roben
671    ENDIF
[1]672
[97]673    IF ( humidity )  THEN
674       IF ( ibc_q_b == 0 )  THEN
675          runten = 'q(0)     = q_surface'
676       ELSE
677          runten = 'q(0)     = q(1)'
678       ENDIF
679       IF ( ibc_q_t == 0 )  THEN
680          roben =  'q(nzt)   = q_top'
681       ELSE
682          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
683       ENDIF
684       WRITE ( io, 301 ) 'q', runten, roben
685    ENDIF
[1]686
[97]687    IF ( passive_scalar )  THEN
688       IF ( ibc_q_b == 0 )  THEN
689          runten = 's(0)     = s_surface'
690       ELSE
691          runten = 's(0)     = s(1)'
692       ENDIF
693       IF ( ibc_q_t == 0 )  THEN
694          roben =  's(nzt)   = s_top'
695       ELSE
696          roben =  's(nzt)   = s(nzt-1) + ds/dz'
697       ENDIF
698       WRITE ( io, 301 ) 's', runten, roben
[1]699    ENDIF
700
701    IF ( use_surface_fluxes )  THEN
702       WRITE ( io, 303 )
703       IF ( constant_heatflux )  THEN
704          WRITE ( io, 306 )  surface_heatflux
705          IF ( random_heatflux )  WRITE ( io, 307 )
706       ENDIF
[75]707       IF ( humidity  .AND.  constant_waterflux )  THEN
[1]708          WRITE ( io, 311 ) surface_waterflux
709       ENDIF
710       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
711          WRITE ( io, 313 ) surface_waterflux
712       ENDIF
713    ENDIF
714
[19]715    IF ( use_top_fluxes )  THEN
716       WRITE ( io, 304 )
[102]717       IF ( coupling_mode == 'uncoupled' )  THEN
[151]718          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
[102]719          IF ( constant_top_heatflux )  THEN
720             WRITE ( io, 306 )  top_heatflux
721          ENDIF
722       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
723          WRITE ( io, 316 )
[19]724       ENDIF
[97]725       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
726          WRITE ( io, 309 )  top_salinityflux
727       ENDIF
[75]728       IF ( humidity  .OR.  passive_scalar )  THEN
[19]729          WRITE ( io, 315 )
730       ENDIF
731    ENDIF
732
[1]733    IF ( prandtl_layer )  THEN
[978]734       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
735                          z0h_factor*roughness_length, kappa, &
[94]736                          rif_min, rif_max
[1]737       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
[75]738       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
[1]739          WRITE ( io, 312 )
740       ENDIF
741       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
742          WRITE ( io, 314 )
743       ENDIF
744    ELSE
745       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
746          WRITE ( io, 310 )  rif_min, rif_max
747       ENDIF
748    ENDIF
749
750    WRITE ( io, 317 )  bc_lr, bc_ns
[707]751    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1159]752       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
[151]753       IF ( turbulent_inflow )  THEN
754          WRITE ( io, 319 )  recycling_width, recycling_plane, &
755                             inflow_damping_height, inflow_damping_width
756       ENDIF
[1]757    ENDIF
758
759!
760!-- Listing of 1D-profiles
[151]761    WRITE ( io, 325 )  dt_dopr_listing
[1]762    IF ( averaging_interval_pr /= 0.0 )  THEN
[151]763       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]764    ENDIF
765
766!
767!-- DATA output
768    WRITE ( io, 330 )
769    IF ( averaging_interval_pr /= 0.0 )  THEN
[151]770       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]771    ENDIF
772
773!
774!-- 1D-profiles
[346]775    dopr_chr = 'Profile:'
[1]776    IF ( dopr_n /= 0 )  THEN
777       WRITE ( io, 331 )
778
779       output_format = ''
780       IF ( netcdf_output )  THEN
[1031]781          output_format = output_format_netcdf
[1]782       ENDIF
[292]783       WRITE ( io, 344 )  output_format
[1]784
785       DO  i = 1, dopr_n
786          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
787          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
788             WRITE ( io, 332 )  dopr_chr
789             dopr_chr = '       :'
790          ENDIF
791       ENDDO
792
793       IF ( dopr_chr /= '' )  THEN
794          WRITE ( io, 332 )  dopr_chr
795       ENDIF
796       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
797       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
798    ENDIF
799
800!
801!-- 2D-arrays
802    DO  av = 0, 1
803
804       i = 1
805       do2d_xy = ''
806       do2d_xz = ''
807       do2d_yz = ''
808       DO  WHILE ( do2d(av,i) /= ' ' )
809
810          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
811          do2d_mode = do2d(av,i)(l-1:l)
812
813          SELECT CASE ( do2d_mode )
814             CASE ( 'xy' )
815                ll = LEN_TRIM( do2d_xy )
816                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
817             CASE ( 'xz' )
818                ll = LEN_TRIM( do2d_xz )
819                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
820             CASE ( 'yz' )
821                ll = LEN_TRIM( do2d_yz )
822                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
823          END SELECT
824
825          i = i + 1
826
827       ENDDO
828
829       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
830              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
831              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
832            ( netcdf_output  .OR.  iso2d_output ) )  THEN
833
834          IF (  av == 0 )  THEN
835             WRITE ( io, 334 )  ''
836          ELSE
837             WRITE ( io, 334 )  '(time-averaged)'
838          ENDIF
839
840          IF ( do2d_at_begin )  THEN
841             begin_chr = 'and at the start'
842          ELSE
843             begin_chr = ''
844          ENDIF
845
846          output_format = ''
847          IF ( netcdf_output )  THEN
[1031]848             output_format = output_format_netcdf
[1]849          ENDIF
850          IF ( iso2d_output )  THEN
851             IF ( netcdf_output )  THEN
[1031]852                output_format = TRIM( output_format_netcdf ) // ' and iso2d'
[1]853             ELSE
854                output_format = 'iso2d'
855             ENDIF
856          ENDIF
[292]857          WRITE ( io, 344 )  output_format
[1]858
859          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
860             i = 1
861             slices = '/'
862             coordinates = '/'
863!
864!--          Building strings with index and coordinate informations of the
865!--          slices
866             DO  WHILE ( section(i,1) /= -9999 )
867
868                WRITE (section_chr,'(I5)')  section(i,1)
869                section_chr = ADJUSTL( section_chr )
870                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
871
[206]872                IF ( section(i,1) == -1 )  THEN
873                   WRITE (coor_chr,'(F10.1)')  -1.0
874                ELSE
875                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
876                ENDIF
[1]877                coor_chr = ADJUSTL( coor_chr )
878                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
879
880                i = i + 1
881             ENDDO
882             IF ( av == 0 )  THEN
883                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
884                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
885                                   TRIM( coordinates )
886                IF ( skip_time_do2d_xy /= 0.0 )  THEN
887                   WRITE ( io, 339 )  skip_time_do2d_xy
888                ENDIF
889             ELSE
890                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
891                                   TRIM( begin_chr ), averaging_interval, &
892                                   dt_averaging_input, 'k', TRIM( slices ), &
893                                   TRIM( coordinates )
894                IF ( skip_time_data_output_av /= 0.0 )  THEN
895                   WRITE ( io, 339 )  skip_time_data_output_av
896                ENDIF
897             ENDIF
898
899          ENDIF
900
901          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
902             i = 1
903             slices = '/'
904             coordinates = '/'
905!
906!--          Building strings with index and coordinate informations of the
907!--          slices
908             DO  WHILE ( section(i,2) /= -9999 )
909
910                WRITE (section_chr,'(I5)')  section(i,2)
911                section_chr = ADJUSTL( section_chr )
912                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
913
914                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
915                coor_chr = ADJUSTL( coor_chr )
916                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
917
918                i = i + 1
919             ENDDO
920             IF ( av == 0 )  THEN
921                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
922                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
923                                   TRIM( coordinates )
924                IF ( skip_time_do2d_xz /= 0.0 )  THEN
925                   WRITE ( io, 339 )  skip_time_do2d_xz
926                ENDIF
927             ELSE
928                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
929                                   TRIM( begin_chr ), averaging_interval, &
930                                   dt_averaging_input, 'j', TRIM( slices ), &
931                                   TRIM( coordinates )
932                IF ( skip_time_data_output_av /= 0.0 )  THEN
933                   WRITE ( io, 339 )  skip_time_data_output_av
934                ENDIF
935             ENDIF
936          ENDIF
937
938          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
939             i = 1
940             slices = '/'
941             coordinates = '/'
942!
943!--          Building strings with index and coordinate informations of the
944!--          slices
945             DO  WHILE ( section(i,3) /= -9999 )
946
947                WRITE (section_chr,'(I5)')  section(i,3)
948                section_chr = ADJUSTL( section_chr )
949                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
950
951                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
952                coor_chr = ADJUSTL( coor_chr )
953                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
954
955                i = i + 1
956             ENDDO
957             IF ( av == 0 )  THEN
958                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
959                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
960                                   TRIM( coordinates )
961                IF ( skip_time_do2d_yz /= 0.0 )  THEN
962                   WRITE ( io, 339 )  skip_time_do2d_yz
963                ENDIF
964             ELSE
965                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
966                                   TRIM( begin_chr ), averaging_interval, &
967                                   dt_averaging_input, 'i', TRIM( slices ), &
968                                   TRIM( coordinates )
969                IF ( skip_time_data_output_av /= 0.0 )  THEN
970                   WRITE ( io, 339 )  skip_time_data_output_av
971                ENDIF
972             ENDIF
973          ENDIF
974
975       ENDIF
976
977    ENDDO
978
979!
980!-- 3d-arrays
981    DO  av = 0, 1
982
983       i = 1
984       do3d_chr = ''
985       DO  WHILE ( do3d(av,i) /= ' ' )
986
987          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
988          i = i + 1
989
990       ENDDO
991
992       IF ( do3d_chr /= '' )  THEN
993          IF ( av == 0 )  THEN
994             WRITE ( io, 336 )  ''
995          ELSE
996             WRITE ( io, 336 )  '(time-averaged)'
997          ENDIF
998
999          output_format = ''
1000          IF ( netcdf_output )  THEN
[1031]1001             output_format = output_format_netcdf
[1]1002          ENDIF
1003          IF ( avs_output )  THEN
1004             IF ( netcdf_output )  THEN
[1031]1005                output_format = TRIM( output_format_netcdf ) // ' and avs'
[1]1006             ELSE
1007                output_format = 'avs'
1008             ENDIF
1009          ENDIF
[292]1010          WRITE ( io, 344 )  output_format
[1]1011
1012          IF ( do3d_at_begin )  THEN
1013             begin_chr = 'and at the start'
1014          ELSE
1015             begin_chr = ''
1016          ENDIF
1017          IF ( av == 0 )  THEN
1018             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1019                                zu(nz_do3d), nz_do3d
1020          ELSE
1021             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1022                                TRIM( begin_chr ), averaging_interval, &
1023                                dt_averaging_input, zu(nz_do3d), nz_do3d
1024          ENDIF
1025
1026          IF ( do3d_compress )  THEN
1027             do3d_chr = ''
1028             i = 1
1029             DO WHILE ( do3d(av,i) /= ' ' )
1030
1031                SELECT CASE ( do3d(av,i) )
1032                   CASE ( 'u' )
1033                      j = 1
1034                   CASE ( 'v' )
1035                      j = 2
1036                   CASE ( 'w' )
1037                      j = 3
1038                   CASE ( 'p' )
1039                      j = 4
1040                   CASE ( 'pt' )
1041                      j = 5
1042                END SELECT
1043                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1044                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1045                           ':' // prec // ','
1046                i = i + 1
1047
1048             ENDDO
1049             WRITE ( io, 338 )  do3d_chr
1050
1051          ENDIF
1052
1053          IF ( av == 0 )  THEN
1054             IF ( skip_time_do3d /= 0.0 )  THEN
1055                WRITE ( io, 339 )  skip_time_do3d
1056             ENDIF
1057          ELSE
1058             IF ( skip_time_data_output_av /= 0.0 )  THEN
1059                WRITE ( io, 339 )  skip_time_data_output_av
1060             ENDIF
1061          ENDIF
1062
1063       ENDIF
1064
1065    ENDDO
1066
1067!
[410]1068!-- masked arrays
1069    IF ( masks > 0 )  WRITE ( io, 345 )  &
1070         mask_scale_x, mask_scale_y, mask_scale_z
1071    DO  mid = 1, masks
1072       DO  av = 0, 1
1073
1074          i = 1
1075          domask_chr = ''
1076          DO  WHILE ( domask(mid,av,i) /= ' ' )
1077             domask_chr = TRIM( domask_chr ) // ' ' //  &
1078                          TRIM( domask(mid,av,i) ) // ','
1079             i = i + 1
1080          ENDDO
1081
1082          IF ( domask_chr /= '' )  THEN
1083             IF ( av == 0 )  THEN
1084                WRITE ( io, 346 )  '', mid
1085             ELSE
1086                WRITE ( io, 346 )  ' (time-averaged)', mid
1087             ENDIF
1088
[1031]1089             output_format = ' '
[410]1090             IF ( netcdf_output )  THEN
[1031]1091                output_format = output_format_netcdf
[410]1092             ENDIF
1093             WRITE ( io, 344 )  output_format
1094
1095             IF ( av == 0 )  THEN
1096                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1097             ELSE
1098                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1099                                   averaging_interval, dt_averaging_input
1100             ENDIF
1101
1102             IF ( av == 0 )  THEN
1103                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1104                   WRITE ( io, 339 )  skip_time_domask(mid)
1105                ENDIF
1106             ELSE
1107                IF ( skip_time_data_output_av /= 0.0 )  THEN
1108                   WRITE ( io, 339 )  skip_time_data_output_av
1109                ENDIF
1110             ENDIF
1111!
1112!--          output locations
1113             DO  dim = 1, 3
1114                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1115                   count = 0
1116                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1117                      count = count + 1
1118                   ENDDO
1119                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1120                                      mask(mid,dim,:count)
1121                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1122                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1123                         mask_loop(mid,dim,3) == 0.0 )  THEN
1124                   WRITE ( io, 350 )  dir(dim), dir(dim)
1125                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1126                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1127                                      mask_loop(mid,dim,1:2)
1128                ELSE
1129                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1130                                      mask_loop(mid,dim,1:3)
1131                ENDIF
1132             ENDDO
1133          ENDIF
1134
1135       ENDDO
1136    ENDDO
1137
1138!
[1]1139!-- Timeseries
1140    IF ( dt_dots /= 9999999.9 )  THEN
1141       WRITE ( io, 340 )
1142
1143       output_format = ''
1144       IF ( netcdf_output )  THEN
[1031]1145          output_format = output_format_netcdf
[1]1146       ENDIF
[292]1147       WRITE ( io, 344 )  output_format
[1]1148       WRITE ( io, 341 )  dt_dots
1149    ENDIF
1150
1151#if defined( __dvrp_graphics )
1152!
1153!-- Dvrp-output
1154    IF ( dt_dvrp /= 9999999.9 )  THEN
1155       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1156                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1157       i = 1
1158       l = 0
[336]1159       m = 0
[1]1160       DO WHILE ( mode_dvrp(i) /= ' ' )
1161          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
[130]1162             READ ( mode_dvrp(i), '(10X,I2)' )  j
[1]1163             l = l + 1
1164             IF ( do3d(0,j) /= ' ' )  THEN
[336]1165                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1166                                   isosurface_color(:,l)
[1]1167             ENDIF
1168          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
[130]1169             READ ( mode_dvrp(i), '(6X,I2)' )  j
[336]1170             m = m + 1
1171             IF ( do2d(0,j) /= ' ' )  THEN
1172                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1173                                   slicer_range_limits_dvrp(:,m)
1174             ENDIF
[1]1175          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
[336]1176             WRITE ( io, 363 )  dvrp_psize
1177             IF ( particle_dvrpsize /= 'none' )  THEN
1178                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1179                                   dvrpsize_interval
1180             ENDIF
1181             IF ( particle_color /= 'none' )  THEN
1182                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1183                                   color_interval
1184             ENDIF
[1]1185          ENDIF
1186          i = i + 1
1187       ENDDO
[237]1188
[336]1189       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1190                          superelevation_y, superelevation, clip_dvrp_l, &
1191                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1192
1193       IF ( TRIM( topography ) /= 'flat' )  THEN
1194          WRITE ( io, 366 )  topography_color
1195          IF ( cluster_size > 1 )  THEN
1196             WRITE ( io, 367 )  cluster_size
1197          ENDIF
[237]1198       ENDIF
1199
[1]1200    ENDIF
1201#endif
1202
1203#if defined( __spectra )
1204!
1205!-- Spectra output
1206    IF ( dt_dosp /= 9999999.9 ) THEN
1207       WRITE ( io, 370 )
1208
[1031]1209       output_format = ' '
[1]1210       IF ( netcdf_output )  THEN
[1031]1211          output_format = output_format_netcdf
[1]1212       ENDIF
[292]1213       WRITE ( io, 344 )  output_format
[1]1214       WRITE ( io, 371 )  dt_dosp
1215       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1216       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1217                          ( spectra_direction(i), i = 1,10 ),  &
[189]1218                          ( comp_spectra_level(i), i = 1,100 ), &
1219                          ( plot_spectra_level(i), i = 1,100 ), &
[1]1220                          averaging_interval_sp, dt_averaging_input_pr
1221    ENDIF
1222#endif
1223
1224    WRITE ( io, 99 )
1225
1226!
1227!-- Physical quantities
1228    WRITE ( io, 400 )
1229
1230!
1231!-- Geostrophic parameters
1232    WRITE ( io, 410 )  omega, phi, f, fs
1233
1234!
1235!-- Other quantities
1236    WRITE ( io, 411 )  g
[1179]1237    WRITE ( io, 412 )  TRIM( reference_state )
1238    IF ( use_single_reference_value )  THEN
[97]1239       IF ( ocean )  THEN
[1179]1240          WRITE ( io, 413 )  prho_reference
[97]1241       ELSE
[1179]1242          WRITE ( io, 414 )  pt_reference
[97]1243       ENDIF
1244    ENDIF
[1]1245
1246!
1247!-- Cloud physics parameters
1248    IF ( cloud_physics ) THEN
[57]1249       WRITE ( io, 415 )
1250       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
[1115]1251       IF ( icloud_scheme == 0 )  THEN
1252          WRITE ( io, 510 ) 1.0E-6 * nc_const
1253          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1254       ENDIF
[1]1255    ENDIF
1256
1257!-- Profile of the geostrophic wind (component ug)
1258!-- Building output strings
1259    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1260    gradients = '------'
1261    slices = '     0'
1262    coordinates = '   0.0'
1263    i = 1
1264    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1265     
[167]1266       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
[1]1267       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1268
[167]1269       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
[1]1270       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1271
[167]1272       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
[1]1273       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1274
[167]1275       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
[1]1276       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1277
[430]1278       IF ( i == 10 )  THEN
1279          EXIT
1280       ELSE
1281          i = i + 1
1282       ENDIF
1283
[1]1284    ENDDO
1285
1286    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1287                       TRIM( gradients ), TRIM( slices )
1288
1289!-- Profile of the geostrophic wind (component vg)
1290!-- Building output strings
1291    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1292    gradients = '------'
1293    slices = '     0'
1294    coordinates = '   0.0'
1295    i = 1
1296    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1297
[167]1298       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
[1]1299       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1300
[167]1301       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
[1]1302       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1303
[167]1304       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
[1]1305       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1306
[167]1307       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
[1]1308       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1309
[430]1310       IF ( i == 10 )  THEN
1311          EXIT
1312       ELSE
1313          i = i + 1
1314       ENDIF
1315 
[1]1316    ENDDO
1317
1318    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1319                       TRIM( gradients ), TRIM( slices )
1320
1321!
[767]1322!-- Initial wind profiles
1323    IF ( u_profile(1) /= 9999999.9 )  WRITE ( io, 427 )
1324
1325!
[1]1326!-- Initial temperature profile
1327!-- Building output strings, starting with surface temperature
1328    WRITE ( temperatures, '(F6.2)' )  pt_surface
1329    gradients = '------'
1330    slices = '     0'
1331    coordinates = '   0.0'
1332    i = 1
1333    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1334
[94]1335       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1336       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
[1]1337
[94]1338       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1339       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
[1]1340
[94]1341       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1342       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
[1]1343
[94]1344       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1345       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
[1]1346
[430]1347       IF ( i == 10 )  THEN
1348          EXIT
1349       ELSE
1350          i = i + 1
1351       ENDIF
1352
[1]1353    ENDDO
1354
1355    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1356                       TRIM( gradients ), TRIM( slices )
1357
1358!
1359!-- Initial humidity profile
1360!-- Building output strings, starting with surface humidity
[75]1361    IF ( humidity  .OR.  passive_scalar )  THEN
[1]1362       WRITE ( temperatures, '(E8.1)' )  q_surface
1363       gradients = '--------'
1364       slices = '       0'
1365       coordinates = '     0.0'
1366       i = 1
1367       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1368         
1369          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1370          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1371
1372          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1373          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1374         
1375          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1376          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1377         
1378          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1379          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1380
[430]1381          IF ( i == 10 )  THEN
1382             EXIT
1383          ELSE
1384             i = i + 1
1385          ENDIF
1386
[1]1387       ENDDO
1388
[75]1389       IF ( humidity )  THEN
[1]1390          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1391                             TRIM( gradients ), TRIM( slices )
1392       ELSE
1393          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1394                             TRIM( gradients ), TRIM( slices )
1395       ENDIF
1396    ENDIF
1397
1398!
[97]1399!-- Initial salinity profile
1400!-- Building output strings, starting with surface salinity
1401    IF ( ocean )  THEN
1402       WRITE ( temperatures, '(F6.2)' )  sa_surface
1403       gradients = '------'
1404       slices = '     0'
1405       coordinates = '   0.0'
1406       i = 1
1407       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1408
1409          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1410          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1411
1412          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1413          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1414
1415          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1416          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1417
1418          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1419          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1420
[430]1421          IF ( i == 10 )  THEN
1422             EXIT
1423          ELSE
1424             i = i + 1
1425          ENDIF
1426
[97]1427       ENDDO
1428
1429       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1430                          TRIM( gradients ), TRIM( slices )
1431    ENDIF
1432
1433!
[411]1434!-- Profile for the large scale vertial velocity
1435!-- Building output strings, starting with surface value
1436    IF ( large_scale_subsidence )  THEN
1437       temperatures = '   0.0'
1438       gradients = '------'
1439       slices = '     0'
1440       coordinates = '   0.0'
1441       i = 1
[580]1442       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
[411]1443
1444          WRITE (coor_chr,'(E10.2,7X)')  &
[580]1445                                w_subs(subs_vertical_gradient_level_i(i))
[411]1446          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1447
[580]1448          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
[411]1449          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1450
[580]1451          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
[411]1452          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1453
[580]1454          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
[411]1455          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1456
[430]1457          IF ( i == 10 )  THEN
1458             EXIT
1459          ELSE
1460             i = i + 1
1461          ENDIF
1462
[411]1463       ENDDO
1464
1465       WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1466                          TRIM( gradients ), TRIM( slices )
1467    ENDIF
1468
1469!
[824]1470!-- Cloud physcis parameters / quantities / numerical methods
1471    WRITE ( io, 430 )
1472    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1473       WRITE ( io, 431 )
1474    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1475       WRITE ( io, 432 )
[1115]1476       IF ( radiation )  WRITE ( io, 132 )
1477       IF ( icloud_scheme == 1 )  THEN
1478          IF ( precipitation )  WRITE ( io, 133 )
1479       ELSEIF ( icloud_scheme == 0 )  THEN
1480          IF ( drizzle )  WRITE ( io, 506 )
1481          IF ( precipitation )  THEN
1482             WRITE ( io, 505 )
1483             IF ( turbulence )  WRITE ( io, 507 )
1484             IF ( ventilation_effect )  WRITE ( io, 508 )
1485             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1486          ENDIF
1487       ENDIF
[824]1488    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1489       WRITE ( io, 433 )
1490       IF ( curvature_solution_effects )  WRITE ( io, 434 )
[825]1491       IF ( collision_kernel /= 'none' )  THEN
1492          WRITE ( io, 435 )  TRIM( collision_kernel )
[828]1493          IF ( collision_kernel(6:9) == 'fast' )  THEN
1494             WRITE ( io, 436 )  radius_classes, dissipation_classes
1495          ENDIF
[825]1496       ELSE
[828]1497          WRITE ( io, 437 )
[825]1498       ENDIF
[824]1499    ENDIF
1500
1501!
[1]1502!-- LES / turbulence parameters
1503    WRITE ( io, 450 )
1504
1505!--
1506! ... LES-constants used must still be added here
1507!--
1508    IF ( constant_diffusion )  THEN
1509       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1510                          prandtl_number
1511    ENDIF
1512    IF ( .NOT. constant_diffusion)  THEN
[108]1513       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
[1]1514       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1515       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1516    ENDIF
1517
1518!
1519!-- Special actions during the run
1520    WRITE ( io, 470 )
1521    IF ( create_disturbances )  THEN
1522       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1523                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1524                          zu(disturbance_level_ind_t), disturbance_level_ind_t
[707]1525       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1]1526          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1527       ELSE
1528          WRITE ( io, 473 )  disturbance_energy_limit
1529       ENDIF
1530       WRITE ( io, 474 )  TRIM( random_generator )
1531    ENDIF
1532    IF ( pt_surface_initial_change /= 0.0 )  THEN
1533       WRITE ( io, 475 )  pt_surface_initial_change
1534    ENDIF
[75]1535    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
[1]1536       WRITE ( io, 476 )  q_surface_initial_change       
1537    ENDIF
1538    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1539       WRITE ( io, 477 )  q_surface_initial_change       
1540    ENDIF
1541
[60]1542    IF ( particle_advection )  THEN
[1]1543!
[60]1544!--    Particle attributes
1545       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1546                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
[117]1547                          end_time_prel, dt_sort_particles
[60]1548       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1549       IF ( random_start_position )  WRITE ( io, 481 )
1550       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1551       WRITE ( io, 495 )  total_number_of_particles
[824]1552       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
[60]1553          WRITE ( io, 483 )  maximum_number_of_tailpoints
1554          IF ( minimum_tailpoint_distance /= 0 )  THEN
1555             WRITE ( io, 484 )  total_number_of_tails,      &
1556                                minimum_tailpoint_distance, &
1557                                maximum_tailpoint_age
1558          ENDIF
[1]1559       ENDIF
[60]1560       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1561          WRITE ( io, 485 )  dt_write_particle_data
[1031]1562          output_format = ' '
[60]1563          IF ( netcdf_output )  THEN
[493]1564             IF ( netcdf_data_format > 1 )  THEN
[60]1565                output_format = 'netcdf (64 bit offset) and binary'
1566             ELSE
1567                output_format = 'netcdf and binary'
1568             ENDIF
[1]1569          ELSE
[60]1570             output_format = 'binary'
[1]1571          ENDIF
[292]1572          WRITE ( io, 344 )  output_format
[1]1573       ENDIF
[60]1574       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1575       IF ( write_particle_statistics )  WRITE ( io, 486 )
[1]1576
[60]1577       WRITE ( io, 487 )  number_of_particle_groups
[1]1578
[60]1579       DO  i = 1, number_of_particle_groups
1580          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1581             WRITE ( io, 490 )  i, 0.0
1582             WRITE ( io, 492 )
[1]1583          ELSE
[60]1584             WRITE ( io, 490 )  i, radius(i)
1585             IF ( density_ratio(i) /= 0.0 )  THEN
1586                WRITE ( io, 491 )  density_ratio(i)
1587             ELSE
1588                WRITE ( io, 492 )
1589             ENDIF
[1]1590          ENDIF
[60]1591          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1592                             pdx(i), pdy(i), pdz(i)
[336]1593          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
[60]1594       ENDDO
[1]1595
[60]1596    ENDIF
[1]1597
[60]1598
[1]1599!
1600!-- Parameters of 1D-model
1601    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1602       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1603                          mixing_length_1d, dissipation_1d
1604       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1605          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1606       ENDIF
1607    ENDIF
1608
1609!
1610!-- User-defined informations
1611    CALL user_header( io )
1612
1613    WRITE ( io, 99 )
1614
1615!
1616!-- Write buffer contents to disc immediately
[82]1617    CALL local_flush( io )
[1]1618
1619!
1620!-- Here the FORMATs start
1621
1622 99 FORMAT (1X,78('-'))
[1106]1623100 FORMAT (/1X,'******************************',6X,42('-')/        &
1624            1X,'* ',A,' *',6X,A/                               &
1625            1X,'******************************',6X,42('-'))
[291]1626101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
[102]1627            37X,42('-'))
[1106]1628102 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
1629            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
1630            ' Run on host:        ',A10)
[1]1631#if defined( __parallel )
[1106]1632103 FORMAT (' Number of PEs:',10X,I6,6X,'Processor grid (x,y): (',I3,',',I3, &
[1]1633              ')',1X,A)
[200]1634104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
[1]1635              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
[102]1636105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1637106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
[1]1638            37X,'because the job is running on an SMP-cluster')
[102]1639107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
[759]1640108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
[1106]1641109 FORMAT (37X,'Precursor run for coupled atmos-ocean run'/ &
1642            37X,42('-'))
1643114 FORMAT (37X,'Coupled atmosphere-ocean run following'/ &
1644            37X,'independent precursor runs'/             &
1645            37X,42('-'))
[1111]1646117 FORMAT (' Accelerator boards / node:  ',I2)
[1]1647#endif
1648110 FORMAT (/' Numerical Schemes:'/ &
1649             ' -----------------'/)
1650111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1651112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1652            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1653113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1654                  ' or Upstream')
1655116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1656                  ' or Upstream')
1657118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
[1106]1658119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1659            '     translation velocity = ',A/ &
[1]1660            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
[1111]1661120 FORMAT (' Accelerator boards: ',8X,I2)
[1]1662122 FORMAT (' --> Time differencing scheme: ',A)
[108]1663123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
[1]1664            '     maximum damping coefficient: ',F5.3, ' 1/s')
1665129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1666130 FORMAT (' --> Additional prognostic equation for the total water content')
[940]1667131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1668                  F6.2, ' K assumed')
[824]1669132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
[1]1670            '     effective emissivity scheme')
[824]1671133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
[1]1672134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1673135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1674                  A,'-cycle)'/ &
1675            '     number of grid levels:                   ',I2/ &
1676            '     Gauss-Seidel red/black iterations:       ',I2)
1677136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1678                  I3,')')
1679137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1680            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1681                  I3,')'/ &
1682            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1683                  I3,')')
[63]1684139 FORMAT (' --> Loop optimization method: ',A)
[1]1685140 FORMAT ('     maximum residual allowed:                ',E10.3)
1686141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1687142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1688                  'step')
[87]1689143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1690                  'kinetic energy')
[927]1691144 FORMAT ('     masking method is used')
[1]1692150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
[241]1693                  'conserved'/ &
1694            '     using the ',A,' mode')
1695151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
[306]1696152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1697           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1698           /'     starting from dp_level_b =', F8.3, 'm', A /)
[411]1699153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1700                  'prognostic equation for')
1701154 FORMAT ('     the potential temperature')
[1]1702200 FORMAT (//' Run time and time step information:'/ &
1703             ' ----------------------------------'/)
[1106]1704201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
[1]1705             '    CFL-factor: ',F4.2)
[1106]1706202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1707203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1708             ' End time:            ',F9.3,' s')
[1]1709204 FORMAT ( A,F9.3,' s')
1710205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
[1106]1711206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1712             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1713               '  ',F9.3,' s'/                                                    &
[1111]1714             '                                      per second of simulated tim', &
[1]1715               'e: ',F9.3,' s')
[1106]1716207 FORMAT ( ' Coupling start time: ',F9.3,' s')
[1]1717250 FORMAT (//' Computational grid and domain size:'/ &
1718              ' ----------------------------------'// &
1719              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1720              ' m    dz =    ',F7.3,' m'/ &
1721              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1722              ' m  z(u) = ',F10.3,' m'/)
1723252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1724              ' factor: ',F5.3/ &
1725            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1726254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1727            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1728260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1729             ' degrees')
1730270 FORMAT (//' Topography informations:'/ &
1731              ' -----------------------'// &
1732              1X,'Topography: ',A)
1733271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1734              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1735                ' / ',I4)
[240]1736272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1737              ' direction' / &
1738              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1739              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
[256]1740278 FORMAT (' Topography grid definition convention:'/ &
1741            ' cell edge (staggered grid points'/  &
1742            ' (u in x-direction, v in y-direction))' /)
1743279 FORMAT (' Topography grid definition convention:'/ &
1744            ' cell center (scalar grid points)' /)
[138]1745280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1746              ' ------------------------------'// &
1747              ' Canopy mode: ', A / &
1748              ' Canopy top: ',I4 / &
1749              ' Leaf drag coefficient: ',F6.2 /)
[153]1750281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1751              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1752282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1753283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
[138]1754              ' Height:              ',A,'  m'/ &
1755              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1756              ' Gradient:            ',A,'  m**2/m**4'/ &
1757              ' Gridpoint:           ',A)
1758               
[1]1759300 FORMAT (//' Boundary conditions:'/ &
1760             ' -------------------'// &
1761             '                     p                    uv             ', &
1762             '                   pt'// &
1763             ' B. bound.: ',A/ &
1764             ' T. bound.: ',A)
[97]1765301 FORMAT (/'                     ',A// &
[1]1766             ' B. bound.: ',A/ &
1767             ' T. bound.: ',A)
[19]1768303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1769304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1770305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1771               'computational u,v-level:'// &
[978]1772             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1773             ' m   kappa = ',F4.2/ &
[1]1774             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
[97]1775306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
[1]1776307 FORMAT ('       Heatflux has a random normal distribution')
1777308 FORMAT ('       Predefined surface temperature')
[97]1778309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
[1]1779310 FORMAT (//'    1D-Model:'// &
1780             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1781311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1782312 FORMAT ('       Predefined surface humidity')
1783313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1784314 FORMAT ('       Predefined scalar value at the surface')
[19]1785315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
[102]1786316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1787                    'atmosphere model')
[1]1788317 FORMAT (//' Lateral boundaries:'/ &
1789            '       left/right:  ',A/    &
1790            '       north/south: ',A)
[1159]1791318 FORMAT (/'       use_cmax: ',L1 / &
1792            '       pt damping layer width = ',F8.2,' m, pt ', &
[978]1793                    'damping factor = ',F6.4)
[151]1794319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1795            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1796            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1797320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
[103]1798            '                                          v: ',F9.6,' m**2/s**2')
[151]1799325 FORMAT (//' List output:'/ &
[1]1800             ' -----------'//  &
1801            '    1D-Profiles:'/    &
1802            '       Output every             ',F8.2,' s')
[151]1803326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
[1]1804            '       Averaging input every    ',F8.2,' s')
1805330 FORMAT (//' Data output:'/ &
1806             ' -----------'/)
1807331 FORMAT (/'    1D-Profiles:')
1808332 FORMAT (/'       ',A)
1809333 FORMAT ('       Output every             ',F8.2,' s',/ &
1810            '       Time averaged over       ',F8.2,' s'/ &
1811            '       Averaging input every    ',F8.2,' s')
1812334 FORMAT (/'    2D-Arrays',A,':')
1813335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1814            '       Output every             ',F8.2,' s  ',A/ &
1815            '       Cross sections at ',A1,' = ',A/ &
1816            '       scalar-coordinates:   ',A,' m'/)
1817336 FORMAT (/'    3D-Arrays',A,':')
1818337 FORMAT (/'       Arrays: ',A/ &
1819            '       Output every             ',F8.2,' s  ',A/ &
1820            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1821338 FORMAT ('       Compressed data output'/ &
1822            '       Decimal precision: ',A/)
1823339 FORMAT ('       No output during initial ',F8.2,' s')
1824340 FORMAT (/'    Time series:')
1825341 FORMAT ('       Output every             ',F8.2,' s'/)
1826342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1827            '       Output every             ',F8.2,' s  ',A/ &
1828            '       Time averaged over       ',F8.2,' s'/ &
1829            '       Averaging input every    ',F8.2,' s'/ &
1830            '       Cross sections at ',A1,' = ',A/ &
1831            '       scalar-coordinates:   ',A,' m'/)
1832343 FORMAT (/'       Arrays: ',A/ &
1833            '       Output every             ',F8.2,' s  ',A/ &
1834            '       Time averaged over       ',F8.2,' s'/ &
1835            '       Averaging input every    ',F8.2,' s'/ &
1836            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
[292]1837344 FORMAT ('       Output format: ',A/)
[410]1838345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1839            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1840            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1841            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1842346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1843347 FORMAT ('       Variables: ',A/ &
1844            '       Output every             ',F8.2,' s')
1845348 FORMAT ('       Variables: ',A/ &
1846            '       Output every             ',F8.2,' s'/ &
1847            '       Time averaged over       ',F8.2,' s'/ &
1848            '       Averaging input every    ',F8.2,' s')
1849349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1850            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1851            13('       ',8(F8.2,',')/) )
1852350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1853            'all gridpoints along ',A,'-direction (default).' )
1854351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1855            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1856            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
[1]1857#if defined( __dvrp_graphics )
1858360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1859            '       Output every      ',F7.1,' s'/ &
1860            '       Output mode:      ',A/ &
1861            '       Host / User:      ',A,' / ',A/ &
1862            '       Directory:        ',A// &
1863            '       The sequence contains:')
[337]1864361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1865            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1866362 FORMAT (/'       Slicer plane ',A/ &
[336]1867            '       Slicer limits: [',F6.2,',',F6.2,']')
[337]1868363 FORMAT (/'       Particles'/ &
[336]1869            '          particle size:  ',F7.2,' m')
1870364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1871                       F6.2,',',F6.2,']')
[337]1872365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
[336]1873            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1874                     ')'/ &
1875            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1876            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
[337]1877366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
[336]1878367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
[1]1879#endif
1880#if defined( __spectra )
1881370 FORMAT ('    Spectra:')
1882371 FORMAT ('       Output every ',F7.1,' s'/)
1883372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1884            '       Directions: ', 10(A5,',')/                         &
[189]1885            '       height levels  k = ', 20(I3,',')/                  &
1886            '                          ', 20(I3,',')/                  &
1887            '                          ', 20(I3,',')/                  &
1888            '                          ', 20(I3,',')/                  &
1889            '                          ', 19(I3,','),I3,'.'/           &
[1]1890            '       height levels selected for standard plot:'/        &
[189]1891            '                      k = ', 20(I3,',')/                  &
1892            '                          ', 20(I3,',')/                  &
1893            '                          ', 20(I3,',')/                  &
1894            '                          ', 20(I3,',')/                  &
1895            '                          ', 19(I3,','),I3,'.'/           &
[1]1896            '       Time averaged over ', F7.1, ' s,' /                &
1897            '       Profiles for the time averaging are taken every ', &
1898                    F6.1,' s')
1899#endif
1900400 FORMAT (//' Physical quantities:'/ &
1901              ' -------------------'/)
1902410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1903            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1904            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1905            '                            f*    = ',F9.6,' 1/s')
1906411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
[1179]1907412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
1908413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1909414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
[57]1910415 FORMAT (/'    Cloud physics parameters:'/ &
[1]1911             '    ------------------------'/)
[57]1912416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
[1]1913            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1914            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1915            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1916            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1917420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1918            '       Height:        ',A,'  m'/ &
1919            '       Temperature:   ',A,'  K'/ &
1920            '       Gradient:      ',A,'  K/100m'/ &
1921            '       Gridpoint:     ',A)
1922421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1923            '       Height:      ',A,'  m'/ &
1924            '       Humidity:    ',A,'  kg/kg'/ &
1925            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1926            '       Gridpoint:   ',A)
1927422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1928            '       Height:                  ',A,'  m'/ &
1929            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1930            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1931            '       Gridpoint:               ',A)
1932423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1933            '       Height:      ',A,'  m'/ &
1934            '       ug:          ',A,'  m/s'/ &
1935            '       Gradient:    ',A,'  1/100s'/ &
1936            '       Gridpoint:   ',A)
1937424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1938            '       Height:      ',A,'  m'/ &
[97]1939            '       vg:          ',A,'  m/s'/ &
[1]1940            '       Gradient:    ',A,'  1/100s'/ &
1941            '       Gridpoint:   ',A)
[97]1942425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1943            '       Height:     ',A,'  m'/ &
1944            '       Salinity:   ',A,'  psu'/ &
1945            '       Gradient:   ',A,'  psu/100m'/ &
1946            '       Gridpoint:  ',A)
[411]1947426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1948            '       Height:      ',A,'  m'/ &
1949            '       w_subs:      ',A,'  m/s'/ &
1950            '       Gradient:    ',A,'  (m/s)/100m'/ &
1951            '       Gridpoint:   ',A)
[767]1952427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1953                  ' profiles')
[824]1954430 FORMAT (//' Cloud physics quantities / methods:'/ &
1955              ' ----------------------------------'/)
1956431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1957                 'on)')
1958432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1959            '    total water content is used.'/ &
1960            '    Condensation is parameterized via 0% - or 100% scheme.')
1961433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1962                 'icle model')
1963434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1964                 ' droplets < 1.0E-6 m')
[825]1965435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
[828]1966436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1967                    'are used'/ &
1968            '          number of radius classes:       ',I3,'    interval ', &
1969                       '[1.0E-6,2.0E-4] m'/ &
1970            '          number of dissipation classes:   ',I2,'    interval ', &
1971                       '[0,1000] cm**2/s**3')
1972437 FORMAT ('    Droplet collision is switched off')
[1]1973450 FORMAT (//' LES / Turbulence quantities:'/ &
1974              ' ---------------------------'/)
[824]1975451 FORMAT ('    Diffusion coefficients are constant:'/ &
1976            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1977453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
1978454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1979455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
[1]1980470 FORMAT (//' Actions during the simulation:'/ &
1981              ' -----------------------------'/)
[94]1982471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1983            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1984            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1985            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
[1]1986472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1987                 ' to i/j =',I4)
1988473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1989                 1X,F5.3, ' m**2/s**2')
1990474 FORMAT ('    Random number generator used    : ',A/)
1991475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1992                 'respectively, if'/ &
1993            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1994                 ' 3D-simulation'/)
1995476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1996                 'respectively, if the'/ &
1997            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1998                 ' the 3D-simulation'/)
1999477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2000                 'respectively, if the'/ &
2001            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2002                 ' the 3D-simulation'/)
2003480 FORMAT ('    Particles:'/ &
2004            '    ---------'// &
2005            '       Particle advection is active (switched on at t = ', F7.1, &
2006                    ' s)'/ &
2007            '       Start of new particle generations every  ',F6.1,' s'/ &
2008            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2009            '                            bottom:     ', A, ' top:         ', A/&
2010            '       Maximum particle age:                 ',F9.1,' s'/ &
[117]2011            '       Advection stopped at t = ',F9.1,' s'/ &
2012            '       Particles are sorted every ',F9.1,' s'/)
[1]2013481 FORMAT ('       Particles have random start positions'/)
[336]2014482 FORMAT ('          Particles are advected only horizontally'/)
[1]2015483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2016484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2017            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2018            '            Maximum age of the end of the tail:  ',F8.2,' s')
2019485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2020486 FORMAT ('       Particle statistics are written on file'/)
2021487 FORMAT ('       Number of particle groups: ',I2/)
2022488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2023            '          minimum timestep for advection: ', F7.5/)
2024489 FORMAT ('       Number of particles simultaneously released at each ', &
2025                    'point: ', I5/)
2026490 FORMAT ('       Particle group ',I2,':'/ &
2027            '          Particle radius: ',E10.3, 'm')
2028491 FORMAT ('          Particle inertia is activated'/ &
2029            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2030492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2031493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2032            '                                         y:',F8.1,' - ',F8.1,' m'/&
2033            '                                         z:',F8.1,' - ',F8.1,' m'/&
2034            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2035                       ' m  dz = ',F8.1,' m'/)
2036494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2037                    F8.2,' s'/)
2038495 FORMAT ('       Number of particles in total domain: ',I10/)
2039500 FORMAT (//' 1D-Model parameters:'/                           &
2040              ' -------------------'//                           &
2041            '    Simulation time:                   ',F8.1,' s'/ &
2042            '    Run-controll output every:         ',F8.1,' s'/ &
2043            '    Vertical profile output every:     ',F8.1,' s'/ &
2044            '    Mixing length calculation:         ',A/         &
2045            '    Dissipation calculation:           ',A/)
2046502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
[667]2047503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2048504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
[1115]2049505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2050506 FORMAT ('    Drizzle parameterization via Stokes law')
2051507 FORMAT ('    Turbulence effects on precipitation process')
2052508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2053509 FORMAT ('    Slope limiter used for sedimentation process')
2054510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2055511 FORMAT ('        Sedimentation Courant number:                  '/&
2056            '                               C_s   = ',F3.1,'        ')
[1]2057
2058 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.