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

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