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

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