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

Last change on this file since 1159 was 1159, checked in by fricke, 11 years ago

Bugfix: In case of non-cyclic lateral boundary conditions, Neumann boundary conditions for the velocity components at the outflow are in fact radiation boundary conditions using the maximum phase velocity that ensures numerical stability (CFL-condition).
Logical operator use_cmax is now used instead of bc_lr_dirneu/_neudir.

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