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

Last change on this file since 275 was 256, checked in by letzel, 15 years ago
  • topography_grid_convention moved from userpar to inipar
  • documentation and examples updated
  • Property svn:keywords set to Id
File size: 66.6 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Output of messages replaced by message handling routine.
7! Output of cluster_size
8! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
9! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
10! dp_smooth, dpdxy, u_bulk, v_bulk
11! topography_grid_convention moved from user_header
12!
13! Former revisions:
14! -----------------
15! $Id: header.f90 256 2009-03-08 08:56:27Z raasch $
16!
17! 206 2008-10-13 14:59:11Z raasch
18! Bugfix: error in zu index in case of section_xy = -1
19!
20! 198 2008-09-17 08:55:28Z raasch
21! Format adjustments allowing output of larger revision numbers
22!
23! 197 2008-09-16 15:29:03Z raasch
24! allow 100 spectra levels instead of 10 for consistency with
25! define_netcdf_header,
26! bugfix in the output of the characteristic levels of potential temperature,
27! geostrophic wind, scalar concentration, humidity and leaf area density,
28! output of turbulence recycling informations
29!
30! 138 2007-11-28 10:03:58Z letzel
31! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
32! Allow two instead of one digit to specify isosurface and slicer variables.
33! Output of sorting frequency of particles
34!
35! 108 2007-08-24 15:10:38Z letzel
36! Output of informations for coupled model runs (boundary conditions etc.)
37! + output of momentumfluxes at the top boundary
38! Rayleigh damping for ocean, e_init
39!
40! 97 2007-06-21 08:23:15Z raasch
41! Adjustments for the ocean version.
42! use_pt_reference renamed use_reference
43!
44! 87 2007-05-22 15:46:47Z raasch
45! Bugfix: output of use_upstream_for_tke
46!
47! 82 2007-04-16 15:40:52Z raasch
48! Preprocessor strings for different linux clusters changed to "lc",
49! routine local_flush is used for buffer flushing
50!
51! 76 2007-03-29 00:58:32Z raasch
52! Output of netcdf_64bit_3d, particles-package is now part of the default code,
53! output of the loop optimization method, moisture renamed humidity,
54! output of subversion revision number
55!
56! 19 2007-02-23 04:53:48Z raasch
57! Output of scalar flux applied at top boundary
58!
59! RCS Log replace by Id keyword, revision history cleaned up
60!
61! Revision 1.63  2006/08/22 13:53:13  raasch
62! Output of dz_max
63!
64! Revision 1.1  1997/08/11 06:17:20  raasch
65! Initial revision
66!
67!
68! Description:
69! ------------
70! Writing a header with all important informations about the actual run.
71! This subroutine is called three times, two times at the beginning
72! (writing information on files RUN_CONTROL and HEADER) and one time at the
73! end of the run, then writing additional information about CPU-usage on file
74! header.
75!------------------------------------------------------------------------------!
76
77    USE arrays_3d
78    USE control_parameters
79    USE cloud_parameters
80    USE cpulog
81    USE dvrp_variables
82    USE grid_variables
83    USE indices
84    USE model_1d
85    USE particle_attributes
86    USE pegrid
87    USE spectrum
88
89    IMPLICIT NONE
90
91    CHARACTER (LEN=1)  ::  prec
92    CHARACTER (LEN=2)  ::  do2d_mode
93    CHARACTER (LEN=5)  ::  section_chr
94    CHARACTER (LEN=9)  ::  time_to_string
95    CHARACTER (LEN=10) ::  coor_chr, host_chr
96    CHARACTER (LEN=16) ::  begin_chr
97    CHARACTER (LEN=23) ::  ver_rev
98    CHARACTER (LEN=40) ::  output_format
99    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
100                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
101                           run_classification
102    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
103                           temperatures, ugcomponent, vgcomponent
104    CHARACTER (LEN=85) ::  roben, runten
105
106    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, cwx, cwy, cxl, cxr, &
107         cyn, cys, i, ihost, io, j, l, ll
108    REAL    ::  cpuseconds_per_simulated_second
109
110!
111!-- Open the output file. At the end of the simulation, output is directed
112!-- to unit 19.
113    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
114         .NOT. simulated_time_at_begin /= simulated_time )  THEN
115       io = 15   !  header output on file RUN_CONTROL
116    ELSE
117       io = 19   !  header output on file HEADER
118    ENDIF
119    CALL check_open( io )
120
121!
122!-- At the end of the run, output file (HEADER) will be rewritten with
123!-- new informations
124    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
125
126!
127!-- Determine kind of model run
128    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
129       run_classification = '3D - restart run'
130    ELSEIF ( TRIM( initializing_actions ) == 'read_data_for_recycling' )  THEN
131       run_classification = '3D - run using 3D - prerun data'
132    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
133       run_classification = '3D - run without 1D - prerun'
134    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
135       run_classification = '3D - run with 1D - prerun'
136    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
137       run_classification = '3D - run initialized by user'
138    ELSE
139       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
140       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
141    ENDIF
142    IF ( ocean )  THEN
143       run_classification = 'ocean - ' // run_classification
144    ELSE
145       run_classification = 'atmosphere - ' // run_classification
146    ENDIF
147
148!
149!-- Run-identification, date, time, host
150    host_chr = host(1:10)
151    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
152    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
153    IF ( coupling_mode /= 'uncoupled' )  WRITE ( io, 101 )  coupling_mode
154    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
155                       ADJUSTR( host_chr )
156#if defined( __parallel )
157    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
158       char1 = 'calculated'
159    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
160               host(1:2) == 'lc' )  .AND.                          &
161             npex == -1  .AND.  pdims(2) == 1 )  THEN
162       char1 = 'forced'
163    ELSE
164       char1 = 'predefined'
165    ENDIF
166    IF ( threads_per_task == 1 )  THEN
167       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
168    ELSE
169       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
170                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
171    ENDIF
172    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
173           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
174         npex == -1  .AND.  pdims(2) == 1 )                      &
175    THEN
176       WRITE ( io, 106 )
177    ELSEIF ( pdims(2) == 1 )  THEN
178       WRITE ( io, 107 )  'x'
179    ELSEIF ( pdims(1) == 1 )  THEN
180       WRITE ( io, 107 )  'y'
181    ENDIF
182    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
183#endif
184    WRITE ( io, 99 )
185
186!
187!-- Numerical schemes
188    WRITE ( io, 110 )
189    IF ( psolver(1:7) == 'poisfft' )  THEN
190       WRITE ( io, 111 )  TRIM( fft_method )
191       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
192    ELSEIF ( psolver == 'sor' )  THEN
193       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
194    ELSEIF ( psolver == 'multigrid' )  THEN
195       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
196       IF ( mg_cycles == -1 )  THEN
197          WRITE ( io, 140 )  residual_limit
198       ELSE
199          WRITE ( io, 141 )  mg_cycles
200       ENDIF
201       IF ( mg_switch_to_pe0_level == 0 )  THEN
202          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
203                             nzt_mg(1)
204       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
205          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
206                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
207                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
208                             nzt_mg(mg_switch_to_pe0_level),    &
209                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
210                             nzt_mg(1)
211       ENDIF
212    ENDIF
213    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
214    THEN
215       WRITE ( io, 142 )
216    ENDIF
217
218    IF ( momentum_advec == 'pw-scheme' )  THEN
219       WRITE ( io, 113 )
220    ELSE
221       WRITE ( io, 114 )
222       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
223       IF ( overshoot_limit_u /= 0.0  .OR.  overshoot_limit_v /= 0.0  .OR. &
224            overshoot_limit_w /= 0.0 )  THEN
225          WRITE ( io, 127 )  overshoot_limit_u, overshoot_limit_v, &
226                             overshoot_limit_w
227       ENDIF
228       IF ( ups_limit_u /= 0.0  .OR.  ups_limit_v /= 0.0  .OR. &
229            ups_limit_w /= 0.0 )                               &
230       THEN
231          WRITE ( io, 125 )  ups_limit_u, ups_limit_v, ups_limit_w
232       ENDIF
233       IF ( long_filter_factor /= 0.0 )  WRITE ( io, 115 )  long_filter_factor
234    ENDIF
235    IF ( scalar_advec == 'pw-scheme' )  THEN
236       WRITE ( io, 116 )
237    ELSEIF ( scalar_advec == 'ups-scheme' )  THEN
238       WRITE ( io, 117 )
239       IF ( cut_spline_overshoot )  WRITE ( io, 124 )
240       IF ( overshoot_limit_e /= 0.0  .OR.  overshoot_limit_pt /= 0.0 )  THEN
241          WRITE ( io, 128 )  overshoot_limit_e, overshoot_limit_pt
242       ENDIF
243       IF ( ups_limit_e /= 0.0  .OR.  ups_limit_pt /= 0.0 )  THEN
244          WRITE ( io, 126 )  ups_limit_e, ups_limit_pt
245       ENDIF
246    ELSE
247       WRITE ( io, 118 )
248    ENDIF
249
250    WRITE ( io, 139 )  TRIM( loop_optimization )
251
252    IF ( galilei_transformation )  THEN
253       IF ( use_ug_for_galilei_tr )  THEN
254          char1 = 'geostrophic wind'
255       ELSE
256          char1 = 'mean wind in model domain'
257       ENDIF
258       IF ( simulated_time_at_begin == simulated_time )  THEN
259          char2 = 'at the start of the run'
260       ELSE
261          char2 = 'at the end of the run'
262       ENDIF
263       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
264                          advected_distance_x/1000.0, advected_distance_y/1000.0
265    ENDIF
266    IF ( timestep_scheme == 'leapfrog' )  THEN
267       WRITE ( io, 120 )
268    ELSEIF ( timestep_scheme == 'leapfrog+euler' )  THEN
269       WRITE ( io, 121 )
270    ELSE
271       WRITE ( io, 122 )  timestep_scheme
272    ENDIF
273    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
274    IF ( rayleigh_damping_factor /= 0.0 )  THEN
275       IF ( .NOT. ocean )  THEN
276          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
277               rayleigh_damping_factor
278       ELSE
279          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
280               rayleigh_damping_factor
281       ENDIF
282    ENDIF
283    IF ( humidity )  THEN
284       IF ( .NOT. cloud_physics )  THEN
285          WRITE ( io, 129 )
286       ELSE
287          WRITE ( io, 130 )
288          WRITE ( io, 131 )
289          IF ( radiation )      WRITE ( io, 132 )
290          IF ( precipitation )  WRITE ( io, 133 )
291       ENDIF
292    ENDIF
293    IF ( passive_scalar )  WRITE ( io, 134 )
294    IF ( conserve_volume_flow )  THEN
295       WRITE ( io, 150 )  conserve_volume_flow_mode
296       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
297          WRITE ( io, 151 )  u_bulk, v_bulk
298       ENDIF
299    ELSEIF ( dp_external )  THEN
300       IF ( dp_smooth )  THEN
301          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
302       ELSE
303          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
304       ENDIF
305    ENDIF
306    WRITE ( io, 99 )
307
308!
309!-- Runtime and timestep informations
310    WRITE ( io, 200 )
311    IF ( .NOT. dt_fixed )  THEN
312       WRITE ( io, 201 )  dt_max, cfl_factor
313    ELSE
314       WRITE ( io, 202 )  dt
315    ENDIF
316    WRITE ( io, 203 )  simulated_time_at_begin, end_time
317
318    IF ( time_restart /= 9999999.9  .AND. &
319         simulated_time_at_begin == simulated_time )  THEN
320       IF ( dt_restart == 9999999.9 )  THEN
321          WRITE ( io, 204 )  ' Restart at:       ',time_restart
322       ELSE
323          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
324       ENDIF
325    ENDIF
326
327    IF ( simulated_time_at_begin /= simulated_time )  THEN
328       i = MAX ( log_point_s(10)%counts, 1 )
329       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
330          cpuseconds_per_simulated_second = 0.0
331       ELSE
332          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
333                                            ( simulated_time -    &
334                                              simulated_time_at_begin )
335       ENDIF
336       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
337                          log_point_s(10)%sum / REAL( i ),     &
338                          cpuseconds_per_simulated_second
339       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
340          IF ( dt_restart == 9999999.9 )  THEN
341             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
342          ELSE
343             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
344          ENDIF
345       ENDIF
346    ENDIF
347
348!
349!-- Computational grid
350    IF ( .NOT. ocean )  THEN
351       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
352       IF ( dz_stretch_level_index < nzt+1 )  THEN
353          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
354                             dz_stretch_factor, dz_max
355       ENDIF
356    ELSE
357       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
358       IF ( dz_stretch_level_index > 0 )  THEN
359          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
360                             dz_stretch_factor, dz_max
361       ENDIF
362    ENDIF
363    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
364                       MIN( nnz+2, nzt+2 )
365    IF ( numprocs > 1 )  THEN
366       IF ( nxa == nx  .AND.  nya == ny  .AND.  nza == nz )  THEN
367          WRITE ( io, 255 )
368       ELSE
369          WRITE ( io, 256 )  nnx-(nxa-nx), nny-(nya-ny), nzt+2
370       ENDIF
371    ENDIF
372    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
373
374!
375!-- Topography
376    WRITE ( io, 270 )  topography
377    SELECT CASE ( TRIM( topography ) )
378
379       CASE ( 'flat' )
380          ! no actions necessary
381
382       CASE ( 'single_building' )
383          blx = INT( building_length_x / dx )
384          bly = INT( building_length_y / dy )
385          bh  = INT( building_height / dz )
386
387          IF ( building_wall_left == 9999999.9 )  THEN
388             building_wall_left = ( nx + 1 - blx ) / 2 * dx
389          ENDIF
390          bxl = INT ( building_wall_left / dx + 0.5 )
391          bxr = bxl + blx
392
393          IF ( building_wall_south == 9999999.9 )  THEN
394             building_wall_south = ( ny + 1 - bly ) / 2 * dy
395          ENDIF
396          bys = INT ( building_wall_south / dy + 0.5 )
397          byn = bys + bly
398
399          WRITE ( io, 271 )  building_length_x, building_length_y, &
400                             building_height, bxl, bxr, bys, byn
401
402       CASE ( 'single_street_canyon' )
403          ch  = NINT( canyon_height / dz )
404          IF ( canyon_width_x /= 9999999.9 )  THEN
405!
406!--          Street canyon in y direction
407             cwx = NINT( canyon_width_x / dx )
408             IF ( canyon_wall_left == 9999999.9 )  THEN
409                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
410             ENDIF
411             cxl = NINT( canyon_wall_left / dx )
412             cxr = cxl + cwx
413             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
414
415          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
416!
417!--          Street canyon in x direction
418             cwy = NINT( canyon_width_y / dy )
419             IF ( canyon_wall_south == 9999999.9 )  THEN
420                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
421             ENDIF
422             cys = NINT( canyon_wall_south / dy )
423             cyn = cys + cwy
424             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
425          ENDIF
426
427    END SELECT
428
429    IF ( TRIM( topography ) /= 'flat' )  THEN
430       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
431          IF ( TRIM( topography ) == 'single_building' .OR.  &
432               TRIM( topography ) == 'single_street_canyon' )  THEN
433             WRITE ( io, 278 )
434          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
435             WRITE ( io, 279 )
436          ENDIF
437       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
438          WRITE ( io, 278 )
439       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
440          WRITE ( io, 279 )
441       ENDIF
442    ENDIF
443
444    IF ( plant_canopy ) THEN
445
446       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
447       IF ( passive_scalar ) THEN
448          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
449                            leaf_surface_concentration
450       ENDIF
451
452!
453!--    Heat flux at the top of vegetation
454       WRITE ( io, 282 ) cthf
455
456!
457!--    Leaf area density profile
458!--    Building output strings, starting with surface value
459       WRITE ( learde, '(F6.2)' )  lad_surface
460       gradients = '------'
461       slices = '     0'
462       coordinates = '   0.0'
463       i = 1
464       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
465
466          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
467          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
468
469          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
470          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
471
472          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
473          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
474
475          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
476          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
477
478          i = i + 1
479       ENDDO
480
481       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
482                          TRIM( gradients ), TRIM( slices )
483
484    ENDIF
485
486!
487!-- Boundary conditions
488    IF ( ibc_p_b == 0 )  THEN
489       runten = 'p(0)     = 0      |'
490    ELSEIF ( ibc_p_b == 1 )  THEN
491       runten = 'p(0)     = p(1)   |'
492    ELSE
493       runten = 'p(0)     = p(1) +R|'
494    ENDIF
495    IF ( ibc_p_t == 0 )  THEN
496       roben  = 'p(nzt+1) = 0      |'
497    ELSE
498       roben  = 'p(nzt+1) = p(nzt) |'
499    ENDIF
500
501    IF ( ibc_uv_b == 0 )  THEN
502       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
503    ELSE
504       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
505    ENDIF
506    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
507       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
508    ELSEIF ( ibc_uv_t == 0 )  THEN
509       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
510    ELSE
511       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
512    ENDIF
513
514    IF ( ibc_pt_b == 0 )  THEN
515       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
516    ELSEIF ( ibc_pt_b == 1 )  THEN
517       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
518    ELSEIF ( ibc_pt_b == 2 )  THEN
519       runten = TRIM( runten ) // ' pt(0) = from coupled model'
520    ENDIF
521    IF ( ibc_pt_t == 0 )  THEN
522       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
523    ELSEIF( ibc_pt_t == 1 )  THEN
524       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
525    ELSEIF( ibc_pt_t == 2 )  THEN
526       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
527    ENDIF
528
529    WRITE ( io, 300 )  runten, roben
530
531    IF ( .NOT. constant_diffusion )  THEN
532       IF ( ibc_e_b == 1 )  THEN
533          runten = 'e(0)     = e(1)'
534       ELSE
535          runten = 'e(0)     = e(1) = (u*/0.1)**2'
536       ENDIF
537       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
538
539       WRITE ( io, 301 )  'e', runten, roben       
540
541    ENDIF
542
543    IF ( ocean )  THEN
544       runten = 'sa(0)    = sa(1)'
545       IF ( ibc_sa_t == 0 )  THEN
546          roben =  'sa(nzt+1) = sa_surface'
547       ELSE
548          roben =  'sa(nzt+1) = sa(nzt)'
549       ENDIF
550       WRITE ( io, 301 ) 'sa', runten, roben
551    ENDIF
552
553    IF ( humidity )  THEN
554       IF ( ibc_q_b == 0 )  THEN
555          runten = 'q(0)     = q_surface'
556       ELSE
557          runten = 'q(0)     = q(1)'
558       ENDIF
559       IF ( ibc_q_t == 0 )  THEN
560          roben =  'q(nzt)   = q_top'
561       ELSE
562          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
563       ENDIF
564       WRITE ( io, 301 ) 'q', runten, roben
565    ENDIF
566
567    IF ( passive_scalar )  THEN
568       IF ( ibc_q_b == 0 )  THEN
569          runten = 's(0)     = s_surface'
570       ELSE
571          runten = 's(0)     = s(1)'
572       ENDIF
573       IF ( ibc_q_t == 0 )  THEN
574          roben =  's(nzt)   = s_top'
575       ELSE
576          roben =  's(nzt)   = s(nzt-1) + ds/dz'
577       ENDIF
578       WRITE ( io, 301 ) 's', runten, roben
579    ENDIF
580
581    IF ( use_surface_fluxes )  THEN
582       WRITE ( io, 303 )
583       IF ( constant_heatflux )  THEN
584          WRITE ( io, 306 )  surface_heatflux
585          IF ( random_heatflux )  WRITE ( io, 307 )
586       ENDIF
587       IF ( humidity  .AND.  constant_waterflux )  THEN
588          WRITE ( io, 311 ) surface_waterflux
589       ENDIF
590       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
591          WRITE ( io, 313 ) surface_waterflux
592       ENDIF
593    ENDIF
594
595    IF ( use_top_fluxes )  THEN
596       WRITE ( io, 304 )
597       IF ( coupling_mode == 'uncoupled' )  THEN
598          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
599          IF ( constant_top_heatflux )  THEN
600             WRITE ( io, 306 )  top_heatflux
601          ENDIF
602       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
603          WRITE ( io, 316 )
604       ENDIF
605       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
606          WRITE ( io, 309 )  top_salinityflux
607       ENDIF
608       IF ( humidity  .OR.  passive_scalar )  THEN
609          WRITE ( io, 315 )
610       ENDIF
611    ENDIF
612
613    IF ( prandtl_layer )  THEN
614       WRITE ( io, 305 )  0.5 * (zu(1)-zu(0)), roughness_length, kappa, &
615                          rif_min, rif_max
616       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
617       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
618          WRITE ( io, 312 )
619       ENDIF
620       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
621          WRITE ( io, 314 )
622       ENDIF
623    ELSE
624       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
625          WRITE ( io, 310 )  rif_min, rif_max
626       ENDIF
627    ENDIF
628
629    WRITE ( io, 317 )  bc_lr, bc_ns
630    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
631       WRITE ( io, 318 )  outflow_damping_width, km_damp_max
632       IF ( turbulent_inflow )  THEN
633          WRITE ( io, 319 )  recycling_width, recycling_plane, &
634                             inflow_damping_height, inflow_damping_width
635       ENDIF
636    ENDIF
637
638!
639!-- Listing of 1D-profiles
640    WRITE ( io, 325 )  dt_dopr_listing
641    IF ( averaging_interval_pr /= 0.0 )  THEN
642       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
643    ENDIF
644
645!
646!-- DATA output
647    WRITE ( io, 330 )
648    IF ( averaging_interval_pr /= 0.0 )  THEN
649       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
650    ENDIF
651
652!
653!-- 1D-profiles
654    dopr_chr = 'Pofile:'
655    IF ( dopr_n /= 0 )  THEN
656       WRITE ( io, 331 )
657
658       output_format = ''
659       IF ( netcdf_output )  THEN
660          IF ( netcdf_64bit )  THEN
661             output_format = 'netcdf (64 bit offset)'
662          ELSE
663             output_format = 'netcdf'
664          ENDIF
665       ENDIF
666       IF ( profil_output )  THEN
667          IF ( netcdf_output )  THEN
668             output_format = TRIM( output_format ) // ' and profil'
669          ELSE
670             output_format = 'profil'
671          ENDIF
672       ENDIF
673       WRITE ( io, 345 )  output_format
674
675       DO  i = 1, dopr_n
676          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
677          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
678             WRITE ( io, 332 )  dopr_chr
679             dopr_chr = '       :'
680          ENDIF
681       ENDDO
682
683       IF ( dopr_chr /= '' )  THEN
684          WRITE ( io, 332 )  dopr_chr
685       ENDIF
686       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
687       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
688    ENDIF
689
690!
691!-- 2D-arrays
692    DO  av = 0, 1
693
694       i = 1
695       do2d_xy = ''
696       do2d_xz = ''
697       do2d_yz = ''
698       DO  WHILE ( do2d(av,i) /= ' ' )
699
700          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
701          do2d_mode = do2d(av,i)(l-1:l)
702
703          SELECT CASE ( do2d_mode )
704             CASE ( 'xy' )
705                ll = LEN_TRIM( do2d_xy )
706                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
707             CASE ( 'xz' )
708                ll = LEN_TRIM( do2d_xz )
709                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
710             CASE ( 'yz' )
711                ll = LEN_TRIM( do2d_yz )
712                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
713          END SELECT
714
715          i = i + 1
716
717       ENDDO
718
719       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
720              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
721              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
722            ( netcdf_output  .OR.  iso2d_output ) )  THEN
723
724          IF (  av == 0 )  THEN
725             WRITE ( io, 334 )  ''
726          ELSE
727             WRITE ( io, 334 )  '(time-averaged)'
728          ENDIF
729
730          IF ( do2d_at_begin )  THEN
731             begin_chr = 'and at the start'
732          ELSE
733             begin_chr = ''
734          ENDIF
735
736          output_format = ''
737          IF ( netcdf_output )  THEN
738             IF ( netcdf_64bit )  THEN
739                output_format = 'netcdf (64 bit offset)'
740             ELSE
741                output_format = 'netcdf'
742             ENDIF
743          ENDIF
744          IF ( iso2d_output )  THEN
745             IF ( netcdf_output )  THEN
746                output_format = TRIM( output_format ) // ' and iso2d'
747             ELSE
748                output_format = 'iso2d'
749             ENDIF
750          ENDIF
751          WRITE ( io, 345 )  output_format
752
753          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
754             i = 1
755             slices = '/'
756             coordinates = '/'
757!
758!--          Building strings with index and coordinate informations of the
759!--          slices
760             DO  WHILE ( section(i,1) /= -9999 )
761
762                WRITE (section_chr,'(I5)')  section(i,1)
763                section_chr = ADJUSTL( section_chr )
764                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
765
766                IF ( section(i,1) == -1 )  THEN
767                   WRITE (coor_chr,'(F10.1)')  -1.0
768                ELSE
769                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
770                ENDIF
771                coor_chr = ADJUSTL( coor_chr )
772                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
773
774                i = i + 1
775             ENDDO
776             IF ( av == 0 )  THEN
777                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
778                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
779                                   TRIM( coordinates )
780                IF ( skip_time_do2d_xy /= 0.0 )  THEN
781                   WRITE ( io, 339 )  skip_time_do2d_xy
782                ENDIF
783             ELSE
784                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
785                                   TRIM( begin_chr ), averaging_interval, &
786                                   dt_averaging_input, 'k', TRIM( slices ), &
787                                   TRIM( coordinates )
788                IF ( skip_time_data_output_av /= 0.0 )  THEN
789                   WRITE ( io, 339 )  skip_time_data_output_av
790                ENDIF
791             ENDIF
792
793          ENDIF
794
795          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
796             i = 1
797             slices = '/'
798             coordinates = '/'
799!
800!--          Building strings with index and coordinate informations of the
801!--          slices
802             DO  WHILE ( section(i,2) /= -9999 )
803
804                WRITE (section_chr,'(I5)')  section(i,2)
805                section_chr = ADJUSTL( section_chr )
806                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
807
808                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
809                coor_chr = ADJUSTL( coor_chr )
810                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
811
812                i = i + 1
813             ENDDO
814             IF ( av == 0 )  THEN
815                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
816                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
817                                   TRIM( coordinates )
818                IF ( skip_time_do2d_xz /= 0.0 )  THEN
819                   WRITE ( io, 339 )  skip_time_do2d_xz
820                ENDIF
821             ELSE
822                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
823                                   TRIM( begin_chr ), averaging_interval, &
824                                   dt_averaging_input, 'j', TRIM( slices ), &
825                                   TRIM( coordinates )
826                IF ( skip_time_data_output_av /= 0.0 )  THEN
827                   WRITE ( io, 339 )  skip_time_data_output_av
828                ENDIF
829             ENDIF
830          ENDIF
831
832          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
833             i = 1
834             slices = '/'
835             coordinates = '/'
836!
837!--          Building strings with index and coordinate informations of the
838!--          slices
839             DO  WHILE ( section(i,3) /= -9999 )
840
841                WRITE (section_chr,'(I5)')  section(i,3)
842                section_chr = ADJUSTL( section_chr )
843                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
844
845                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
846                coor_chr = ADJUSTL( coor_chr )
847                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
848
849                i = i + 1
850             ENDDO
851             IF ( av == 0 )  THEN
852                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
853                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
854                                   TRIM( coordinates )
855                IF ( skip_time_do2d_yz /= 0.0 )  THEN
856                   WRITE ( io, 339 )  skip_time_do2d_yz
857                ENDIF
858             ELSE
859                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
860                                   TRIM( begin_chr ), averaging_interval, &
861                                   dt_averaging_input, 'i', TRIM( slices ), &
862                                   TRIM( coordinates )
863                IF ( skip_time_data_output_av /= 0.0 )  THEN
864                   WRITE ( io, 339 )  skip_time_data_output_av
865                ENDIF
866             ENDIF
867          ENDIF
868
869       ENDIF
870
871    ENDDO
872
873!
874!-- 3d-arrays
875    DO  av = 0, 1
876
877       i = 1
878       do3d_chr = ''
879       DO  WHILE ( do3d(av,i) /= ' ' )
880
881          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
882          i = i + 1
883
884       ENDDO
885
886       IF ( do3d_chr /= '' )  THEN
887          IF ( av == 0 )  THEN
888             WRITE ( io, 336 )  ''
889          ELSE
890             WRITE ( io, 336 )  '(time-averaged)'
891          ENDIF
892
893          output_format = ''
894          IF ( netcdf_output )  THEN
895             IF ( netcdf_64bit .AND. netcdf_64bit_3d )  THEN
896                output_format = 'netcdf (64 bit offset)'
897             ELSE
898                output_format = 'netcdf'
899             ENDIF
900          ENDIF
901          IF ( avs_output )  THEN
902             IF ( netcdf_output )  THEN
903                output_format = TRIM( output_format ) // ' and avs'
904             ELSE
905                output_format = 'avs'
906             ENDIF
907          ENDIF
908          WRITE ( io, 345 )  output_format
909
910          IF ( do3d_at_begin )  THEN
911             begin_chr = 'and at the start'
912          ELSE
913             begin_chr = ''
914          ENDIF
915          IF ( av == 0 )  THEN
916             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
917                                zu(nz_do3d), nz_do3d
918          ELSE
919             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
920                                TRIM( begin_chr ), averaging_interval, &
921                                dt_averaging_input, zu(nz_do3d), nz_do3d
922          ENDIF
923
924          IF ( do3d_compress )  THEN
925             do3d_chr = ''
926             i = 1
927             DO WHILE ( do3d(av,i) /= ' ' )
928
929                SELECT CASE ( do3d(av,i) )
930                   CASE ( 'u' )
931                      j = 1
932                   CASE ( 'v' )
933                      j = 2
934                   CASE ( 'w' )
935                      j = 3
936                   CASE ( 'p' )
937                      j = 4
938                   CASE ( 'pt' )
939                      j = 5
940                END SELECT
941                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
942                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
943                           ':' // prec // ','
944                i = i + 1
945
946             ENDDO
947             WRITE ( io, 338 )  do3d_chr
948
949          ENDIF
950
951          IF ( av == 0 )  THEN
952             IF ( skip_time_do3d /= 0.0 )  THEN
953                WRITE ( io, 339 )  skip_time_do3d
954             ENDIF
955          ELSE
956             IF ( skip_time_data_output_av /= 0.0 )  THEN
957                WRITE ( io, 339 )  skip_time_data_output_av
958             ENDIF
959          ENDIF
960
961       ENDIF
962
963    ENDDO
964
965!
966!-- Timeseries
967    IF ( dt_dots /= 9999999.9 )  THEN
968       WRITE ( io, 340 )
969
970       output_format = ''
971       IF ( netcdf_output )  THEN
972          IF ( netcdf_64bit )  THEN
973             output_format = 'netcdf (64 bit offset)'
974          ELSE
975             output_format = 'netcdf'
976          ENDIF
977       ENDIF
978       IF ( profil_output )  THEN
979          IF ( netcdf_output )  THEN
980             output_format = TRIM( output_format ) // ' and profil'
981          ELSE
982             output_format = 'profil'
983          ENDIF
984       ENDIF
985       WRITE ( io, 345 )  output_format
986       WRITE ( io, 341 )  dt_dots
987    ENDIF
988
989#if defined( __dvrp_graphics )
990!
991!-- Dvrp-output
992    IF ( dt_dvrp /= 9999999.9 )  THEN
993       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
994                          TRIM( dvrp_username ), TRIM( dvrp_directory )
995       i = 1
996       l = 0
997       DO WHILE ( mode_dvrp(i) /= ' ' )
998          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
999             READ ( mode_dvrp(i), '(10X,I2)' )  j
1000             l = l + 1
1001             IF ( do3d(0,j) /= ' ' )  THEN
1002                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l)
1003             ENDIF
1004          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1005             READ ( mode_dvrp(i), '(6X,I2)' )  j
1006             IF ( do2d(0,j) /= ' ' )  WRITE ( io, 362 )  TRIM( do2d(0,j) )
1007          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1008             WRITE ( io, 363 )
1009          ENDIF
1010          i = i + 1
1011       ENDDO
1012
1013       IF ( TRIM( topography ) /= 'flat'  .AND.  cluster_size > 1 )  THEN
1014          WRITE ( io, 364 )  cluster_size
1015       ENDIF
1016
1017    ENDIF
1018#endif
1019
1020#if defined( __spectra )
1021!
1022!-- Spectra output
1023    IF ( dt_dosp /= 9999999.9 ) THEN
1024       WRITE ( io, 370 )
1025
1026       output_format = ''
1027       IF ( netcdf_output )  THEN
1028          IF ( netcdf_64bit )  THEN
1029             output_format = 'netcdf (64 bit offset)'
1030          ELSE
1031             output_format = 'netcdf'
1032          ENDIF
1033       ENDIF
1034       IF ( profil_output )  THEN
1035          IF ( netcdf_output )  THEN
1036             output_format = TRIM( output_format ) // ' and profil'
1037          ELSE
1038             output_format = 'profil'
1039          ENDIF
1040       ENDIF
1041       WRITE ( io, 345 )  output_format
1042       WRITE ( io, 371 )  dt_dosp
1043       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1044       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1045                          ( spectra_direction(i), i = 1,10 ),  &
1046                          ( comp_spectra_level(i), i = 1,100 ), &
1047                          ( plot_spectra_level(i), i = 1,100 ), &
1048                          averaging_interval_sp, dt_averaging_input_pr
1049    ENDIF
1050#endif
1051
1052    WRITE ( io, 99 )
1053
1054!
1055!-- Physical quantities
1056    WRITE ( io, 400 )
1057
1058!
1059!-- Geostrophic parameters
1060    WRITE ( io, 410 )  omega, phi, f, fs
1061
1062!
1063!-- Other quantities
1064    WRITE ( io, 411 )  g
1065    IF ( use_reference )  THEN
1066       IF ( ocean )  THEN
1067          WRITE ( io, 412 )  prho_reference
1068       ELSE
1069          WRITE ( io, 413 )  pt_reference
1070       ENDIF
1071    ENDIF
1072
1073!
1074!-- Cloud physics parameters
1075    IF ( cloud_physics ) THEN
1076       WRITE ( io, 415 )
1077       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1078    ENDIF
1079
1080!-- Profile of the geostrophic wind (component ug)
1081!-- Building output strings
1082    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1083    gradients = '------'
1084    slices = '     0'
1085    coordinates = '   0.0'
1086    i = 1
1087    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1088     
1089       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1090       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1091
1092       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1093       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1094
1095       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1096       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1097
1098       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1099       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1100
1101       i = i + 1
1102    ENDDO
1103
1104    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1105                       TRIM( gradients ), TRIM( slices )
1106
1107!-- Profile of the geostrophic wind (component vg)
1108!-- Building output strings
1109    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1110    gradients = '------'
1111    slices = '     0'
1112    coordinates = '   0.0'
1113    i = 1
1114    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1115
1116       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1117       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1118
1119       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1120       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1121
1122       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1123       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1124
1125       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1126       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1127
1128       i = i + 1 
1129    ENDDO
1130
1131    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1132                       TRIM( gradients ), TRIM( slices )
1133
1134!
1135!-- Initial temperature profile
1136!-- Building output strings, starting with surface temperature
1137    WRITE ( temperatures, '(F6.2)' )  pt_surface
1138    gradients = '------'
1139    slices = '     0'
1140    coordinates = '   0.0'
1141    i = 1
1142    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1143
1144       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1145       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1146
1147       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1148       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1149
1150       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1151       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1152
1153       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1154       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1155
1156       i = i + 1
1157    ENDDO
1158
1159    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1160                       TRIM( gradients ), TRIM( slices )
1161
1162!
1163!-- Initial humidity profile
1164!-- Building output strings, starting with surface humidity
1165    IF ( humidity  .OR.  passive_scalar )  THEN
1166       WRITE ( temperatures, '(E8.1)' )  q_surface
1167       gradients = '--------'
1168       slices = '       0'
1169       coordinates = '     0.0'
1170       i = 1
1171       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1172         
1173          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1174          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1175
1176          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1177          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1178         
1179          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1180          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1181         
1182          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1183          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1184
1185          i = i + 1
1186       ENDDO
1187
1188       IF ( humidity )  THEN
1189          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1190                             TRIM( gradients ), TRIM( slices )
1191       ELSE
1192          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1193                             TRIM( gradients ), TRIM( slices )
1194       ENDIF
1195    ENDIF
1196
1197!
1198!-- Initial salinity profile
1199!-- Building output strings, starting with surface salinity
1200    IF ( ocean )  THEN
1201       WRITE ( temperatures, '(F6.2)' )  sa_surface
1202       gradients = '------'
1203       slices = '     0'
1204       coordinates = '   0.0'
1205       i = 1
1206       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1207
1208          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1209          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1210
1211          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1212          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1213
1214          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1215          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1216
1217          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1218          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1219
1220          i = i + 1
1221       ENDDO
1222
1223       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1224                          TRIM( gradients ), TRIM( slices )
1225    ENDIF
1226
1227!
1228!-- LES / turbulence parameters
1229    WRITE ( io, 450 )
1230
1231!--
1232! ... LES-constants used must still be added here
1233!--
1234    IF ( constant_diffusion )  THEN
1235       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1236                          prandtl_number
1237    ENDIF
1238    IF ( .NOT. constant_diffusion)  THEN
1239       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1240       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1241       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1242       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1243    ENDIF
1244
1245!
1246!-- Special actions during the run
1247    WRITE ( io, 470 )
1248    IF ( create_disturbances )  THEN
1249       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1250                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1251                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1252       IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
1253          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1254       ELSE
1255          WRITE ( io, 473 )  disturbance_energy_limit
1256       ENDIF
1257       WRITE ( io, 474 )  TRIM( random_generator )
1258    ENDIF
1259    IF ( pt_surface_initial_change /= 0.0 )  THEN
1260       WRITE ( io, 475 )  pt_surface_initial_change
1261    ENDIF
1262    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1263       WRITE ( io, 476 )  q_surface_initial_change       
1264    ENDIF
1265    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1266       WRITE ( io, 477 )  q_surface_initial_change       
1267    ENDIF
1268
1269    IF ( particle_advection )  THEN
1270!
1271!--    Particle attributes
1272       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1273                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1274                          end_time_prel, dt_sort_particles
1275       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1276       IF ( random_start_position )  WRITE ( io, 481 )
1277       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1278       WRITE ( io, 495 )  total_number_of_particles
1279       IF ( .NOT. vertical_particle_advection )  WRITE ( io, 482 )
1280       IF ( maximum_number_of_tailpoints /= 0 )  THEN
1281          WRITE ( io, 483 )  maximum_number_of_tailpoints
1282          IF ( minimum_tailpoint_distance /= 0 )  THEN
1283             WRITE ( io, 484 )  total_number_of_tails,      &
1284                                minimum_tailpoint_distance, &
1285                                maximum_tailpoint_age
1286          ENDIF
1287       ENDIF
1288       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1289          WRITE ( io, 485 )  dt_write_particle_data
1290          output_format = ''
1291          IF ( netcdf_output )  THEN
1292             IF ( netcdf_64bit )  THEN
1293                output_format = 'netcdf (64 bit offset) and binary'
1294             ELSE
1295                output_format = 'netcdf and binary'
1296             ENDIF
1297          ELSE
1298             output_format = 'binary'
1299          ENDIF
1300          WRITE ( io, 345 )  output_format
1301       ENDIF
1302       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1303       IF ( write_particle_statistics )  WRITE ( io, 486 )
1304
1305       WRITE ( io, 487 )  number_of_particle_groups
1306
1307       DO  i = 1, number_of_particle_groups
1308          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1309             WRITE ( io, 490 )  i, 0.0
1310             WRITE ( io, 492 )
1311          ELSE
1312             WRITE ( io, 490 )  i, radius(i)
1313             IF ( density_ratio(i) /= 0.0 )  THEN
1314                WRITE ( io, 491 )  density_ratio(i)
1315             ELSE
1316                WRITE ( io, 492 )
1317             ENDIF
1318          ENDIF
1319          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1320                             pdx(i), pdy(i), pdz(i)
1321       ENDDO
1322
1323    ENDIF
1324
1325
1326!
1327!-- Parameters of 1D-model
1328    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1329       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1330                          mixing_length_1d, dissipation_1d
1331       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1332          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1333       ENDIF
1334    ENDIF
1335
1336!
1337!-- User-defined informations
1338    CALL user_header( io )
1339
1340    WRITE ( io, 99 )
1341
1342!
1343!-- Write buffer contents to disc immediately
1344    CALL local_flush( io )
1345
1346!
1347!-- Here the FORMATs start
1348
1349 99 FORMAT (1X,78('-'))
1350100 FORMAT (/1X,'***************************',9X,42('-')/        &
1351            1X,'* ',A,' *',9X,A/                               &
1352            1X,'***************************',9X,42('-'))
1353101 FORMAT (37X,'coupled run: ',A/ &
1354            37X,42('-'))
1355102 FORMAT (/' Date:              ',A8,9X,'Run:       ',A20/      &
1356            ' Time:              ',A8,9X,'Run-No.:   ',I2.2/     &
1357            ' Run on host:     ',A10)
1358#if defined( __parallel )
1359103 FORMAT (' Number of PEs:',8X,I5,9X,'Processor grid (x,y): (',I3,',',I3, &
1360              ')',1X,A)
1361104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1362              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1363105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1364106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1365            37X,'because the job is running on an SMP-cluster')
1366107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1367#endif
1368110 FORMAT (/' Numerical Schemes:'/ &
1369             ' -----------------'/)
1370111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1371112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1372            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1373113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1374                  ' or Upstream')
1375114 FORMAT (' --> Momentum advection via Upstream-Spline-Scheme')
1376115 FORMAT ('     Tendencies are smoothed via Long-Filter with factor ',F5.3) 
1377116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1378                  ' or Upstream')
1379117 FORMAT (' --> Scalar advection via Upstream-Spline-Scheme')
1380118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1381119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1382            '     Translation velocity = ',A/ &
1383            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1384120 FORMAT (' --> Time differencing scheme: leapfrog only (no euler in case', &
1385                  ' of timestep changes)')
1386121 FORMAT (' --> Time differencing scheme: leapfrog + euler in case of', &
1387                  ' timestep changes')
1388122 FORMAT (' --> Time differencing scheme: ',A)
1389123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1390            '     maximum damping coefficient: ',F5.3, ' 1/s')
1391124 FORMAT ('     Spline-overshoots are being suppressed')
1392125 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1393                  ' of'/                                                       &
1394            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1395126 FORMAT ('     Upstream-Scheme is used if Upstream-differences fall short', &
1396                  ' of'/                                                       &
1397            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1398127 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1399            '     delta_u = ',F6.4,4X,'delta_v = ',F6.4,4X,'delta_w = ',F6.4)
1400128 FORMAT ('     The following absolute overshoot differences are tolerated:'/&
1401            '     delta_e = ',F6.4,4X,'delta_pt = ',F6.4)
1402129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1403130 FORMAT (' --> Additional prognostic equation for the total water content')
1404131 FORMAT (' --> Parameterization of condensation processes via (0%-or100%)')
1405132 FORMAT (' --> Parameterization of long-wave radiation processes via'/ &
1406            '     effective emissivity scheme')
1407133 FORMAT (' --> Precipitation parameterization via Kessler-Scheme')
1408134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1409135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1410                  A,'-cycle)'/ &
1411            '     number of grid levels:                   ',I2/ &
1412            '     Gauss-Seidel red/black iterations:       ',I2)
1413136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1414                  I3,')')
1415137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1416            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1417                  I3,')'/ &
1418            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1419                  I3,')')
1420138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1421139 FORMAT (' --> Loop optimization method: ',A)
1422140 FORMAT ('     maximum residual allowed:                ',E10.3)
1423141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1424142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1425                  'step')
1426143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1427                  'kinetic energy')
1428150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1429                  'conserved'/ &
1430            '     using the ',A,' mode')
1431151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1432152 FORMAT (' --> External pressure gradient directly prescribed by the user:'/, &
1433              2(1X,E12.5),'Pa/m', &
1434             ' in x/y direction starting from dp_level_b =', F6.3, 'm', &
1435             A /)
1436200 FORMAT (//' Run time and time step information:'/ &
1437             ' ----------------------------------'/)
1438201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1439             '    CFL-factor: ',F4.2)
1440202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1441203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1442             ' End time:         ',F9.3,' s')
1443204 FORMAT ( A,F9.3,' s')
1444205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1445206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1446             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1447               '  ',F9.3,' s'/                                                 &
1448             '                                   per second of simulated tim', &
1449               'e: ',F9.3,' s')
1450250 FORMAT (//' Computational grid and domain size:'/ &
1451              ' ----------------------------------'// &
1452              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1453              ' m    dz =    ',F7.3,' m'/ &
1454              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1455              ' m  z(u) = ',F10.3,' m'/)
1456252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1457              ' factor: ',F5.3/ &
1458            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1459254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1460            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1461255 FORMAT (' Subdomains have equal size')
1462256 FORMAT (' Subdomains at the upper edges of the virtual processor grid ', &
1463              'have smaller sizes'/                                          &
1464            ' Size of smallest subdomain:    (  ',I4,',   ',I4,',   ',I4,')')
1465260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1466             ' degrees')
1467270 FORMAT (//' Topography informations:'/ &
1468              ' -----------------------'// &
1469              1X,'Topography: ',A)
1470271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1471              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1472                ' / ',I4)
1473272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1474              ' direction' / &
1475              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1476              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1477278 FORMAT (' Topography grid definition convention:'/ &
1478            ' cell edge (staggered grid points'/  &
1479            ' (u in x-direction, v in y-direction))' /)
1480279 FORMAT (' Topography grid definition convention:'/ &
1481            ' cell center (scalar grid points)' /)
1482280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1483              ' ------------------------------'// &
1484              ' Canopy mode: ', A / &
1485              ' Canopy top: ',I4 / &
1486              ' Leaf drag coefficient: ',F6.2 /)
1487281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1488              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1489282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1490283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1491              ' Height:              ',A,'  m'/ &
1492              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1493              ' Gradient:            ',A,'  m**2/m**4'/ &
1494              ' Gridpoint:           ',A)
1495               
1496300 FORMAT (//' Boundary conditions:'/ &
1497             ' -------------------'// &
1498             '                     p                    uv             ', &
1499             '                   pt'// &
1500             ' B. bound.: ',A/ &
1501             ' T. bound.: ',A)
1502301 FORMAT (/'                     ',A// &
1503             ' B. bound.: ',A/ &
1504             ' T. bound.: ',A)
1505303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1506304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1507305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1508               'computational u,v-level:'// &
1509             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   kappa = ',F4.2/ &
1510             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1511306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1512307 FORMAT ('       Heatflux has a random normal distribution')
1513308 FORMAT ('       Predefined surface temperature')
1514309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1515310 FORMAT (//'    1D-Model:'// &
1516             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1517311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1518312 FORMAT ('       Predefined surface humidity')
1519313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1520314 FORMAT ('       Predefined scalar value at the surface')
1521315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1522316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1523                    'atmosphere model')
1524317 FORMAT (//' Lateral boundaries:'/ &
1525            '       left/right:  ',A/    &
1526            '       north/south: ',A)
1527318 FORMAT (/'       outflow damping layer width: ',I3,' gridpoints with km_', &
1528                    'max =',F5.1,' m**2/s')
1529319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1530            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1531            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1532320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1533            '                                          v: ',F9.6,' m**2/s**2')
1534325 FORMAT (//' List output:'/ &
1535             ' -----------'//  &
1536            '    1D-Profiles:'/    &
1537            '       Output every             ',F8.2,' s')
1538326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1539            '       Averaging input every    ',F8.2,' s')
1540330 FORMAT (//' Data output:'/ &
1541             ' -----------'/)
1542331 FORMAT (/'    1D-Profiles:')
1543332 FORMAT (/'       ',A)
1544333 FORMAT ('       Output every             ',F8.2,' s',/ &
1545            '       Time averaged over       ',F8.2,' s'/ &
1546            '       Averaging input every    ',F8.2,' s')
1547334 FORMAT (/'    2D-Arrays',A,':')
1548335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1549            '       Output every             ',F8.2,' s  ',A/ &
1550            '       Cross sections at ',A1,' = ',A/ &
1551            '       scalar-coordinates:   ',A,' m'/)
1552336 FORMAT (/'    3D-Arrays',A,':')
1553337 FORMAT (/'       Arrays: ',A/ &
1554            '       Output every             ',F8.2,' s  ',A/ &
1555            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1556338 FORMAT ('       Compressed data output'/ &
1557            '       Decimal precision: ',A/)
1558339 FORMAT ('       No output during initial ',F8.2,' s')
1559340 FORMAT (/'    Time series:')
1560341 FORMAT ('       Output every             ',F8.2,' s'/)
1561342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1562            '       Output every             ',F8.2,' s  ',A/ &
1563            '       Time averaged over       ',F8.2,' s'/ &
1564            '       Averaging input every    ',F8.2,' s'/ &
1565            '       Cross sections at ',A1,' = ',A/ &
1566            '       scalar-coordinates:   ',A,' m'/)
1567343 FORMAT (/'       Arrays: ',A/ &
1568            '       Output every             ',F8.2,' s  ',A/ &
1569            '       Time averaged over       ',F8.2,' s'/ &
1570            '       Averaging input every    ',F8.2,' s'/ &
1571            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1572345 FORMAT ('       Output format: ',A/)
1573#if defined( __dvrp_graphics )
1574360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1575            '       Output every      ',F7.1,' s'/ &
1576            '       Output mode:      ',A/ &
1577            '       Host / User:      ',A,' / ',A/ &
1578            '       Directory:        ',A// &
1579            '       The sequence contains:')
1580361 FORMAT ('       Isosurface of ',A,'  Threshold value: ', E12.3)
1581362 FORMAT ('       Sectional plane ',A)
1582363 FORMAT ('       Particles')
1583364 FORMAT (/'       Polygon reduction for topography: cluster_size = ', I1)
1584#endif
1585#if defined( __spectra )
1586370 FORMAT ('    Spectra:')
1587371 FORMAT ('       Output every ',F7.1,' s'/)
1588372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1589            '       Directions: ', 10(A5,',')/                         &
1590            '       height levels  k = ', 20(I3,',')/                  &
1591            '                          ', 20(I3,',')/                  &
1592            '                          ', 20(I3,',')/                  &
1593            '                          ', 20(I3,',')/                  &
1594            '                          ', 19(I3,','),I3,'.'/           &
1595            '       height levels selected for standard plot:'/        &
1596            '                      k = ', 20(I3,',')/                  &
1597            '                          ', 20(I3,',')/                  &
1598            '                          ', 20(I3,',')/                  &
1599            '                          ', 20(I3,',')/                  &
1600            '                          ', 19(I3,','),I3,'.'/           &
1601            '       Time averaged over ', F7.1, ' s,' /                &
1602            '       Profiles for the time averaging are taken every ', &
1603                    F6.1,' s')
1604#endif
1605400 FORMAT (//' Physical quantities:'/ &
1606              ' -------------------'/)
1607410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1608            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1609            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1610            '                            f*    = ',F9.6,' 1/s')
1611411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1612412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1613413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1614415 FORMAT (/'    Cloud physics parameters:'/ &
1615             '    ------------------------'/)
1616416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1617            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1618            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1619            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1620            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1621420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1622            '       Height:        ',A,'  m'/ &
1623            '       Temperature:   ',A,'  K'/ &
1624            '       Gradient:      ',A,'  K/100m'/ &
1625            '       Gridpoint:     ',A)
1626421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1627            '       Height:      ',A,'  m'/ &
1628            '       Humidity:    ',A,'  kg/kg'/ &
1629            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1630            '       Gridpoint:   ',A)
1631422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1632            '       Height:                  ',A,'  m'/ &
1633            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1634            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1635            '       Gridpoint:               ',A)
1636423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1637            '       Height:      ',A,'  m'/ &
1638            '       ug:          ',A,'  m/s'/ &
1639            '       Gradient:    ',A,'  1/100s'/ &
1640            '       Gridpoint:   ',A)
1641424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1642            '       Height:      ',A,'  m'/ &
1643            '       vg:          ',A,'  m/s'/ &
1644            '       Gradient:    ',A,'  1/100s'/ &
1645            '       Gridpoint:   ',A)
1646425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1647            '       Height:     ',A,'  m'/ &
1648            '       Salinity:   ',A,'  psu'/ &
1649            '       Gradient:   ',A,'  psu/100m'/ &
1650            '       Gridpoint:  ',A)
1651450 FORMAT (//' LES / Turbulence quantities:'/ &
1652              ' ---------------------------'/)
1653451 FORMAT ('   Diffusion coefficients are constant:'/ &
1654            '   Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1655452 FORMAT ('   Mixing length is limited to the Prandtl mixing lenth.')
1656453 FORMAT ('   Mixing length is limited to ',F4.2,' * z')
1657454 FORMAT ('   TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1658455 FORMAT ('   initial TKE is prescribed as ',E9.2,' (m/s)**2')
1659470 FORMAT (//' Actions during the simulation:'/ &
1660              ' -----------------------------'/)
1661471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1662            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1663            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1664            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1665472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1666                 ' to i/j =',I4)
1667473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1668                 1X,F5.3, ' m**2/s**2')
1669474 FORMAT ('    Random number generator used    : ',A/)
1670475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1671                 'respectively, if'/ &
1672            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1673                 ' 3D-simulation'/)
1674476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1675                 'respectively, if the'/ &
1676            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1677                 ' the 3D-simulation'/)
1678477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1679                 'respectively, if the'/ &
1680            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1681                 ' the 3D-simulation'/)
1682480 FORMAT ('    Particles:'/ &
1683            '    ---------'// &
1684            '       Particle advection is active (switched on at t = ', F7.1, &
1685                    ' s)'/ &
1686            '       Start of new particle generations every  ',F6.1,' s'/ &
1687            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
1688            '                            bottom:     ', A, ' top:         ', A/&
1689            '       Maximum particle age:                 ',F9.1,' s'/ &
1690            '       Advection stopped at t = ',F9.1,' s'/ &
1691            '       Particles are sorted every ',F9.1,' s'/)
1692481 FORMAT ('       Particles have random start positions'/)
1693482 FORMAT ('       Particles are advected only horizontally'/)
1694483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
1695484 FORMAT ('            Number of tails of the total domain: ',I10/ &
1696            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
1697            '            Maximum age of the end of the tail:  ',F8.2,' s')
1698485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
1699486 FORMAT ('       Particle statistics are written on file'/)
1700487 FORMAT ('       Number of particle groups: ',I2/)
1701488 FORMAT ('       SGS velocity components are used for particle advection'/ &
1702            '          minimum timestep for advection: ', F7.5/)
1703489 FORMAT ('       Number of particles simultaneously released at each ', &
1704                    'point: ', I5/)
1705490 FORMAT ('       Particle group ',I2,':'/ &
1706            '          Particle radius: ',E10.3, 'm')
1707491 FORMAT ('          Particle inertia is activated'/ &
1708            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
1709492 FORMAT ('          Particles are advected only passively (no inertia)'/)
1710493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
1711            '                                         y:',F8.1,' - ',F8.1,' m'/&
1712            '                                         z:',F8.1,' - ',F8.1,' m'/&
1713            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
1714                       ' m  dz = ',F8.1,' m'/)
1715494 FORMAT ('       Output of particle time series in NetCDF format every ', &
1716                    F8.2,' s'/)
1717495 FORMAT ('       Number of particles in total domain: ',I10/)
1718500 FORMAT (//' 1D-Model parameters:'/                           &
1719              ' -------------------'//                           &
1720            '    Simulation time:                   ',F8.1,' s'/ &
1721            '    Run-controll output every:         ',F8.1,' s'/ &
1722            '    Vertical profile output every:     ',F8.1,' s'/ &
1723            '    Mixing length calculation:         ',A/         &
1724            '    Dissipation calculation:           ',A/)
1725502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
1726
1727
1728 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.