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

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

last commit documented

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