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

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

last commit documented, rc-file for example run updated

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