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

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