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

Last change on this file since 493 was 493, checked in by raasch, 14 years ago

New:
---
Output in NetCDF4-format. New d3par-parameter netcdf_data_format.

(check_open, check_parameters, close_file, data_output_2d, data_output_3d, header, modules, netcdf, parin)

Modules to be loaded for compilation (mbuild) or job execution (mrun)
can be given in the configuration file using variable modules. Example:

%modules ifort/11.0.069:netcdf lcsgih parallel

This method replaces the (undocumented) mpilib-variable.

WARNING: All fixed settings of modules in the scripts mbuild, mrun, and subjob
have been removed! Please set the modules variable appropriately in your
configuration file. (mbuild, mrun, subjob)

Changed:


Parameters netcdf_64bit and netcdf_64bit_3d have been removed. Use
netcdf_data_format = 2 for choosing the classic 64bit-offset format (this is
the default). The offset-format can not be set independently for the
3d-output-data any more.

Parameters netcdf_format_mask, netcdf_format_mask_av, and variables
nc_format_mask, format_parallel_io removed. They are replaced by the new
parameter netcdf_data_format. (check_open, close_file,
data_output_mask, header, init_masks, modules, parin)

Errors:


bugfix in trunk/UTIL/Makefile: forgot to compile for interpret_config

Bugfix: timeseries data have to be collected by PE0 (user_statistics)

  • Property svn:keywords set to Id
