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

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

New:
---
Initial profiles can be used as reference state in the buoyancy term. New parameter
reference_state introduced. Calculation and handling of reference state in buoyancy term revised.
binary version for restart files changed from 3.9 to 3.9a (no downward compatibility!),
initial profile for rho added to hom (id=77)

Errors:


small bugfix for background communication (time_integration)

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