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

Last change on this file since 291 was 291, checked in by raasch, 15 years ago

changes for coupling with independent precursor runs; z_i calculation with Sullivan criterion

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