File size: 76.3 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! NetCDF data output format extendend for NetCDF4/HDF5
7!
8! Former revisions:
9! -----------------
10! $Id: header.f90 493 2010-03-01 08:30:24Z raasch $
11!
12! 449 2010-02-02 11:23:59Z raasch
13! +large scale vertical motion (subsidence/ascent)
14! Bugfix: index problem concerning gradient_level indices removed
15!
16! 410 2009-12-04 17:05:40Z letzel
17! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
18! mask_scale|_x|y|z, masks, skip_time_domask
19!
20! 346 2009-07-06 10:13:41Z raasch
21! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
22! Coupling with independent precursor runs.
23! Output of messages replaced by message handling routine.
24! Output of several additional dvr parameters
25! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
26! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
27! dp_smooth, dpdxy, u_bulk, v_bulk
28! topography_grid_convention moved from user_header
29! small bugfix concerning 3d 64bit netcdf output format
30!
31! 206 2008-10-13 14:59:11Z raasch
32! Bugfix: error in zu index in case of section_xy = -1
33!
34! 198 2008-09-17 08:55:28Z raasch
35! Format adjustments allowing output of larger revision numbers
36!
37! 197 2008-09-16 15:29:03Z raasch
38! allow 100 spectra levels instead of 10 for consistency with
39! define_netcdf_header,
40! bugfix in the output of the characteristic levels of potential temperature,
41! geostrophic wind, scalar concentration, humidity and leaf area density,
42! output of turbulence recycling informations
43!
44! 138 2007-11-28 10:03:58Z letzel
45! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
46! Allow two instead of one digit to specify isosurface and slicer variables.
47! Output of sorting frequency of particles
48!
49! 108 2007-08-24 15:10:38Z letzel
50! Output of informations for coupled model runs (boundary conditions etc.)
51! + output of momentumfluxes at the top boundary
52! Rayleigh damping for ocean, e_init
53!
54! 97 2007-06-21 08:23:15Z raasch
55! Adjustments for the ocean version.
56! use_pt_reference renamed use_reference
57!
58! 87 2007-05-22 15:46:47Z raasch
59! Bugfix: output of use_upstream_for_tke
60!
61! 82 2007-04-16 15:40:52Z raasch
62! Preprocessor strings for different linux clusters changed to "lc",
63! routine local_flush is used for buffer flushing
64!
65! 76 2007-03-29 00:58:32Z raasch
66! Output of netcdf_64bit_3d, particles-package is now part of the default code,
67! output of the loop optimization method, moisture renamed humidity,
68! output of subversion revision number
69!
70! 19 2007-02-23 04:53:48Z raasch
71! Output of scalar flux applied at top boundary
72!
73! RCS Log replace by Id keyword, revision history cleaned up
74!
75! Revision 1.63  2006/08/22 13:53:13  raasch
76! Output of dz_max
77!
78! Revision 1.1  1997/08/11 06:17:20  raasch
79! Initial revision
80!
81!
82! Description:
83! ------------
84! Writing a header with all important informations about the actual run.
85! This subroutine is called three times, two times at the beginning
86! (writing information on files RUN_CONTROL and HEADER) and one time at the
87! end of the run, then writing additional information about CPU-usage on file
88! header.
89!-----------------------------------------------------------------------------!
90
91    USE arrays_3d
92    USE control_parameters
93    USE cloud_parameters
94    USE cpulog
95    USE dvrp_variables
96    USE grid_variables
97    USE indices
98    USE model_1d
99    USE particle_attributes
100    USE pegrid
101    USE subsidence_mod
102    USE spectrum
103
104    IMPLICIT NONE
105
106    CHARACTER (LEN=1)  ::  prec
107    CHARACTER (LEN=2)  ::  do2d_mode
108    CHARACTER (LEN=5)  ::  section_chr
109    CHARACTER (LEN=9)  ::  time_to_string
110    CHARACTER (LEN=10) ::  coor_chr, host_chr
111    CHARACTER (LEN=16) ::  begin_chr
112    CHARACTER (LEN=23) ::  ver_rev
113    CHARACTER (LEN=40) ::  output_format
114    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
115                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
116                           domask_chr, run_classification
117    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
118                           temperatures, ugcomponent, vgcomponent
119    CHARACTER (LEN=85) ::  roben, runten
120
121    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
122
123    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
124         cxl, cxr, cyn, cys, dim, i, ihost, io, j, l, ll, m, mpi_type
125    REAL    ::  cpuseconds_per_simulated_second
126
127!
128!-- Open the output file. At the end of the simulation, output is directed
129!-- to unit 19.
130    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
131         .NOT. simulated_time_at_begin /= simulated_time )  THEN
132       io = 15   !  header output on file RUN_CONTROL
133    ELSE
134       io = 19   !  header output on file HEADER
135    ENDIF
136    CALL check_open( io )
137
138!
139!-- At the end of the run, output file (HEADER) will be rewritten with
140!-- new informations
141    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
142
143!
144!-- Determine kind of model run
145    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
146       run_classification = '3D - restart run'
147    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
148       run_classification = '3D - run with cyclic fill of 3D - prerun data'
149    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
150       run_classification = '3D - run without 1D - prerun'
151    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
152       run_classification = '3D - run with 1D - prerun'
153    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
154       run_classification = '3D - run initialized by user'
155    ELSE
156       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
157       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
158    ENDIF
159    IF ( ocean )  THEN
160       run_classification = 'ocean - ' // run_classification
161    ELSE
162       run_classification = 'atmosphere - ' // run_classification
163    ENDIF
164
165!
166!-- Run-identification, date, time, host
167    host_chr = host(1:10)
168    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
169    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
170    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
171#if defined( __mpi2 )
172       mpi_type = 2
173#else
174       mpi_type = 1
175#endif
176       WRITE ( io, 101 )  mpi_type, coupling_mode
177    ENDIF
178    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
179                       ADJUSTR( host_chr )
180#if defined( __parallel )
181    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
182       char1 = 'calculated'
183    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
184               host(1:2) == 'lc' )  .AND.                          &
185             npex == -1  .AND.  pdims(2) == 1 )  THEN
186       char1 = 'forced'
187    ELSE
188       char1 = 'predefined'
189    ENDIF
190    IF ( threads_per_task == 1 )  THEN
191       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
192    ELSE
193       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
194                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
195    ENDIF
196    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
197           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
198         npex == -1  .AND.  pdims(2) == 1 )                      &
199    THEN
200       WRITE ( io, 106 )
201    ELSEIF ( pdims(2) == 1 )  THEN
202       WRITE ( io, 107 )  'x'
203    ELSEIF ( pdims(1) == 1 )  THEN
204       WRITE ( io, 107 )  'y'
205    ENDIF
206    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
207#endif
208    WRITE ( io, 99 )
209
210!
211!-- Numerical schemes
212    WRITE ( io, 110 )
213    IF ( psolver(1:7) == 'poisfft' )  THEN
214       WRITE ( io, 111 )  TRIM( fft_method )
215       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
216    ELSEIF ( psolver == 'sor' )  THEN
217       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
218    ELSEIF ( psolver == 'multigrid' )  THEN
219       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
220       IF ( mg_cycles == -1 )  THEN
221          WRITE ( io, 140 )  residual_limit
222       ELSE
223          WRITE ( io, 141 )  mg_cycles
224       ENDIF
225       IF ( mg_switch_to_pe0_level == 0 )  THEN
226          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
227                             nzt_mg(1)
228       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
229          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
230                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
231                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
232                             nzt_mg(mg_switch_to_pe0_level),    &
233                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
234                             nzt_mg(1)
235       ENDIF
236    ENDIF
237    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
238    THEN
239       WRITE ( io, 142 )
240    ENDIF
241
242    IF ( momentum_advec == 'pw-scheme' )  THEN
243       WRITE ( io, 113 )
244    ELSE
245       WRITE ( io, 114 )
246       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
247       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
248            overshoot_limit_w /= 0.0 )  THEN
249          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
250                             overshoot_limit_w
251       ENDIF
252       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
253            ups_limit_w /= 0.0 )                               &
254       THEN
255          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
256       ENDIF
257       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
258    ENDIF
259    IF ( scalar_advec == 'pw-scheme' )  THEN
260       WRITE ( io, 116 )
261    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
262       WRITE ( io, 117 )
263       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
264       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
265          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
266       ENDIF
267       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
268          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
269       ENDIF
270    ELSE
271       WRITE ( io, 118 )
272    ENDIF
273
274    WRITE ( io, 139 )  TRIM( loop_optimization )
275
276    IF ( galilei_transformation )  THEN
277       IF ( use_ug_for_galilei_tr )  THEN
278          char1 = 'geostrophic wind'
279       ELSE
280          char1 = 'mean wind in model domain'
281       ENDIF
282       IF ( simulated_time_at_begin == simulated_time )  THEN
283          char2 = 'at the start of the run'
284       ELSE
285          char2 = 'at the end of the run'
286       ENDIF
287       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
288                          advected_distance_x/1000.0, advected_distance_y/1000.0
289    ENDIF
290    IF ( timestep_scheme == 'leapfrog' )  THEN
291       WRITE ( io, 120 )
292    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
293       WRITE ( io, 121 )
294    ELSE
295       WRITE ( io, 122 )  timestep_scheme
296    ENDIF
297    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
298    IF ( rayleigh_damping_factor /= 0.0 )  THEN
299       IF ( .NOT. ocean )  THEN
300          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
301               rayleigh_damping_factor
302       ELSE
303          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
304               rayleigh_damping_factor
305       ENDIF
306    ENDIF
307    IF ( humidity )  THEN
308       IF ( .NOT. cloud_physics )  THEN
309          WRITE ( io, 129 )
310       ELSE
311          WRITE ( io, 130 )
312          WRITE ( io, 131 )
313          IF ( radiation )      WRITE ( io, 132 )
314          IF ( precipitation )  WRITE ( io, 133 )
315       ENDIF
316    ENDIF
317    IF ( passive_scalar )  WRITE ( io, 134 )
318    IF ( conserve_volume_flow )  THEN
319       WRITE ( io, 150 )  conserve_volume_flow_mode
320       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
321          WRITE ( io, 151 )  u_bulk, v_bulk
322       ENDIF
323    ELSEIF ( dp_external )  THEN
324       IF ( dp_smooth )  THEN
325          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
326       ELSE
327          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
328       ENDIF
329    ENDIF
330    IF ( large_scale_subsidence )  THEN
331        WRITE ( io, 153 )
332        WRITE ( io, 154 )
333    ENDIF
334    WRITE ( io, 99 )
335
336!
337!-- Runtime and timestep informations
338    WRITE ( io, 200 )
339    IF ( .NOT. dt_fixed )  THEN
340       WRITE ( io, 201 )  dt_max, cfl_factor
341    ELSE
342       WRITE ( io, 202 )  dt
343    ENDIF
344    WRITE ( io, 203 )  simulated_time_at_begin, end_time
345
346    IF ( time_restart /= 9999999.9  .AND. &
347         simulated_time_at_begin == simulated_time )  THEN
348       IF ( dt_restart == 9999999.9 )  THEN
349          WRITE ( io, 204 )  ' Restart at:       ',time_restart
350       ELSE
351          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
352       ENDIF
353    ENDIF
354
355    IF ( simulated_time_at_begin /= simulated_time )  THEN
356       i = MAX ( log_point_s(10)%counts, 1 )
357       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
358          cpuseconds_per_simulated_second = 0.0
359       ELSE
360          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
361                                            ( simulated_time -    &
362                                              simulated_time_at_begin )
363       ENDIF
364       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
365                          log_point_s(10)%sum / REAL( i ),     &
366                          cpuseconds_per_simulated_second
367       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
368          IF ( dt_restart == 9999999.9 )  THEN
369             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
370          ELSE
371             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
372          ENDIF
373       ENDIF
374    ENDIF
375
376!
377!-- Start time for coupled runs, if independent precursor runs for atmosphere
378!-- and ocean are used. In this case, coupling_start_time defines the time
379!-- when the coupling is switched on.
380    IF ( coupling_start_time /= 0.0 )  THEN
381       IF ( coupling_start_time >= simulated_time_at_begin )  THEN
382          char1 = 'Precursor run for a coupled atmosphere-ocean run'
383       ELSE
384          char1 = 'Coupled atmosphere-ocean run following independent ' // &
385                  'precursor runs'
386       ENDIF
387       WRITE ( io, 207 )  char1, coupling_start_time
388    ENDIF
389
390!
391!-- Computational grid
392    IF ( .NOT. ocean )  THEN
393       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
394       IF ( dz_stretch_level_index < nzt+1 )  THEN
395          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
396                             dz_stretch_factor, dz_max
397       ENDIF
398    ELSE
399       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
400       IF ( dz_stretch_level_index > 0 )  THEN
401          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
402                             dz_stretch_factor, dz_max
403       ENDIF
404    ENDIF
405    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
406                       MIN( nnz+2, nzt+2 )
407    IF ( numprocs > 1 )  THEN
408       IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
409          WRITE ( io, 255 )
410       ELSE
411          WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
412       ENDIF
413    ENDIF
414    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
415
416!
417!-- Topography
418    WRITE ( io, 270 )  topography
419    SELECT CASE ( TRIM( topography ) )
420
421       CASE ( 'flat' )
422          ! no actions necessary
423
424       CASE ( 'single_building' )
425          blx = INT( building_length_x / dx )
426          bly = INT( building_length_y / dy )
427          bh  = INT( building_height / dz )
428
429          IF ( building_wall_left == 9999999.9 )  THEN
430             building_wall_left = ( nx + 1 - blx ) / 2 * dx
431          ENDIF
432          bxl = INT ( building_wall_left / dx + 0.5 )
433          bxr = bxl + blx
434
435          IF ( building_wall_south == 9999999.9 )  THEN
436             building_wall_south = ( ny + 1 - bly ) / 2 * dy
437          ENDIF
438          bys = INT ( building_wall_south / dy + 0.5 )
439          byn = bys + bly
440
441          WRITE ( io, 271 )  building_length_x, building_length_y, &
442                             building_height, bxl, bxr, bys, byn
443
444       CASE ( 'single_street_canyon' )
445          ch  = NINT( canyon_height / dz )
446          IF ( canyon_width_x /= 9999999.9 )  THEN
447!
448!--          Street canyon in y direction
449             cwx = NINT( canyon_width_x / dx )
450             IF ( canyon_wall_left == 9999999.9 )  THEN
451                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
452             ENDIF
453             cxl = NINT( canyon_wall_left / dx )
454             cxr = cxl + cwx
455             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
456
457          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
458!
459!--          Street canyon in x direction
460             cwy = NINT( canyon_width_y / dy )
461             IF ( canyon_wall_south == 9999999.9 )  THEN
462                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
463             ENDIF
464             cys = NINT( canyon_wall_south / dy )
465             cyn = cys + cwy
466             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
467          ENDIF
468
469    END SELECT
470
471    IF ( TRIM( topography ) /= 'flat' )  THEN
472       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
473          IF ( TRIM( topography ) == 'single_building' .OR.  &
474               TRIM( topography ) == 'single_street_canyon' )  THEN
475             WRITE ( io, 278 )
476          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
477             WRITE ( io, 279 )
478          ENDIF
479       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
480          WRITE ( io, 278 )
481       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
482          WRITE ( io, 279 )
483       ENDIF
484    ENDIF
485
486    IF ( plant_canopy ) THEN
487
488       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
489       IF ( passive_scalar ) THEN
490          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
491                            leaf_surface_concentration
492       ENDIF
493
494!
495!--    Heat flux at the top of vegetation
496       WRITE ( io, 282 ) cthf
497
498!
499!--    Leaf area density profile
500!--    Building output strings, starting with surface value
501       WRITE ( learde, '(F6.2)' )  lad_surface
502       gradients = '------'
503       slices = '     0'
504       coordinates = '   0.0'
505       i = 1
506       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
507
508          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
509          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
510
511          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
512          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
513
514          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
515          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
516
517          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
518          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
519
520          i = i + 1
521       ENDDO
522
523       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
524                          TRIM( gradients ), TRIM( slices )
525
526    ENDIF
527
528!
529!-- Boundary conditions
530    IF ( ibc_p_b == 0 )  THEN
531       runten = 'p(0)     = 0      |'
532    ELSEIF ( ibc_p_b == 1 )  THEN
533       runten = 'p(0)     = p(1)   |'
534    ELSE
535       runten = 'p(0)     = p(1) +R|'
536    ENDIF
537    IF ( ibc_p_t == 0 )  THEN
538       roben  = 'p(nzt+1) = 0      |'
539    ELSE
540       roben  = 'p(nzt+1) = p(nzt) |'
541    ENDIF
542
543    IF ( ibc_uv_b == 0 )  THEN
544       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
545    ELSE
546       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
547    ENDIF
548    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
549       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
550    ELSEIF ( ibc_uv_t == 0 )  THEN
551       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
552    ELSE
553       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
554    ENDIF
555
556    IF ( ibc_pt_b == 0 )  THEN
557       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
558    ELSEIF ( ibc_pt_b == 1 )  THEN
559       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
560    ELSEIF ( ibc_pt_b == 2 )  THEN
561       runten = TRIM( runten ) // ' pt(0) = from coupled model'
562    ENDIF
563    IF ( ibc_pt_t == 0 )  THEN
564       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
565    ELSEIF( ibc_pt_t == 1 )  THEN
566       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
567    ELSEIF( ibc_pt_t == 2 )  THEN
568       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
569    ENDIF
570
571    WRITE ( io, 300 )  runten, roben
572
573    IF ( .NOT. constant_diffusion )  THEN
574       IF ( ibc_e_b == 1 )  THEN
575          runten = 'e(0)     = e(1)'
576       ELSE
577          runten = 'e(0)     = e(1) = (u*/0.1)**2'
578       ENDIF
579       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
580
581       WRITE ( io, 301 )  'e', runten, roben       
582
583    ENDIF
584
585    IF ( ocean )  THEN
586       runten = 'sa(0)    = sa(1)'
587       IF ( ibc_sa_t == 0 )  THEN
588          roben =  'sa(nzt+1) = sa_surface'
589       ELSE
590          roben =  'sa(nzt+1) = sa(nzt)'
591       ENDIF
592       WRITE ( io, 301 ) 'sa', runten, roben
593    ENDIF
594
595    IF ( humidity )  THEN
596       IF ( ibc_q_b == 0 )  THEN
597          runten = 'q(0)     = q_surface'
598       ELSE
599          runten = 'q(0)     = q(1)'
600       ENDIF
601       IF ( ibc_q_t == 0 )  THEN
602          roben =  'q(nzt)   = q_top'
603       ELSE
604          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
605       ENDIF
606       WRITE ( io, 301 ) 'q', runten, roben
607    ENDIF
608
609    IF ( passive_scalar )  THEN
610       IF ( ibc_q_b == 0 )  THEN
611          runten = 's(0)     = s_surface'
612       ELSE
613          runten = 's(0)     = s(1)'
614       ENDIF
615       IF ( ibc_q_t == 0 )  THEN
616          roben =  's(nzt)   = s_top'
617       ELSE
618          roben =  's(nzt)   = s(nzt-1) + ds/dz'
619       ENDIF
620       WRITE ( io, 301 ) 's', runten, roben
621    ENDIF
622
623    IF ( use_surface_fluxes )  THEN
624       WRITE ( io, 303 )
625       IF ( constant_heatflux )  THEN
626          WRITE ( io, 306 )  surface_heatflux
627          IF ( random_heatflux )  WRITE ( io, 307 )
628       ENDIF
629       IF ( humidity  .AND.  constant_waterflux )  THEN
630          WRITE ( io, 311 ) surface_waterflux
631       ENDIF
632       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
633          WRITE ( io, 313 ) surface_waterflux
634       ENDIF
635    ENDIF
636
637    IF ( use_top_fluxes )  THEN
638       WRITE ( io, 304 )
639       IF ( coupling_mode == 'uncoupled' )  THEN
640          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
641          IF ( constant_top_heatflux )  THEN
642             WRITE ( io, 306 )  top_heatflux
643          ENDIF
644       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
645          WRITE ( io, 316 )
646       ENDIF
647       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
648          WRITE ( io, 309 )  top_salinityflux
649       ENDIF
650       IF ( humidity  .OR.  passive_scalar )  THEN
651          WRITE ( io, 315 )
652       ENDIF
653    ENDIF
654
655    IF ( prandtl_layer )  THEN
656       WRITE ( io, 305 )  0.5 * (zu(1)-zu(0)), roughness_length, kappa, &
657                          rif_min, rif_max
658       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
659       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
660          WRITE ( io, 312 )
661       ENDIF
662       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
663          WRITE ( io, 314 )
664       ENDIF
665    ELSE
666       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
667          WRITE ( io, 310 )  rif_min, rif_max
668       ENDIF
669    ENDIF
670
671    WRITE ( io, 317 )  bc_lr, bc_ns
672    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
673       WRITE ( io, 318 )  outflow_damping_width, km_damp_max
674       IF ( turbulent_inflow )  THEN
675          WRITE ( io, 319 )  recycling_width, recycling_plane, &
676                             inflow_damping_height, inflow_damping_width
677       ENDIF
678    ENDIF
679
680!
681!-- Listing of 1D-profiles
682    WRITE ( io, 325 )  dt_dopr_listing
683    IF ( averaging_interval_pr /= 0.0 )  THEN
684       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
685    ENDIF
686
687!
688!-- DATA output
689    WRITE ( io, 330 )
690    IF ( averaging_interval_pr /= 0.0 )  THEN
691       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
692    ENDIF
693
694!
695!-- 1D-profiles
696    dopr_chr = 'Profile:'
697    IF ( dopr_n /= 0 )  THEN
698       WRITE ( io, 331 )
699
700       output_format = ''
701       IF ( netcdf_output )  THEN
702          IF ( netcdf_data_format == 1 )  THEN
703             output_format = 'NetCDF classic'
704          ELSE
705             output_format = 'NetCDF 64bit offset'
706          ENDIF
707       ENDIF
708       IF ( profil_output )  THEN
709          IF ( netcdf_output )  THEN
710             output_format = TRIM( output_format ) // ' and profil'
711          ELSE
712             output_format = 'profil'
713          ENDIF
714       ENDIF
715       WRITE ( io, 344 )  output_format
716
717       DO  i = 1, dopr_n
718          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
719          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
720             WRITE ( io, 332 )  dopr_chr
721             dopr_chr = '       :'
722          ENDIF
723       ENDDO
724
725       IF ( dopr_chr /= '' )  THEN
726          WRITE ( io, 332 )  dopr_chr
727       ENDIF
728       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
729       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
730    ENDIF
731
732!
733!-- 2D-arrays
734    DO  av = 0, 1
735
736       i = 1
737       do2d_xy = ''
738       do2d_xz = ''
739       do2d_yz = ''
740       DO  WHILE ( do2d(av,i) /= ' ' )
741
742          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
743          do2d_mode = do2d(av,i)(l-1:l)
744
745          SELECT CASE ( do2d_mode )
746             CASE ( 'xy' )
747                ll = LEN_TRIM( do2d_xy )
748                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
749             CASE ( 'xz' )
750                ll = LEN_TRIM( do2d_xz )
751                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
752             CASE ( 'yz' )
753                ll = LEN_TRIM( do2d_yz )
754                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
755          END SELECT
756
757          i = i + 1
758
759       ENDDO
760
761       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
762              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
763              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
764            ( netcdf_output  .OR.  iso2d_output ) )  THEN
765
766          IF (  av == 0 )  THEN
767             WRITE ( io, 334 )  ''
768          ELSE
769             WRITE ( io, 334 )  '(time-averaged)'
770          ENDIF
771
772          IF ( do2d_at_begin )  THEN
773             begin_chr = 'and at the start'
774          ELSE
775             begin_chr = ''
776          ENDIF
777
778          output_format = ''
779          IF ( netcdf_output )  THEN
780             IF ( netcdf_data_format == 1 )  THEN
781                output_format = 'NetCDF classic'
782             ELSEIF ( netcdf_data_format == 2 )  THEN
783                output_format = 'NetCDF 64bit offset'
784             ELSEIF ( netcdf_data_format == 3 )  THEN
785                output_format = 'NetCDF4/HDF5'
786             ELSEIF ( netcdf_data_format == 4 )  THEN
787                output_format = 'NetCDF4/HDF5 clasic'
788             ENDIF
789          ENDIF
790          IF ( iso2d_output )  THEN
791             IF ( netcdf_output )  THEN
792                output_format = TRIM( output_format ) // ' and iso2d'
793             ELSE
794                output_format = 'iso2d'
795             ENDIF
796          ENDIF
797          WRITE ( io, 344 )  output_format
798
799          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
800             i = 1
801             slices = '/'
802             coordinates = '/'
803!
804!--          Building strings with index and coordinate informations of the
805!--          slices
806             DO  WHILE ( section(i,1) /= -9999 )
807
808                WRITE (section_chr,'(I5)')  section(i,1)
809                section_chr = ADJUSTL( section_chr )
810                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
811
812                IF ( section(i,1) == -1 )  THEN
813                   WRITE (coor_chr,'(F10.1)')  -1.0
814                ELSE
815                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
816                ENDIF
817                coor_chr = ADJUSTL( coor_chr )
818                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
819
820                i = i + 1
821             ENDDO
822             IF ( av == 0 )  THEN
823                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
824                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
825                                   TRIM( coordinates )
826                IF ( skip_time_do2d_xy /= 0.0 )  THEN
827                   WRITE ( io, 339 )  skip_time_do2d_xy
828                ENDIF
829             ELSE
830                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
831                                   TRIM( begin_chr ), averaging_interval, &
832                                   dt_averaging_input, 'k', TRIM( slices ), &
833                                   TRIM( coordinates )
834                IF ( skip_time_data_output_av /= 0.0 )  THEN
835                   WRITE ( io, 339 )  skip_time_data_output_av
836                ENDIF
837             ENDIF
838
839          ENDIF
840
841          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
842             i = 1
843             slices = '/'
844             coordinates = '/'
845!
846!--          Building strings with index and coordinate informations of the
847!--          slices
848             DO  WHILE ( section(i,2) /= -9999 )
849
850                WRITE (section_chr,'(I5)')  section(i,2)
851                section_chr = ADJUSTL( section_chr )
852                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
853
854                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
855                coor_chr = ADJUSTL( coor_chr )
856                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
857
858                i = i + 1
859             ENDDO
860             IF ( av == 0 )  THEN
861                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
862                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
863                                   TRIM( coordinates )
864                IF ( skip_time_do2d_xz /= 0.0 )  THEN
865                   WRITE ( io, 339 )  skip_time_do2d_xz
866                ENDIF
867             ELSE
868                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
869                                   TRIM( begin_chr ), averaging_interval, &
870                                   dt_averaging_input, 'j', TRIM( slices ), &
871                                   TRIM( coordinates )
872                IF ( skip_time_data_output_av /= 0.0 )  THEN
873                   WRITE ( io, 339 )  skip_time_data_output_av
874                ENDIF
875             ENDIF
876          ENDIF
877
878          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
879             i = 1
880             slices = '/'
881             coordinates = '/'
882!
883!--          Building strings with index and coordinate informations of the
884!--          slices
885             DO  WHILE ( section(i,3) /= -9999 )
886
887                WRITE (section_chr,'(I5)')  section(i,3)
888                section_chr = ADJUSTL( section_chr )
889                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
890
891                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
892                coor_chr = ADJUSTL( coor_chr )
893                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
894
895                i = i + 1
896             ENDDO
897             IF ( av == 0 )  THEN
898                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
899                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
900                                   TRIM( coordinates )
901                IF ( skip_time_do2d_yz /= 0.0 )  THEN
902                   WRITE ( io, 339 )  skip_time_do2d_yz
903                ENDIF
904             ELSE
905                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
906                                   TRIM( begin_chr ), averaging_interval, &
907                                   dt_averaging_input, 'i', TRIM( slices ), &
908                                   TRIM( coordinates )
909                IF ( skip_time_data_output_av /= 0.0 )  THEN
910                   WRITE ( io, 339 )  skip_time_data_output_av
911                ENDIF
912             ENDIF
913          ENDIF
914
915       ENDIF
916
917    ENDDO
918
919!
920!-- 3d-arrays
921    DO  av = 0, 1
922
923       i = 1
924       do3d_chr = ''
925       DO  WHILE ( do3d(av,i) /= ' ' )
926
927          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
928          i = i + 1
929
930       ENDDO
931
932       IF ( do3d_chr /= '' )  THEN
933          IF ( av == 0 )  THEN
934             WRITE ( io, 336 )  ''
935          ELSE
936             WRITE ( io, 336 )  '(time-averaged)'
937          ENDIF
938
939          output_format = ''
940          IF ( netcdf_output )  THEN
941             IF ( netcdf_data_format == 1 )  THEN
942                output_format = 'NetCDF classic'
943             ELSEIF ( netcdf_data_format == 2 )  THEN
944                output_format = 'NetCDF 64bit offset'
945             ELSEIF ( netcdf_data_format == 3 )  THEN
946                output_format = 'NetCDF4/HDF5'
947             ELSEIF ( netcdf_data_format == 4 )  THEN
948                output_format = 'NetCDF4/HDF5 clasic'
949             ENDIF
950          ENDIF
951          IF ( avs_output )  THEN
952             IF ( netcdf_output )  THEN
953                output_format = TRIM( output_format ) // ' and avs'
954             ELSE
955                output_format = 'avs'
956             ENDIF
957          ENDIF
958          WRITE ( io, 344 )  output_format
959
960          IF ( do3d_at_begin )  THEN
961             begin_chr = 'and at the start'
962          ELSE
963             begin_chr = ''
964          ENDIF
965          IF ( av == 0 )  THEN
966             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
967                                zu(nz_do3d), nz_do3d
968          ELSE
969             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
970                                TRIM( begin_chr ), averaging_interval, &
971                                dt_averaging_input, zu(nz_do3d), nz_do3d
972          ENDIF
973
974          IF ( do3d_compress )  THEN
975             do3d_chr = ''
976             i = 1
977             DO WHILE ( do3d(av,i) /= ' ' )
978
979                SELECT CASE ( do3d(av,i) )
980                   CASE ( 'u' )
981                      j = 1
982                   CASE ( 'v' )
983                      j = 2
984                   CASE ( 'w' )
985                      j = 3
986                   CASE ( 'p' )
987                      j = 4
988                   CASE ( 'pt' )
989                      j = 5
990                END SELECT
991                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
992                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
993                           ':' // prec // ','
994                i = i + 1
995
996             ENDDO
997             WRITE ( io, 338 )  do3d_chr
998
999          ENDIF
1000
1001          IF ( av == 0 )  THEN
1002             IF ( skip_time_do3d /= 0.0 )  THEN
1003                WRITE ( io, 339 )  skip_time_do3d
1004             ENDIF
1005          ELSE
1006             IF ( skip_time_data_output_av /= 0.0 )  THEN
1007                WRITE ( io, 339 )  skip_time_data_output_av
1008             ENDIF
1009          ENDIF
1010
1011       ENDIF
1012
1013    ENDDO
1014
1015!
1016!-- masked arrays
1017    IF ( masks > 0 )  WRITE ( io, 345 )  &
1018         mask_scale_x, mask_scale_y, mask_scale_z
1019    DO  mid = 1, masks
1020       DO  av = 0, 1
1021
1022          i = 1
1023          domask_chr = ''
1024          DO  WHILE ( domask(mid,av,i) /= ' ' )
1025             domask_chr = TRIM( domask_chr ) // ' ' //  &
1026                          TRIM( domask(mid,av,i) ) // ','
1027             i = i + 1
1028          ENDDO
1029
1030          IF ( domask_chr /= '' )  THEN
1031             IF ( av == 0 )  THEN
1032                WRITE ( io, 346 )  '', mid
1033             ELSE
1034                WRITE ( io, 346 )  ' (time-averaged)', mid
1035             ENDIF
1036
1037             output_format = ''
1038             IF ( netcdf_output )  THEN
1039                IF ( netcdf_data_format == 1 )  THEN
1040                   output_format = 'NetCDF classic'
1041                ELSEIF ( netcdf_data_format == 2 )  THEN
1042                   output_format = 'NetCDF 64bit offset'
1043                ELSEIF ( netcdf_data_format == 3 )  THEN
1044                   output_format = 'NetCDF4/HDF5'
1045                ELSEIF ( netcdf_data_format == 4 )  THEN
1046                   output_format = 'NetCDF4/HDF5 clasic'
1047                ENDIF
1048             ENDIF
1049             WRITE ( io, 344 )  output_format
1050
1051             IF ( av == 0 )  THEN
1052                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1053             ELSE
1054                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1055                                   averaging_interval, dt_averaging_input
1056             ENDIF
1057
1058             IF ( av == 0 )  THEN
1059                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1060                   WRITE ( io, 339 )  skip_time_domask(mid)
1061                ENDIF
1062             ELSE
1063                IF ( skip_time_data_output_av /= 0.0 )  THEN
1064                   WRITE ( io, 339 )  skip_time_data_output_av
1065                ENDIF
1066             ENDIF
1067!
1068!--          output locations
1069             DO  dim = 1, 3
1070                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1071                   count = 0
1072                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1073                      count = count + 1
1074                   ENDDO
1075                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1076                                      mask(mid,dim,:count)
1077                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1078                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1079                         mask_loop(mid,dim,3) == 0.0 )  THEN
1080                   WRITE ( io, 350 )  dir(dim), dir(dim)
1081                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1082                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1083                                      mask_loop(mid,dim,1:2)
1084                ELSE
1085                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1086                                      mask_loop(mid,dim,1:3)
1087                ENDIF
1088             ENDDO
1089          ENDIF
1090
1091       ENDDO
1092    ENDDO
1093
1094!
1095!-- Timeseries
1096    IF ( dt_dots /= 9999999.9 )  THEN
1097       WRITE ( io, 340 )
1098
1099       output_format = ''
1100       IF ( netcdf_output )  THEN
1101          IF ( netcdf_data_format == 1 )  THEN
1102             output_format = 'NetCDF classic'
1103          ELSE
1104             output_format = 'NetCDF 64bit offset'
1105          ENDIF
1106       ENDIF
1107       IF ( profil_output )  THEN
1108          IF ( netcdf_output )  THEN
1109             output_format = TRIM( output_format ) // ' and profil'
1110          ELSE
1111             output_format = 'profil'
1112          ENDIF
1113       ENDIF
1114       WRITE ( io, 344 )  output_format
1115       WRITE ( io, 341 )  dt_dots
1116    ENDIF
1117
1118#if defined( __dvrp_graphics )
1119!
1120!-- Dvrp-output
1121    IF ( dt_dvrp /= 9999999.9 )  THEN
1122       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1123                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1124       i = 1
1125       l = 0
1126       m = 0
1127       DO WHILE ( mode_dvrp(i) /= ' ' )
1128          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1129             READ ( mode_dvrp(i), '(10X,I2)' )  j
1130             l = l + 1
1131             IF ( do3d(0,j) /= ' ' )  THEN
1132                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1133                                   isosurface_color(:,l)
1134             ENDIF
1135          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1136             READ ( mode_dvrp(i), '(6X,I2)' )  j
1137             m = m + 1
1138             IF ( do2d(0,j) /= ' ' )  THEN
1139                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1140                                   slicer_range_limits_dvrp(:,m)
1141             ENDIF
1142          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1143             WRITE ( io, 363 )  dvrp_psize
1144             IF ( particle_dvrpsize /= 'none' )  THEN
1145                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1146                                   dvrpsize_interval
1147             ENDIF
1148             IF ( particle_color /= 'none' )  THEN
1149                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1150                                   color_interval
1151             ENDIF
1152          ENDIF
1153          i = i + 1
1154       ENDDO
1155
1156       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1157                          superelevation_y, superelevation, clip_dvrp_l, &
1158                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1159
1160       IF ( TRIM( topography ) /= 'flat' )  THEN
1161          WRITE ( io, 366 )  topography_color
1162          IF ( cluster_size > 1 )  THEN
1163             WRITE ( io, 367 )  cluster_size
1164          ENDIF
1165       ENDIF
1166
1167    ENDIF
1168#endif
1169
1170#if defined( __spectra )
1171!
1172!-- Spectra output
1173    IF ( dt_dosp /= 9999999.9 ) THEN
1174       WRITE ( io, 370 )
1175
1176       output_format = ''
1177       IF ( netcdf_output )  THEN
1178          IF ( netcdf_data_format == 1 )  THEN
1179             output_format = 'NetCDF classic'
1180          ELSE
1181             output_format = 'NetCDF 64bit offset'
1182          ENDIF
1183       ENDIF
1184       IF ( profil_output )  THEN
1185          IF ( netcdf_output )  THEN
1186             output_format = TRIM( output_format ) // ' and profil'
1187          ELSE
1188             output_format = 'profil'
1189          ENDIF
1190       ENDIF
1191       WRITE ( io, 344 )  output_format
1192       WRITE ( io, 371 )  dt_dosp
1193       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1194       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1195                          ( spectra_direction(i), i = 1,10 ),  &
1196                          ( comp_spectra_level(i), i = 1,100 ), &
1197                          ( plot_spectra_level(i), i = 1,100 ), &
1198                          averaging_interval_sp, dt_averaging_input_pr
1199    ENDIF
1200#endif
1201
1202    WRITE ( io, 99 )
1203
1204!
1205!-- Physical quantities
1206    WRITE ( io, 400 )
1207
1208!
1209!-- Geostrophic parameters
1210    WRITE ( io, 410 )  omega, phi, f, fs
1211
1212!
1213!-- Other quantities
1214    WRITE ( io, 411 )  g
1215    IF ( use_reference )  THEN
1216       IF ( ocean )  THEN
1217          WRITE ( io, 412 )  prho_reference
1218       ELSE
1219          WRITE ( io, 413 )  pt_reference
1220       ENDIF
1221    ENDIF
1222
1223!
1224!-- Cloud physics parameters
1225    IF ( cloud_physics ) THEN
1226       WRITE ( io, 415 )
1227       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1228    ENDIF
1229
1230!-- Profile of the geostrophic wind (component ug)
1231!-- Building output strings
1232    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1233    gradients = '------'
1234    slices = '     0'
1235    coordinates = '   0.0'
1236    i = 1
1237    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1238     
1239       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1240       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1241
1242       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1243       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1244
1245       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1246       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1247
1248       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1249       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1250
1251       IF ( i == 10 )  THEN
1252          EXIT
1253       ELSE
1254          i = i + 1
1255       ENDIF
1256
1257    ENDDO
1258
1259    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1260                       TRIM( gradients ), TRIM( slices )
1261
1262!-- Profile of the geostrophic wind (component vg)
1263!-- Building output strings
1264    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1265    gradients = '------'
1266    slices = '     0'
1267    coordinates = '   0.0'
1268    i = 1
1269    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1270
1271       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1272       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1273
1274       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1275       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1276
1277       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1278       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1279
1280       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1281       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1282
1283       IF ( i == 10 )  THEN
1284          EXIT
1285       ELSE
1286          i = i + 1
1287       ENDIF
1288 
1289    ENDDO
1290
1291    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1292                       TRIM( gradients ), TRIM( slices )
1293
1294!
1295!-- Initial temperature profile
1296!-- Building output strings, starting with surface temperature
1297    WRITE ( temperatures, '(F6.2)' )  pt_surface
1298    gradients = '------'
1299    slices = '     0'
1300    coordinates = '   0.0'
1301    i = 1
1302    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1303
1304       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1305       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1306
1307       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1308       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1309
1310       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1311       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1312
1313       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1314       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1315
1316       IF ( i == 10 )  THEN
1317          EXIT
1318       ELSE
1319          i = i + 1
1320       ENDIF
1321
1322    ENDDO
1323
1324    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1325                       TRIM( gradients ), TRIM( slices )
1326
1327!
1328!-- Initial humidity profile
1329!-- Building output strings, starting with surface humidity
1330    IF ( humidity  .OR.  passive_scalar )  THEN
1331       WRITE ( temperatures, '(E8.1)' )  q_surface
1332       gradients = '--------'
1333       slices = '       0'
1334       coordinates = '     0.0'
1335       i = 1
1336       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1337         
1338          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1339          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1340
1341          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1342          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1343         
1344          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1345          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1346         
1347          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1348          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1349
1350          IF ( i == 10 )  THEN
1351             EXIT
1352          ELSE
1353             i = i + 1
1354          ENDIF
1355
1356       ENDDO
1357
1358       IF ( humidity )  THEN
1359          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1360                             TRIM( gradients ), TRIM( slices )
1361       ELSE
1362          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1363                             TRIM( gradients ), TRIM( slices )
1364       ENDIF
1365    ENDIF
1366
1367!
1368!-- Initial salinity profile
1369!-- Building output strings, starting with surface salinity
1370    IF ( ocean )  THEN
1371       WRITE ( temperatures, '(F6.2)' )  sa_surface
1372       gradients = '------'
1373       slices = '     0'
1374       coordinates = '   0.0'
1375       i = 1
1376       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1377
1378          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1379          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1380
1381          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1382          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1383
1384          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1385          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1386
1387          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1388          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1389
1390          IF ( i == 10 )  THEN
1391             EXIT
1392          ELSE
1393             i = i + 1
1394          ENDIF
1395
1396       ENDDO
1397
1398       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1399                          TRIM( gradients ), TRIM( slices )
1400    ENDIF
1401
1402!
1403!-- Profile for the large scale vertial velocity
1404!-- Building output strings, starting with surface value
1405    IF ( large_scale_subsidence )  THEN
1406       temperatures = '   0.0'
1407       gradients = '------'
1408       slices = '     0'
1409       coordinates = '   0.0'
1410       i = 1
1411       DO  WHILE ( ws_vertical_gradient_level_ind(i) /= -9999 )
1412
1413          WRITE (coor_chr,'(E10.2,7X)')  &
1414                                w_subs(ws_vertical_gradient_level_ind(i))
1415          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1416
1417          WRITE (coor_chr,'(E10.2,7X)')  ws_vertical_gradient(i)
1418          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1419
1420          WRITE (coor_chr,'(I10,7X)')  ws_vertical_gradient_level_ind(i)
1421          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1422
1423          WRITE (coor_chr,'(F10.2,7X)')  ws_vertical_gradient_level(i)
1424          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1425
1426          IF ( i == 10 )  THEN
1427             EXIT
1428          ELSE
1429             i = i + 1
1430          ENDIF
1431
1432       ENDDO
1433
1434       WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1435                          TRIM( gradients ), TRIM( slices )
1436    ENDIF
1437
1438!
1439!-- LES / turbulence parameters
1440    WRITE ( io, 450 )
1441
1442!--
1443! ... LES-constants used must still be added here
1444!--
1445    IF ( constant_diffusion )  THEN
1446       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1447                          prandtl_number
1448    ENDIF
1449    IF ( .NOT. constant_diffusion)  THEN
1450       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1451       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1452       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1453       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1454    ENDIF
1455
1456!
1457!-- Special actions during the run
1458    WRITE ( io, 470 )
1459    IF ( create_disturbances )  THEN
1460       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1461                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1462                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1463       IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1464          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1465       ELSE
1466          WRITE ( io, 473 )  disturbance_energy_limit
1467       ENDIF
1468       WRITE ( io, 474 )  TRIM( random_generator )
1469    ENDIF
1470    IF ( pt_surface_initial_change /= 0.0 )  THEN
1471       WRITE ( io, 475 )  pt_surface_initial_change
1472    ENDIF
1473    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1474       WRITE ( io, 476 )  q_surface_initial_change       
1475    ENDIF
1476    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1477       WRITE ( io, 477 )  q_surface_initial_change       
1478    ENDIF
1479
1480    IF ( particle_advection )  THEN
1481!
1482!--    Particle attributes
1483       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1484                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1485                          end_time_prel, dt_sort_particles
1486       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1487       IF ( random_start_position )  WRITE ( io, 481 )
1488       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1489       WRITE ( io, 495 )  total_number_of_particles
1490       IF ( maximum_number_of_tailpoints /= 0 )  THEN
1491          WRITE ( io, 483 )  maximum_number_of_tailpoints
1492          IF ( minimum_tailpoint_distance /= 0 )  THEN
1493             WRITE ( io, 484 )  total_number_of_tails,      &
1494                                minimum_tailpoint_distance, &
1495                                maximum_tailpoint_age
1496          ENDIF
1497       ENDIF
1498       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1499          WRITE ( io, 485 )  dt_write_particle_data
1500          output_format = ''
1501          IF ( netcdf_output )  THEN
1502             IF ( netcdf_data_format > 1 )  THEN
1503                output_format = 'netcdf (64 bit offset) and binary'
1504             ELSE
1505                output_format = 'netcdf and binary'
1506             ENDIF
1507          ELSE
1508             output_format = 'binary'
1509          ENDIF
1510          WRITE ( io, 344 )  output_format
1511       ENDIF
1512       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1513       IF ( write_particle_statistics )  WRITE ( io, 486 )
1514
1515       WRITE ( io, 487 )  number_of_particle_groups
1516
1517       DO  i = 1, number_of_particle_groups
1518          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1519             WRITE ( io, 490 )  i, 0.0
1520             WRITE ( io, 492 )
1521          ELSE
1522             WRITE ( io, 490 )  i, radius(i)
1523             IF ( density_ratio(i) /= 0.0 )  THEN
1524                WRITE ( io, 491 )  density_ratio(i)
1525             ELSE
1526                WRITE ( io, 492 )
1527             ENDIF
1528          ENDIF
1529          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1530                             pdx(i), pdy(i), pdz(i)
1531          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1532       ENDDO
1533
1534    ENDIF
1535
1536
1537!
1538!-- Parameters of 1D-model
1539    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1540       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1541                          mixing_length_1d, dissipation_1d
1542       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1543          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1544       ENDIF
1545    ENDIF
1546
1547!
1548!-- User-defined informations
1549    CALL user_header( io )
1550
1551    WRITE ( io, 99 )
1552
1553!
1554!-- Write buffer contents to disc immediately
1555    CALL local_flush( io )
1556
1557!
1558!-- Here the FORMATs start
1559
1560 99 FORMAT (1X,78('-'))
1561100 FORMAT (/1X,'***************************',9X,42('-')/        &
1562            1X,'* ',A,' *',9X,A/                               &
1563            1X,'***************************',9X,42('-'))
1564101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1565            37X,42('-'))
1566102 FORMAT (/' Date:              ',A8,9X,'Run:       ',A20/      &
1567            ' Time:              ',A8,9X,'Run-No.:   ',I2.2/     &
1568            ' Run on host:     ',A10)
1569#if defined( __parallel )
1570103 FORMAT (' Number of PEs:',8X,I5,9X,'Processor grid (x,y): (',I3,',',I3, &
1571              ')',1X,A)
1572104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1573              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1574105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1575106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1576            37X,'because the job is running on an SMP-cluster')
1577107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1578#endif
1579110 FORMAT (/' Numerical Schemes:'/ &
1580             ' -----------------'/)
1581111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1582112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1583            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1584113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1585                  ' or Upstream')
1586114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1587115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1588116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1589                  ' or Upstream')
1590117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1591118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1592119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1593            '     Translation velocity = ',A/ &
1594            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1595120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1596                  ' of timestep changes)')
1597121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1598                  ' timestep changes')
1599122 FORMAT (' --> Time differencing scheme: ',A)
1600123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1601            '     maximum damping coefficient: ',F5.3, ' 1/s')
1602124 FORMAT ('     Spline-overshoots are being suppressed')
1603125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1604                  ' of'/                                                       &
1605            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1606126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1607                  ' of'/                                                       &
1608            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1609127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1610            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1611128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1612            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1613129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1614130 FORMAT (' --> Additional prognostic equation for the total water content')
1615131 FORMAT (' --> Parameterization of condensation processes via (0%-or100%)')
1616132 FORMAT (' --> Parameterization of long-wave radiation processes via'/ &
1617            '     effective emissivity scheme')
1618133 FORMAT (' --> Precipitation parameterization via Kessler-Scheme')
1619134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1620135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1621                  A,'-cycle)'/ &
1622            '     number of grid levels:                   ',I2/ &
1623            '     Gauss-Seidel red/black iterations:       ',I2)
1624136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1625                  I3,')')
1626137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1627            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1628                  I3,')'/ &
1629            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1630                  I3,')')
1631138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1632139 FORMAT (' --> Loop optimization method: ',A)
1633140 FORMAT ('     maximum residual allowed:                ',E10.3)
1634141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1635142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1636                  'step')
1637143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1638                  'kinetic energy')
1639150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1640                  'conserved'/ &
1641            '     using the ',A,' mode')
1642151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1643152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1644           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1645           /'     starting from dp_level_b =', F8.3, 'm', A /)
1646153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1647                  'prognostic equation for')
1648154 FORMAT ('     the potential temperature')
1649200 FORMAT (//' Run time and time step information:'/ &
1650             ' ----------------------------------'/)
1651201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1652             '    CFL-factor: ',F4.2)
1653202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1654203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1655             ' End time:         ',F9.3,' s')
1656204 FORMAT ( A,F9.3,' s')
1657205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1658206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1659             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1660               '  ',F9.3,' s'/                                                 &
1661             '                                   per second of simulated tim', &
1662               'e: ',F9.3,' s')
1663207 FORMAT ( A/' Coupling start time:',F9.3,' s')
1664250 FORMAT (//' Computational grid and domain size:'/ &
1665              ' ----------------------------------'// &
1666              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1667              ' m    dz =    ',F7.3,' m'/ &
1668              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1669              ' m  z(u) = ',F10.3,' m'/)
1670252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1671              ' factor: ',F5.3/ &
1672            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1673254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1674            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1675255 FORMAT (' Subdomains have equal size')
1676256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1677              'have smaller sizes'/                                          &
1678            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1679260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1680             ' degrees')
1681270 FORMAT (//' Topography informations:'/ &
1682              ' -----------------------'// &
1683              1X,'Topography: ',A)
1684271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1685              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1686                ' / ',I4)
1687272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1688              ' direction' / &
1689              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1690              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1691278 FORMAT (' Topography grid definition convention:'/ &
1692            ' cell edge (staggered grid points'/  &
1693            ' (u in x-direction, v in y-direction))' /)
1694279 FORMAT (' Topography grid definition convention:'/ &
1695            ' cell center (scalar grid points)' /)
1696280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1697              ' ------------------------------'// &
1698              ' Canopy mode: ', A / &
1699              ' Canopy top: ',I4 / &
1700              ' Leaf drag coefficient: ',F6.2 /)
1701281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1702              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1703282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1704283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1705              ' Height:              ',A,'  m'/ &
1706              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1707              ' Gradient:            ',A,'  m**2/m**4'/ &
1708              ' Gridpoint:           ',A)
1709               
1710300 FORMAT (//' Boundary conditions:'/ &
1711             ' -------------------'// &
1712             '                     p                    uv             ', &
1713             '                   pt'// &
1714             ' B. bound.: ',A/ &
1715             ' T. bound.: ',A)
1716301 FORMAT (/'                     ',A// &
1717             ' B. bound.: ',A/ &
1718             ' T. bound.: ',A)
1719303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1720304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1721305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1722               'computational u,v-level:'// &
1723             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1724             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1725306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1726307 FORMAT ('       Heatflux has a random normal distribution')
1727308 FORMAT ('       Predefined surface temperature')
1728309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1729310 FORMAT (//'    1D-Model:'// &
1730             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1731311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1732312 FORMAT ('       Predefined surface humidity')
1733313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1734314 FORMAT ('       Predefined scalar value at the surface')
1735315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1736316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1737                    'atmosphere model')
1738317 FORMAT (//' Lateral boundaries:'/ &
1739            '       left/right:  ',A/    &
1740            '       north/south: ',A)
1741318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1742                    'max =',F5.1,' m**2/s')
1743319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1744            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1745            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1746320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1747            '                                          v: ',F9.6,' m**2/s**2')
1748325 FORMAT (//' List output:'/ &
1749             ' -----------'//  &
1750            '    1D-Profiles:'/    &
1751            '       Output every             ',F8.2,' s')
1752326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1753            '       Averaging input every    ',F8.2,' s')
1754330 FORMAT (//' Data output:'/ &
1755             ' -----------'/)
1756331 FORMAT (/'    1D-Profiles:')
1757332 FORMAT (/'       ',A)
1758333 FORMAT ('       Output every             ',F8.2,' s',/ &
1759            '       Time averaged over       ',F8.2,' s'/ &
1760            '       Averaging input every    ',F8.2,' s')
1761334 FORMAT (/'    2D-Arrays',A,':')
1762335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1763            '       Output every             ',F8.2,' s  ',A/ &
1764            '       Cross sections at ',A1,' = ',A/ &
1765            '       scalar-coordinates:   ',A,' m'/)
1766336 FORMAT (/'    3D-Arrays',A,':')
1767337 FORMAT (/'       Arrays: ',A/ &
1768            '       Output every             ',F8.2,' s  ',A/ &
1769            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1770338 FORMAT ('       Compressed data output'/ &
1771            '       Decimal precision: ',A/)
1772339 FORMAT ('       No output during initial ',F8.2,' s')
1773340 FORMAT (/'    Time series:')
1774341 FORMAT ('       Output every             ',F8.2,' s'/)
1775342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1776            '       Output every             ',F8.2,' s  ',A/ &
1777            '       Time averaged over       ',F8.2,' s'/ &
1778            '       Averaging input every    ',F8.2,' s'/ &
1779            '       Cross sections at ',A1,' = ',A/ &
1780            '       scalar-coordinates:   ',A,' m'/)
1781343 FORMAT (/'       Arrays: ',A/ &
1782            '       Output every             ',F8.2,' s  ',A/ &
1783            '       Time averaged over       ',F8.2,' s'/ &
1784            '       Averaging input every    ',F8.2,' s'/ &
1785            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1786344 FORMAT ('       Output format: ',A/)
1787345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1788            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1789            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1790            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1791346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1792347 FORMAT ('       Variables: ',A/ &
1793            '       Output every             ',F8.2,' s')
1794348 FORMAT ('       Variables: ',A/ &
1795            '       Output every             ',F8.2,' s'/ &
1796            '       Time averaged over       ',F8.2,' s'/ &
1797            '       Averaging input every    ',F8.2,' s')
1798349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1799            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1800            13('       ',8(F8.2,',')/) )
1801350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1802            'all gridpoints along ',A,'-direction (default).' )
1803351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1804            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1805            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1806#if defined( __dvrp_graphics )
1807360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1808            '       Output every      ',F7.1,' s'/ &
1809            '       Output mode:      ',A/ &
1810            '       Host / User:      ',A,' / ',A/ &
1811            '       Directory:        ',A// &
1812            '       The sequence contains:')
1813361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1814            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1815362 FORMAT (/'       Slicer plane ',A/ &
1816            '       Slicer limits: [',F6.2,',',F6.2,']')
1817363 FORMAT (/'       Particles'/ &
1818            '          particle size:  ',F7.2,' m')
1819364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1820                       F6.2,',',F6.2,']')
1821365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1822            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1823                     ')'/ &
1824            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1825            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1826366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1827367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1828#endif
1829#if defined( __spectra )
1830370 FORMAT ('    Spectra:')
1831371 FORMAT ('       Output every ',F7.1,' s'/)
1832372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1833            '       Directions: ', 10(A5,',')/                         &
1834            '       height levels  k = ', 20(I3,',')/                  &
1835            '                          ', 20(I3,',')/                  &
1836            '                          ', 20(I3,',')/                  &
1837            '                          ', 20(I3,',')/                  &
1838            '                          ', 19(I3,','),I3,'.'/           &
1839            '       height levels selected for standard plot:'/        &
1840            '                      k = ', 20(I3,',')/                  &
1841            '                          ', 20(I3,',')/                  &
1842            '                          ', 20(I3,',')/                  &
1843            '                          ', 20(I3,',')/                  &
1844            '                          ', 19(I3,','),I3,'.'/           &
1845            '       Time averaged over ', F7.1, ' s,' /                &
1846            '       Profiles for the time averaging are taken every ', &
1847                    F6.1,' s')
1848#endif
1849400 FORMAT (//' Physical quantities:'/ &
1850              ' -------------------'/)
1851410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1852            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1853            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1854            '                            f*    = ',F9.6,' 1/s')
1855411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1856412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1857413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1858415 FORMAT (/'    Cloud physics parameters:'/ &
1859             '    ------------------------'/)
1860416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1861            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1862            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1863            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1864            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1865420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1866            '       Height:        ',A,'  m'/ &
1867            '       Temperature:   ',A,'  K'/ &
1868            '       Gradient:      ',A,'  K/100m'/ &
1869            '       Gridpoint:     ',A)
1870421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1871            '       Height:      ',A,'  m'/ &
1872            '       Humidity:    ',A,'  kg/kg'/ &
1873            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1874            '       Gridpoint:   ',A)
1875422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1876            '       Height:                  ',A,'  m'/ &
1877            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1878            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1879            '       Gridpoint:               ',A)
1880423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1881            '       Height:      ',A,'  m'/ &
1882            '       ug:          ',A,'  m/s'/ &
1883            '       Gradient:    ',A,'  1/100s'/ &
1884            '       Gridpoint:   ',A)
1885424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1886            '       Height:      ',A,'  m'/ &
1887            '       vg:          ',A,'  m/s'/ &
1888            '       Gradient:    ',A,'  1/100s'/ &
1889            '       Gridpoint:   ',A)
1890425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1891            '       Height:     ',A,'  m'/ &
1892            '       Salinity:   ',A,'  psu'/ &
1893            '       Gradient:   ',A,'  psu/100m'/ &
1894            '       Gridpoint:  ',A)
1895426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1896            '       Height:      ',A,'  m'/ &
1897            '       w_subs:      ',A,'  m/s'/ &
1898            '       Gradient:    ',A,'  (m/s)/100m'/ &
1899            '       Gridpoint:   ',A)
1900450 FORMAT (//' LES / Turbulence quantities:'/ &
1901              ' ---------------------------'/)
1902451 FORMAT ('   Diffusion coefficients are constant:'/ &
1903            '   Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1904452 FORMAT ('   Mixing length is limited to the Prandtl mixing lenth.')
1905453 FORMAT ('   Mixing length is limited to ',F4.2,' * z')
1906454 FORMAT ('   TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1907455 FORMAT ('   initial TKE is prescribed as ',E9.2,' (m/s)**2')
1908470 FORMAT (//' Actions during the simulation:'/ &
1909              ' -----------------------------'/)
1910471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1911            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1912            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1913            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1914472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1915                 ' to i/j =',I4)
1916473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1917                 1X,F5.3, ' m**2/s**2')
1918474 FORMAT ('    Random number generator used    : ',A/)
1919475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1920                 'respectively, if'/ &
1921            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1922                 ' 3D-simulation'/)
1923476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1924                 'respectively, if the'/ &
1925            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1926                 ' the 3D-simulation'/)
1927477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1928                 'respectively, if the'/ &
1929            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1930                 ' the 3D-simulation'/)
1931480 FORMAT ('    Particles:'/ &
1932            '    ---------'// &
1933            '       Particle advection is active (switched on at t = ', F7.1, &
1934                    ' s)'/ &
1935            '       Start of new particle generations every  ',F6.1,' s'/ &
1936            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
1937            '                            bottom:     ', A, ' top:         ', A/&
1938            '       Maximum particle age:                 ',F9.1,' s'/ &
1939            '       Advection stopped at t = ',F9.1,' s'/ &
1940            '       Particles are sorted every ',F9.1,' s'/)
1941481 FORMAT ('       Particles have random start positions'/)
1942482 FORMAT ('          Particles are advected only horizontally'/)
1943483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
1944484 FORMAT ('            Number of tails of the total domain: ',I10/ &
1945            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
1946            '            Maximum age of the end of the tail:  ',F8.2,' s')
1947485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
1948486 FORMAT ('       Particle statistics are written on file'/)
1949487 FORMAT ('       Number of particle groups: ',I2/)
1950488 FORMAT ('       SGS velocity components are used for particle advection'/ &
1951            '          minimum timestep for advection: ', F7.5/)
1952489 FORMAT ('       Number of particles simultaneously released at each ', &
1953                    'point: ', I5/)
1954490 FORMAT ('       Particle group ',I2,':'/ &
1955            '          Particle radius: ',E10.3, 'm')
1956491 FORMAT ('          Particle inertia is activated'/ &
1957            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
1958492 FORMAT ('          Particles are advected only passively (no inertia)'/)
1959493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
1960            '                                         y:',F8.1,' - ',F8.1,' m'/&
1961            '                                         z:',F8.1,' - ',F8.1,' m'/&
1962            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
1963                       ' m  dz = ',F8.1,' m'/)
1964494 FORMAT ('       Output of particle time series in NetCDF format every ', &
1965                    F8.2,' s'/)
1966495 FORMAT ('       Number of particles in total domain: ',I10/)
1967500 FORMAT (//' 1D-Model parameters:'/                           &
1968              ' -------------------'//                           &
1969            '    Simulation time:                   ',F8.1,' s'/ &
1970            '    Run-controll output every:         ',F8.1,' s'/ &
1971            '    Vertical profile output every:     ',F8.1,' s'/ &
1972            '    Mixing length calculation:         ',A/         &
1973            '    Dissipation calculation:           ',A/)
1974502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
1975
1976
1977 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.