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

Last change on this file since 1010 was 1004, checked in by raasch, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 77.0 KB
Line 
1 SUBROUTINE header
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: header.f90 1004 2012-09-14 14:56:50Z raasch $
11!
12! 1003 2012-09-14 14:35:53Z raasch
13! output of information about equal/unequal subdomain size removed
14!
15! 1001 2012-09-13 14:08:46Z raasch
16! all actions concerning leapfrog- and upstream-spline-scheme removed
17!
18! 978 2012-08-09 08:28:32Z fricke
19! -km_damp_max, outflow_damping_width
20! +pt_damping_factor, pt_damping_width
21! +z0h
22!
23! 964 2012-07-26 09:14:24Z raasch
24! output of profil-related quantities removed
25!
26! 940 2012-07-09 14:31:00Z raasch
27! Output in case of simulations for pure neutral stratification (no pt-equation
28! solved)
29!
30! 927 2012-06-06 19:15:04Z raasch
31! output of masking_method for mg-solver
32!
33! 868 2012-03-28 12:21:07Z raasch
34! translation velocity in Galilean transformation changed to 0.6 * ug
35!
36! 833 2012-02-22 08:55:55Z maronga
37! Adjusted format for leaf area density
38!
39! 828 2012-02-21 12:00:36Z raasch
40! output of dissipation_classes + radius_classes
41!
42! 825 2012-02-19 03:03:44Z raasch
43! Output of cloud physics parameters/quantities complemented and restructured
44!
45! 767 2011-10-14 06:39:12Z raasch
46! Output of given initial u,v-profiles
47!
48! 759 2011-09-15 13:58:31Z raasch
49! output of maximum number of parallel io streams
50!
51! 707 2011-03-29 11:39:40Z raasch
52! bc_lr/ns replaced by bc_lr/ns_cyc
53!
54! 667 2010-12-23 12:06:00Z suehring/gryschka
55! Output of advection scheme.
56! Modified output of Prandtl-layer height.
57!
58! 580 2010-10-05 13:59:11Z heinze
59! Renaming of ws_vertical_gradient to subs_vertical_gradient,
60! ws_vertical_gradient_level to subs_vertical_gradient_level and
61! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
62!
63! 493 2010-03-01 08:30:24Z raasch
64! NetCDF data output format extendend for NetCDF4/HDF5
65!
66! 449 2010-02-02 11:23:59Z raasch
67! +large scale vertical motion (subsidence/ascent)
68! Bugfix: index problem concerning gradient_level indices removed
69!
70! 410 2009-12-04 17:05:40Z letzel
71! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
72! mask_scale|_x|y|z, masks, skip_time_domask
73!
74! 346 2009-07-06 10:13:41Z raasch
75! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
76! Coupling with independent precursor runs.
77! Output of messages replaced by message handling routine.
78! Output of several additional dvr parameters
79! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
80! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
81! dp_smooth, dpdxy, u_bulk, v_bulk
82! topography_grid_convention moved from user_header
83! small bugfix concerning 3d 64bit netcdf output format
84!
85! 206 2008-10-13 14:59:11Z raasch
86! Bugfix: error in zu index in case of section_xy = -1
87!
88! 198 2008-09-17 08:55:28Z raasch
89! Format adjustments allowing output of larger revision numbers
90!
91! 197 2008-09-16 15:29:03Z raasch
92! allow 100 spectra levels instead of 10 for consistency with
93! define_netcdf_header,
94! bugfix in the output of the characteristic levels of potential temperature,
95! geostrophic wind, scalar concentration, humidity and leaf area density,
96! output of turbulence recycling informations
97!
98! 138 2007-11-28 10:03:58Z letzel
99! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
100! Allow two instead of one digit to specify isosurface and slicer variables.
101! Output of sorting frequency of particles
102!
103! 108 2007-08-24 15:10:38Z letzel
104! Output of informations for coupled model runs (boundary conditions etc.)
105! + output of momentumfluxes at the top boundary
106! Rayleigh damping for ocean, e_init
107!
108! 97 2007-06-21 08:23:15Z raasch
109! Adjustments for the ocean version.
110! use_pt_reference renamed use_reference
111!
112! 87 2007-05-22 15:46:47Z raasch
113! Bugfix: output of use_upstream_for_tke
114!
115! 82 2007-04-16 15:40:52Z raasch
116! Preprocessor strings for different linux clusters changed to "lc",
117! routine local_flush is used for buffer flushing
118!
119! 76 2007-03-29 00:58:32Z raasch
120! Output of netcdf_64bit_3d, particles-package is now part of the default code,
121! output of the loop optimization method, moisture renamed humidity,
122! output of subversion revision number
123!
124! 19 2007-02-23 04:53:48Z raasch
125! Output of scalar flux applied at top boundary
126!
127! RCS Log replace by Id keyword, revision history cleaned up
128!
129! Revision 1.63  2006/08/22 13:53:13  raasch
130! Output of dz_max
131!
132! Revision 1.1  1997/08/11 06:17:20  raasch
133! Initial revision
134!
135!
136! Description:
137! ------------
138! Writing a header with all important informations about the actual run.
139! This subroutine is called three times, two times at the beginning
140! (writing information on files RUN_CONTROL and HEADER) and one time at the
141! end of the run, then writing additional information about CPU-usage on file
142! header.
143!-----------------------------------------------------------------------------!
144
145    USE arrays_3d
146    USE control_parameters
147    USE cloud_parameters
148    USE cpulog
149    USE dvrp_variables
150    USE grid_variables
151    USE indices
152    USE model_1d
153    USE particle_attributes
154    USE pegrid
155    USE subsidence_mod
156    USE spectrum
157
158    IMPLICIT NONE
159
160    CHARACTER (LEN=1)  ::  prec
161    CHARACTER (LEN=2)  ::  do2d_mode
162    CHARACTER (LEN=5)  ::  section_chr
163    CHARACTER (LEN=9)  ::  time_to_string
164    CHARACTER (LEN=10) ::  coor_chr, host_chr
165    CHARACTER (LEN=16) ::  begin_chr
166    CHARACTER (LEN=23) ::  ver_rev
167    CHARACTER (LEN=40) ::  output_format
168    CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
169                           do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
170                           domask_chr, run_classification
171    CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
172                           temperatures, ugcomponent, vgcomponent
173    CHARACTER (LEN=85) ::  roben, runten
174
175    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
176
177    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
178         cxl, cxr, cyn, cys, dim, i, ihost, io, j, l, ll, m, mpi_type
179    REAL    ::  cpuseconds_per_simulated_second
180
181!
182!-- Open the output file. At the end of the simulation, output is directed
183!-- to unit 19.
184    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
185         .NOT. simulated_time_at_begin /= simulated_time )  THEN
186       io = 15   !  header output on file RUN_CONTROL
187    ELSE
188       io = 19   !  header output on file HEADER
189    ENDIF
190    CALL check_open( io )
191
192!
193!-- At the end of the run, output file (HEADER) will be rewritten with
194!-- new informations
195    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
196
197!
198!-- Determine kind of model run
199    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
200       run_classification = '3D - restart run'
201    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
202       run_classification = '3D - run with cyclic fill of 3D - prerun data'
203    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
204       run_classification = '3D - run without 1D - prerun'
205    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
206       run_classification = '3D - run with 1D - prerun'
207    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
208       run_classification = '3D - run initialized by user'
209    ELSE
210       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
211       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
212    ENDIF
213    IF ( ocean )  THEN
214       run_classification = 'ocean - ' // run_classification
215    ELSE
216       run_classification = 'atmosphere - ' // run_classification
217    ENDIF
218
219!
220!-- Run-identification, date, time, host
221    host_chr = host(1:10)
222    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
223    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
224    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
225#if defined( __mpi2 )
226       mpi_type = 2
227#else
228       mpi_type = 1
229#endif
230       WRITE ( io, 101 )  mpi_type, coupling_mode
231    ENDIF
232    WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, &
233                       ADJUSTR( host_chr )
234#if defined( __parallel )
235    IF ( npex == -1  .AND.  pdims(2) /= 1 )  THEN
236       char1 = 'calculated'
237    ELSEIF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.  &
238               host(1:2) == 'lc' )  .AND.                          &
239             npex == -1  .AND.  pdims(2) == 1 )  THEN
240       char1 = 'forced'
241    ELSE
242       char1 = 'predefined'
243    ENDIF
244    IF ( threads_per_task == 1 )  THEN
245       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
246    ELSE
247       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
248                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
249    ENDIF
250    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
251           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
252         npex == -1  .AND.  pdims(2) == 1 )                      &
253    THEN
254       WRITE ( io, 106 )
255    ELSEIF ( pdims(2) == 1 )  THEN
256       WRITE ( io, 107 )  'x'
257    ELSEIF ( pdims(1) == 1 )  THEN
258       WRITE ( io, 107 )  'y'
259    ENDIF
260    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
261    IF ( numprocs /= maximum_parallel_io_streams )  THEN
262       WRITE ( io, 108 )  maximum_parallel_io_streams
263    ENDIF
264#endif
265    WRITE ( io, 99 )
266
267!
268!-- Numerical schemes
269    WRITE ( io, 110 )
270    IF ( psolver(1:7) == 'poisfft' )  THEN
271       WRITE ( io, 111 )  TRIM( fft_method )
272       IF ( psolver == 'poisfft_hybrid' )  WRITE ( io, 138 )
273    ELSEIF ( psolver == 'sor' )  THEN
274       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
275    ELSEIF ( psolver == 'multigrid' )  THEN
276       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
277       IF ( mg_cycles == -1 )  THEN
278          WRITE ( io, 140 )  residual_limit
279       ELSE
280          WRITE ( io, 141 )  mg_cycles
281       ENDIF
282       IF ( mg_switch_to_pe0_level == 0 )  THEN
283          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
284                             nzt_mg(1)
285       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
286          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
287                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
288                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
289                             nzt_mg(mg_switch_to_pe0_level),    &
290                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
291                             nzt_mg(1)
292       ENDIF
293       IF ( masking_method )  WRITE ( io, 144 )
294    ENDIF
295    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
296    THEN
297       WRITE ( io, 142 )
298    ENDIF
299
300    IF ( momentum_advec == 'pw-scheme' )  THEN
301       WRITE ( io, 113 )
302    ELSEIF (momentum_advec == 'ws-scheme' ) THEN
303       WRITE ( io, 503 )
304    ENDIF
305    IF ( scalar_advec == 'pw-scheme' )  THEN
306       WRITE ( io, 116 )
307    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
308       WRITE ( io, 504 )
309    ELSE
310       WRITE ( io, 118 )
311    ENDIF
312
313    WRITE ( io, 139 )  TRIM( loop_optimization )
314
315    IF ( galilei_transformation )  THEN
316       IF ( use_ug_for_galilei_tr )  THEN
317          char1 = '0.6 * geostrophic wind'
318       ELSE
319          char1 = 'mean wind in model domain'
320       ENDIF
321       IF ( simulated_time_at_begin == simulated_time )  THEN
322          char2 = 'at the start of the run'
323       ELSE
324          char2 = 'at the end of the run'
325       ENDIF
326       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), &
327                          advected_distance_x/1000.0, advected_distance_y/1000.0
328    ENDIF
329    WRITE ( io, 122 )  timestep_scheme
330    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
331    IF ( rayleigh_damping_factor /= 0.0 )  THEN
332       IF ( .NOT. ocean )  THEN
333          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
334               rayleigh_damping_factor
335       ELSE
336          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
337               rayleigh_damping_factor
338       ENDIF
339    ENDIF
340    IF ( neutral )  WRITE ( io, 131 )  pt_surface
341    IF ( humidity )  THEN
342       IF ( .NOT. cloud_physics )  THEN
343          WRITE ( io, 129 )
344       ELSE
345          WRITE ( io, 130 )
346       ENDIF
347    ENDIF
348    IF ( passive_scalar )  WRITE ( io, 134 )
349    IF ( conserve_volume_flow )  THEN
350       WRITE ( io, 150 )  conserve_volume_flow_mode
351       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
352          WRITE ( io, 151 )  u_bulk, v_bulk
353       ENDIF
354    ELSEIF ( dp_external )  THEN
355       IF ( dp_smooth )  THEN
356          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
357       ELSE
358          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
359       ENDIF
360    ENDIF
361    IF ( large_scale_subsidence )  THEN
362        WRITE ( io, 153 )
363        WRITE ( io, 154 )
364    ENDIF
365    WRITE ( io, 99 )
366
367!
368!-- Runtime and timestep informations
369    WRITE ( io, 200 )
370    IF ( .NOT. dt_fixed )  THEN
371       WRITE ( io, 201 )  dt_max, cfl_factor
372    ELSE
373       WRITE ( io, 202 )  dt
374    ENDIF
375    WRITE ( io, 203 )  simulated_time_at_begin, end_time
376
377    IF ( time_restart /= 9999999.9  .AND. &
378         simulated_time_at_begin == simulated_time )  THEN
379       IF ( dt_restart == 9999999.9 )  THEN
380          WRITE ( io, 204 )  ' Restart at:       ',time_restart
381       ELSE
382          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
383       ENDIF
384    ENDIF
385
386    IF ( simulated_time_at_begin /= simulated_time )  THEN
387       i = MAX ( log_point_s(10)%counts, 1 )
388       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0 )  THEN
389          cpuseconds_per_simulated_second = 0.0
390       ELSE
391          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
392                                            ( simulated_time -    &
393                                              simulated_time_at_begin )
394       ENDIF
395       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum, &
396                          log_point_s(10)%sum / REAL( i ),     &
397                          cpuseconds_per_simulated_second
398       IF ( time_restart /= 9999999.9  .AND.  time_restart < end_time )  THEN
399          IF ( dt_restart == 9999999.9 )  THEN
400             WRITE ( io, 204 )  ' Next restart at:  ',time_restart
401          ELSE
402             WRITE ( io, 205 )  ' Next restart at:  ',time_restart, dt_restart
403          ENDIF
404       ENDIF
405    ENDIF
406
407!
408!-- Start time for coupled runs, if independent precursor runs for atmosphere
409!-- and ocean are used. In this case, coupling_start_time defines the time
410!-- when the coupling is switched on.
411    IF ( coupling_start_time /= 0.0 )  THEN
412       IF ( coupling_start_time >= simulated_time_at_begin )  THEN
413          char1 = 'Precursor run for a coupled atmosphere-ocean run'
414       ELSE
415          char1 = 'Coupled atmosphere-ocean run following independent ' // &
416                  'precursor runs'
417       ENDIF
418       WRITE ( io, 207 )  char1, coupling_start_time
419    ENDIF
420
421!
422!-- Computational grid
423    IF ( .NOT. ocean )  THEN
424       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
425       IF ( dz_stretch_level_index < nzt+1 )  THEN
426          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
427                             dz_stretch_factor, dz_max
428       ENDIF
429    ELSE
430       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
431       IF ( dz_stretch_level_index > 0 )  THEN
432          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
433                             dz_stretch_factor, dz_max
434       ENDIF
435    ENDIF
436    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
437                       MIN( nnz+2, nzt+2 )
438    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
439
440!
441!-- Topography
442    WRITE ( io, 270 )  topography
443    SELECT CASE ( TRIM( topography ) )
444
445       CASE ( 'flat' )
446          ! no actions necessary
447
448       CASE ( 'single_building' )
449          blx = INT( building_length_x / dx )
450          bly = INT( building_length_y / dy )
451          bh  = INT( building_height / dz )
452
453          IF ( building_wall_left == 9999999.9 )  THEN
454             building_wall_left = ( nx + 1 - blx ) / 2 * dx
455          ENDIF
456          bxl = INT ( building_wall_left / dx + 0.5 )
457          bxr = bxl + blx
458
459          IF ( building_wall_south == 9999999.9 )  THEN
460             building_wall_south = ( ny + 1 - bly ) / 2 * dy
461          ENDIF
462          bys = INT ( building_wall_south / dy + 0.5 )
463          byn = bys + bly
464
465          WRITE ( io, 271 )  building_length_x, building_length_y, &
466                             building_height, bxl, bxr, bys, byn
467
468       CASE ( 'single_street_canyon' )
469          ch  = NINT( canyon_height / dz )
470          IF ( canyon_width_x /= 9999999.9 )  THEN
471!
472!--          Street canyon in y direction
473             cwx = NINT( canyon_width_x / dx )
474             IF ( canyon_wall_left == 9999999.9 )  THEN
475                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
476             ENDIF
477             cxl = NINT( canyon_wall_left / dx )
478             cxr = cxl + cwx
479             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
480
481          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
482!
483!--          Street canyon in x direction
484             cwy = NINT( canyon_width_y / dy )
485             IF ( canyon_wall_south == 9999999.9 )  THEN
486                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
487             ENDIF
488             cys = NINT( canyon_wall_south / dy )
489             cyn = cys + cwy
490             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
491          ENDIF
492
493    END SELECT
494
495    IF ( TRIM( topography ) /= 'flat' )  THEN
496       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
497          IF ( TRIM( topography ) == 'single_building' .OR.  &
498               TRIM( topography ) == 'single_street_canyon' )  THEN
499             WRITE ( io, 278 )
500          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
501             WRITE ( io, 279 )
502          ENDIF
503       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
504          WRITE ( io, 278 )
505       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
506          WRITE ( io, 279 )
507       ENDIF
508    ENDIF
509
510    IF ( plant_canopy ) THEN
511
512       WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
513       IF ( passive_scalar ) THEN
514          WRITE ( io, 281 ) scalar_exchange_coefficient,   &
515                            leaf_surface_concentration
516       ENDIF
517
518!
519!--    Heat flux at the top of vegetation
520       WRITE ( io, 282 ) cthf
521
522!
523!--    Leaf area density profile
524!--    Building output strings, starting with surface value
525       WRITE ( learde, '(F6.4)' )  lad_surface
526       gradients = '------'
527       slices = '     0'
528       coordinates = '   0.0'
529       i = 1
530       DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
531
532          WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
533          learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
534
535          WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
536          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
537
538          WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
539          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
540
541          WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
542          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
543
544          i = i + 1
545       ENDDO
546
547       WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
548                          TRIM( gradients ), TRIM( slices )
549
550    ENDIF
551
552!
553!-- Boundary conditions
554    IF ( ibc_p_b == 0 )  THEN
555       runten = 'p(0)     = 0      |'
556    ELSEIF ( ibc_p_b == 1 )  THEN
557       runten = 'p(0)     = p(1)   |'
558    ELSE
559       runten = 'p(0)     = p(1) +R|'
560    ENDIF
561    IF ( ibc_p_t == 0 )  THEN
562       roben  = 'p(nzt+1) = 0      |'
563    ELSE
564       roben  = 'p(nzt+1) = p(nzt) |'
565    ENDIF
566
567    IF ( ibc_uv_b == 0 )  THEN
568       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
569    ELSE
570       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
571    ENDIF
572    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
573       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
574    ELSEIF ( ibc_uv_t == 0 )  THEN
575       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
576    ELSE
577       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
578    ENDIF
579
580    IF ( ibc_pt_b == 0 )  THEN
581       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
582    ELSEIF ( ibc_pt_b == 1 )  THEN
583       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
584    ELSEIF ( ibc_pt_b == 2 )  THEN
585       runten = TRIM( runten ) // ' pt(0) = from coupled model'
586    ENDIF
587    IF ( ibc_pt_t == 0 )  THEN
588       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
589    ELSEIF( ibc_pt_t == 1 )  THEN
590       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
591    ELSEIF( ibc_pt_t == 2 )  THEN
592       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
593
594    ENDIF
595
596    WRITE ( io, 300 )  runten, roben
597
598    IF ( .NOT. constant_diffusion )  THEN
599       IF ( ibc_e_b == 1 )  THEN
600          runten = 'e(0)     = e(1)'
601       ELSE
602          runten = 'e(0)     = e(1) = (u*/0.1)**2'
603       ENDIF
604       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
605
606       WRITE ( io, 301 )  'e', runten, roben       
607
608    ENDIF
609
610    IF ( ocean )  THEN
611       runten = 'sa(0)    = sa(1)'
612       IF ( ibc_sa_t == 0 )  THEN
613          roben =  'sa(nzt+1) = sa_surface'
614       ELSE
615          roben =  'sa(nzt+1) = sa(nzt)'
616       ENDIF
617       WRITE ( io, 301 ) 'sa', runten, roben
618    ENDIF
619
620    IF ( humidity )  THEN
621       IF ( ibc_q_b == 0 )  THEN
622          runten = 'q(0)     = q_surface'
623       ELSE
624          runten = 'q(0)     = q(1)'
625       ENDIF
626       IF ( ibc_q_t == 0 )  THEN
627          roben =  'q(nzt)   = q_top'
628       ELSE
629          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
630       ENDIF
631       WRITE ( io, 301 ) 'q', runten, roben
632    ENDIF
633
634    IF ( passive_scalar )  THEN
635       IF ( ibc_q_b == 0 )  THEN
636          runten = 's(0)     = s_surface'
637       ELSE
638          runten = 's(0)     = s(1)'
639       ENDIF
640       IF ( ibc_q_t == 0 )  THEN
641          roben =  's(nzt)   = s_top'
642       ELSE
643          roben =  's(nzt)   = s(nzt-1) + ds/dz'
644       ENDIF
645       WRITE ( io, 301 ) 's', runten, roben
646    ENDIF
647
648    IF ( use_surface_fluxes )  THEN
649       WRITE ( io, 303 )
650       IF ( constant_heatflux )  THEN
651          WRITE ( io, 306 )  surface_heatflux
652          IF ( random_heatflux )  WRITE ( io, 307 )
653       ENDIF
654       IF ( humidity  .AND.  constant_waterflux )  THEN
655          WRITE ( io, 311 ) surface_waterflux
656       ENDIF
657       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
658          WRITE ( io, 313 ) surface_waterflux
659       ENDIF
660    ENDIF
661
662    IF ( use_top_fluxes )  THEN
663       WRITE ( io, 304 )
664       IF ( coupling_mode == 'uncoupled' )  THEN
665          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
666          IF ( constant_top_heatflux )  THEN
667             WRITE ( io, 306 )  top_heatflux
668          ENDIF
669       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
670          WRITE ( io, 316 )
671       ENDIF
672       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
673          WRITE ( io, 309 )  top_salinityflux
674       ENDIF
675       IF ( humidity  .OR.  passive_scalar )  THEN
676          WRITE ( io, 315 )
677       ENDIF
678    ENDIF
679
680    IF ( prandtl_layer )  THEN
681       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
682                          z0h_factor*roughness_length, kappa, &
683                          rif_min, rif_max
684       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
685       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
686          WRITE ( io, 312 )
687       ENDIF
688       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
689          WRITE ( io, 314 )
690       ENDIF
691    ELSE
692       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
693          WRITE ( io, 310 )  rif_min, rif_max
694       ENDIF
695    ENDIF
696
697    WRITE ( io, 317 )  bc_lr, bc_ns
698    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
699       WRITE ( io, 318 )  pt_damping_width, pt_damping_factor       
700       IF ( turbulent_inflow )  THEN
701          WRITE ( io, 319 )  recycling_width, recycling_plane, &
702                             inflow_damping_height, inflow_damping_width
703       ENDIF
704    ENDIF
705
706!
707!-- Listing of 1D-profiles
708    WRITE ( io, 325 )  dt_dopr_listing
709    IF ( averaging_interval_pr /= 0.0 )  THEN
710       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
711    ENDIF
712
713!
714!-- DATA output
715    WRITE ( io, 330 )
716    IF ( averaging_interval_pr /= 0.0 )  THEN
717       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
718    ENDIF
719
720!
721!-- 1D-profiles
722    dopr_chr = 'Profile:'
723    IF ( dopr_n /= 0 )  THEN
724       WRITE ( io, 331 )
725
726       output_format = ''
727       IF ( netcdf_output )  THEN
728          IF ( netcdf_data_format == 1 )  THEN
729             output_format = 'NetCDF classic'
730          ELSE
731             output_format = 'NetCDF 64bit offset'
732          ENDIF
733       ENDIF
734       WRITE ( io, 344 )  output_format
735
736       DO  i = 1, dopr_n
737          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
738          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
739             WRITE ( io, 332 )  dopr_chr
740             dopr_chr = '       :'
741          ENDIF
742       ENDDO
743
744       IF ( dopr_chr /= '' )  THEN
745          WRITE ( io, 332 )  dopr_chr
746       ENDIF
747       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
748       IF ( skip_time_dopr /= 0.0 )  WRITE ( io, 339 )  skip_time_dopr
749    ENDIF
750
751!
752!-- 2D-arrays
753    DO  av = 0, 1
754
755       i = 1
756       do2d_xy = ''
757       do2d_xz = ''
758       do2d_yz = ''
759       DO  WHILE ( do2d(av,i) /= ' ' )
760
761          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
762          do2d_mode = do2d(av,i)(l-1:l)
763
764          SELECT CASE ( do2d_mode )
765             CASE ( 'xy' )
766                ll = LEN_TRIM( do2d_xy )
767                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
768             CASE ( 'xz' )
769                ll = LEN_TRIM( do2d_xz )
770                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
771             CASE ( 'yz' )
772                ll = LEN_TRIM( do2d_yz )
773                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
774          END SELECT
775
776          i = i + 1
777
778       ENDDO
779
780       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
781              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
782              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) )  .AND. &
783            ( netcdf_output  .OR.  iso2d_output ) )  THEN
784
785          IF (  av == 0 )  THEN
786             WRITE ( io, 334 )  ''
787          ELSE
788             WRITE ( io, 334 )  '(time-averaged)'
789          ENDIF
790
791          IF ( do2d_at_begin )  THEN
792             begin_chr = 'and at the start'
793          ELSE
794             begin_chr = ''
795          ENDIF
796
797          output_format = ''
798          IF ( netcdf_output )  THEN
799             IF ( netcdf_data_format == 1 )  THEN
800                output_format = 'NetCDF classic'
801             ELSEIF ( netcdf_data_format == 2 )  THEN
802                output_format = 'NetCDF 64bit offset'
803             ELSEIF ( netcdf_data_format == 3 )  THEN
804                output_format = 'NetCDF4/HDF5'
805             ELSEIF ( netcdf_data_format == 4 )  THEN
806                output_format = 'NetCDF4/HDF5 clasic'
807             ENDIF
808          ENDIF
809          IF ( iso2d_output )  THEN
810             IF ( netcdf_output )  THEN
811                output_format = TRIM( output_format ) // ' and iso2d'
812             ELSE
813                output_format = 'iso2d'
814             ENDIF
815          ENDIF
816          WRITE ( io, 344 )  output_format
817
818          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
819             i = 1
820             slices = '/'
821             coordinates = '/'
822!
823!--          Building strings with index and coordinate informations of the
824!--          slices
825             DO  WHILE ( section(i,1) /= -9999 )
826
827                WRITE (section_chr,'(I5)')  section(i,1)
828                section_chr = ADJUSTL( section_chr )
829                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
830
831                IF ( section(i,1) == -1 )  THEN
832                   WRITE (coor_chr,'(F10.1)')  -1.0
833                ELSE
834                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
835                ENDIF
836                coor_chr = ADJUSTL( coor_chr )
837                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
838
839                i = i + 1
840             ENDDO
841             IF ( av == 0 )  THEN
842                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
843                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
844                                   TRIM( coordinates )
845                IF ( skip_time_do2d_xy /= 0.0 )  THEN
846                   WRITE ( io, 339 )  skip_time_do2d_xy
847                ENDIF
848             ELSE
849                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
850                                   TRIM( begin_chr ), averaging_interval, &
851                                   dt_averaging_input, 'k', TRIM( slices ), &
852                                   TRIM( coordinates )
853                IF ( skip_time_data_output_av /= 0.0 )  THEN
854                   WRITE ( io, 339 )  skip_time_data_output_av
855                ENDIF
856             ENDIF
857
858          ENDIF
859
860          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
861             i = 1
862             slices = '/'
863             coordinates = '/'
864!
865!--          Building strings with index and coordinate informations of the
866!--          slices
867             DO  WHILE ( section(i,2) /= -9999 )
868
869                WRITE (section_chr,'(I5)')  section(i,2)
870                section_chr = ADJUSTL( section_chr )
871                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
872
873                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
874                coor_chr = ADJUSTL( coor_chr )
875                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
876
877                i = i + 1
878             ENDDO
879             IF ( av == 0 )  THEN
880                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
881                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
882                                   TRIM( coordinates )
883                IF ( skip_time_do2d_xz /= 0.0 )  THEN
884                   WRITE ( io, 339 )  skip_time_do2d_xz
885                ENDIF
886             ELSE
887                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
888                                   TRIM( begin_chr ), averaging_interval, &
889                                   dt_averaging_input, 'j', TRIM( slices ), &
890                                   TRIM( coordinates )
891                IF ( skip_time_data_output_av /= 0.0 )  THEN
892                   WRITE ( io, 339 )  skip_time_data_output_av
893                ENDIF
894             ENDIF
895          ENDIF
896
897          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
898             i = 1
899             slices = '/'
900             coordinates = '/'
901!
902!--          Building strings with index and coordinate informations of the
903!--          slices
904             DO  WHILE ( section(i,3) /= -9999 )
905
906                WRITE (section_chr,'(I5)')  section(i,3)
907                section_chr = ADJUSTL( section_chr )
908                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
909
910                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
911                coor_chr = ADJUSTL( coor_chr )
912                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
913
914                i = i + 1
915             ENDDO
916             IF ( av == 0 )  THEN
917                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
918                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
919                                   TRIM( coordinates )
920                IF ( skip_time_do2d_yz /= 0.0 )  THEN
921                   WRITE ( io, 339 )  skip_time_do2d_yz
922                ENDIF
923             ELSE
924                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
925                                   TRIM( begin_chr ), averaging_interval, &
926                                   dt_averaging_input, 'i', TRIM( slices ), &
927                                   TRIM( coordinates )
928                IF ( skip_time_data_output_av /= 0.0 )  THEN
929                   WRITE ( io, 339 )  skip_time_data_output_av
930                ENDIF
931             ENDIF
932          ENDIF
933
934       ENDIF
935
936    ENDDO
937
938!
939!-- 3d-arrays
940    DO  av = 0, 1
941
942       i = 1
943       do3d_chr = ''
944       DO  WHILE ( do3d(av,i) /= ' ' )
945
946          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
947          i = i + 1
948
949       ENDDO
950
951       IF ( do3d_chr /= '' )  THEN
952          IF ( av == 0 )  THEN
953             WRITE ( io, 336 )  ''
954          ELSE
955             WRITE ( io, 336 )  '(time-averaged)'
956          ENDIF
957
958          output_format = ''
959          IF ( netcdf_output )  THEN
960             IF ( netcdf_data_format == 1 )  THEN
961                output_format = 'NetCDF classic'
962             ELSEIF ( netcdf_data_format == 2 )  THEN
963                output_format = 'NetCDF 64bit offset'
964             ELSEIF ( netcdf_data_format == 3 )  THEN
965                output_format = 'NetCDF4/HDF5'
966             ELSEIF ( netcdf_data_format == 4 )  THEN
967                output_format = 'NetCDF4/HDF5 clasic'
968             ENDIF
969          ENDIF
970          IF ( avs_output )  THEN
971             IF ( netcdf_output )  THEN
972                output_format = TRIM( output_format ) // ' and avs'
973             ELSE
974                output_format = 'avs'
975             ENDIF
976          ENDIF
977          WRITE ( io, 344 )  output_format
978
979          IF ( do3d_at_begin )  THEN
980             begin_chr = 'and at the start'
981          ELSE
982             begin_chr = ''
983          ENDIF
984          IF ( av == 0 )  THEN
985             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
986                                zu(nz_do3d), nz_do3d
987          ELSE
988             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
989                                TRIM( begin_chr ), averaging_interval, &
990                                dt_averaging_input, zu(nz_do3d), nz_do3d
991          ENDIF
992
993          IF ( do3d_compress )  THEN
994             do3d_chr = ''
995             i = 1
996             DO WHILE ( do3d(av,i) /= ' ' )
997
998                SELECT CASE ( do3d(av,i) )
999                   CASE ( 'u' )
1000                      j = 1
1001                   CASE ( 'v' )
1002                      j = 2
1003                   CASE ( 'w' )
1004                      j = 3
1005                   CASE ( 'p' )
1006                      j = 4
1007                   CASE ( 'pt' )
1008                      j = 5
1009                END SELECT
1010                WRITE ( prec, '(I1)' )  plot_3d_precision(j)%precision
1011                do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // &
1012                           ':' // prec // ','
1013                i = i + 1
1014
1015             ENDDO
1016             WRITE ( io, 338 )  do3d_chr
1017
1018          ENDIF
1019
1020          IF ( av == 0 )  THEN
1021             IF ( skip_time_do3d /= 0.0 )  THEN
1022                WRITE ( io, 339 )  skip_time_do3d
1023             ENDIF
1024          ELSE
1025             IF ( skip_time_data_output_av /= 0.0 )  THEN
1026                WRITE ( io, 339 )  skip_time_data_output_av
1027             ENDIF
1028          ENDIF
1029
1030       ENDIF
1031
1032    ENDDO
1033
1034!
1035!-- masked arrays
1036    IF ( masks > 0 )  WRITE ( io, 345 )  &
1037         mask_scale_x, mask_scale_y, mask_scale_z
1038    DO  mid = 1, masks
1039       DO  av = 0, 1
1040
1041          i = 1
1042          domask_chr = ''
1043          DO  WHILE ( domask(mid,av,i) /= ' ' )
1044             domask_chr = TRIM( domask_chr ) // ' ' //  &
1045                          TRIM( domask(mid,av,i) ) // ','
1046             i = i + 1
1047          ENDDO
1048
1049          IF ( domask_chr /= '' )  THEN
1050             IF ( av == 0 )  THEN
1051                WRITE ( io, 346 )  '', mid
1052             ELSE
1053                WRITE ( io, 346 )  ' (time-averaged)', mid
1054             ENDIF
1055
1056             output_format = ''
1057             IF ( netcdf_output )  THEN
1058                IF ( netcdf_data_format == 1 )  THEN
1059                   output_format = 'NetCDF classic'
1060                ELSEIF ( netcdf_data_format == 2 )  THEN
1061                   output_format = 'NetCDF 64bit offset'
1062                ELSEIF ( netcdf_data_format == 3 )  THEN
1063                   output_format = 'NetCDF4/HDF5'
1064                ELSEIF ( netcdf_data_format == 4 )  THEN
1065                   output_format = 'NetCDF4/HDF5 clasic'
1066                ENDIF
1067             ENDIF
1068             WRITE ( io, 344 )  output_format
1069
1070             IF ( av == 0 )  THEN
1071                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1072             ELSE
1073                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1074                                   averaging_interval, dt_averaging_input
1075             ENDIF
1076
1077             IF ( av == 0 )  THEN
1078                IF ( skip_time_domask(mid) /= 0.0 )  THEN
1079                   WRITE ( io, 339 )  skip_time_domask(mid)
1080                ENDIF
1081             ELSE
1082                IF ( skip_time_data_output_av /= 0.0 )  THEN
1083                   WRITE ( io, 339 )  skip_time_data_output_av
1084                ENDIF
1085             ENDIF
1086!
1087!--          output locations
1088             DO  dim = 1, 3
1089                IF ( mask(mid,dim,1) >= 0.0 )  THEN
1090                   count = 0
1091                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0 )
1092                      count = count + 1
1093                   ENDDO
1094                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1095                                      mask(mid,dim,:count)
1096                ELSEIF ( mask_loop(mid,dim,1) < 0.0 .AND.  &
1097                         mask_loop(mid,dim,2) < 0.0 .AND.  &
1098                         mask_loop(mid,dim,3) == 0.0 )  THEN
1099                   WRITE ( io, 350 )  dir(dim), dir(dim)
1100                ELSEIF ( mask_loop(mid,dim,3) == 0.0 )  THEN
1101                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1102                                      mask_loop(mid,dim,1:2)
1103                ELSE
1104                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1105                                      mask_loop(mid,dim,1:3)
1106                ENDIF
1107             ENDDO
1108          ENDIF
1109
1110       ENDDO
1111    ENDDO
1112
1113!
1114!-- Timeseries
1115    IF ( dt_dots /= 9999999.9 )  THEN
1116       WRITE ( io, 340 )
1117
1118       output_format = ''
1119       IF ( netcdf_output )  THEN
1120          IF ( netcdf_data_format == 1 )  THEN
1121             output_format = 'NetCDF classic'
1122          ELSE
1123             output_format = 'NetCDF 64bit offset'
1124          ENDIF
1125       ENDIF
1126       WRITE ( io, 344 )  output_format
1127       WRITE ( io, 341 )  dt_dots
1128    ENDIF
1129
1130#if defined( __dvrp_graphics )
1131!
1132!-- Dvrp-output
1133    IF ( dt_dvrp /= 9999999.9 )  THEN
1134       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1135                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1136       i = 1
1137       l = 0
1138       m = 0
1139       DO WHILE ( mode_dvrp(i) /= ' ' )
1140          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
1141             READ ( mode_dvrp(i), '(10X,I2)' )  j
1142             l = l + 1
1143             IF ( do3d(0,j) /= ' ' )  THEN
1144                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1145                                   isosurface_color(:,l)
1146             ENDIF
1147          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
1148             READ ( mode_dvrp(i), '(6X,I2)' )  j
1149             m = m + 1
1150             IF ( do2d(0,j) /= ' ' )  THEN
1151                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1152                                   slicer_range_limits_dvrp(:,m)
1153             ENDIF
1154          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
1155             WRITE ( io, 363 )  dvrp_psize
1156             IF ( particle_dvrpsize /= 'none' )  THEN
1157                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1158                                   dvrpsize_interval
1159             ENDIF
1160             IF ( particle_color /= 'none' )  THEN
1161                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1162                                   color_interval
1163             ENDIF
1164          ENDIF
1165          i = i + 1
1166       ENDDO
1167
1168       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1169                          superelevation_y, superelevation, clip_dvrp_l, &
1170                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1171
1172       IF ( TRIM( topography ) /= 'flat' )  THEN
1173          WRITE ( io, 366 )  topography_color
1174          IF ( cluster_size > 1 )  THEN
1175             WRITE ( io, 367 )  cluster_size
1176          ENDIF
1177       ENDIF
1178
1179    ENDIF
1180#endif
1181
1182#if defined( __spectra )
1183!
1184!-- Spectra output
1185    IF ( dt_dosp /= 9999999.9 ) THEN
1186       WRITE ( io, 370 )
1187
1188       output_format = ''
1189       IF ( netcdf_output )  THEN
1190          IF ( netcdf_data_format == 1 )  THEN
1191             output_format = 'NetCDF classic'
1192          ELSE
1193             output_format = 'NetCDF 64bit offset'
1194          ENDIF
1195       ENDIF
1196       WRITE ( io, 344 )  output_format
1197       WRITE ( io, 371 )  dt_dosp
1198       IF ( skip_time_dosp /= 0.0 )  WRITE ( io, 339 )  skip_time_dosp
1199       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1200                          ( spectra_direction(i), i = 1,10 ),  &
1201                          ( comp_spectra_level(i), i = 1,100 ), &
1202                          ( plot_spectra_level(i), i = 1,100 ), &
1203                          averaging_interval_sp, dt_averaging_input_pr
1204    ENDIF
1205#endif
1206
1207    WRITE ( io, 99 )
1208
1209!
1210!-- Physical quantities
1211    WRITE ( io, 400 )
1212
1213!
1214!-- Geostrophic parameters
1215    WRITE ( io, 410 )  omega, phi, f, fs
1216
1217!
1218!-- Other quantities
1219    WRITE ( io, 411 )  g
1220    IF ( use_reference )  THEN
1221       IF ( ocean )  THEN
1222          WRITE ( io, 412 )  prho_reference
1223       ELSE
1224          WRITE ( io, 413 )  pt_reference
1225       ENDIF
1226    ENDIF
1227
1228!
1229!-- Cloud physics parameters
1230    IF ( cloud_physics ) THEN
1231       WRITE ( io, 415 )
1232       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
1233    ENDIF
1234
1235!-- Profile of the geostrophic wind (component ug)
1236!-- Building output strings
1237    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
1238    gradients = '------'
1239    slices = '     0'
1240    coordinates = '   0.0'
1241    i = 1
1242    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
1243     
1244       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
1245       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
1246
1247       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
1248       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1249
1250       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
1251       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1252
1253       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
1254       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1255
1256       IF ( i == 10 )  THEN
1257          EXIT
1258       ELSE
1259          i = i + 1
1260       ENDIF
1261
1262    ENDDO
1263
1264    WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
1265                       TRIM( gradients ), TRIM( slices )
1266
1267!-- Profile of the geostrophic wind (component vg)
1268!-- Building output strings
1269    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
1270    gradients = '------'
1271    slices = '     0'
1272    coordinates = '   0.0'
1273    i = 1
1274    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
1275
1276       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
1277       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
1278
1279       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
1280       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1281
1282       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
1283       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1284
1285       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
1286       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
1287
1288       IF ( i == 10 )  THEN
1289          EXIT
1290       ELSE
1291          i = i + 1
1292       ENDIF
1293 
1294    ENDDO
1295
1296    WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
1297                       TRIM( gradients ), TRIM( slices )
1298
1299!
1300!-- Initial wind profiles
1301    IF ( u_profile(1) /= 9999999.9 )  WRITE ( io, 427 )
1302
1303!
1304!-- Initial temperature profile
1305!-- Building output strings, starting with surface temperature
1306    WRITE ( temperatures, '(F6.2)' )  pt_surface
1307    gradients = '------'
1308    slices = '     0'
1309    coordinates = '   0.0'
1310    i = 1
1311    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1312
1313       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1314       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1315
1316       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1317       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1318
1319       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1320       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1321
1322       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1323       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1324
1325       IF ( i == 10 )  THEN
1326          EXIT
1327       ELSE
1328          i = i + 1
1329       ENDIF
1330
1331    ENDDO
1332
1333    WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1334                       TRIM( gradients ), TRIM( slices )
1335
1336!
1337!-- Initial humidity profile
1338!-- Building output strings, starting with surface humidity
1339    IF ( humidity  .OR.  passive_scalar )  THEN
1340       WRITE ( temperatures, '(E8.1)' )  q_surface
1341       gradients = '--------'
1342       slices = '       0'
1343       coordinates = '     0.0'
1344       i = 1
1345       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1346         
1347          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1348          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1349
1350          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1351          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1352         
1353          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1354          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1355         
1356          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1357          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1358
1359          IF ( i == 10 )  THEN
1360             EXIT
1361          ELSE
1362             i = i + 1
1363          ENDIF
1364
1365       ENDDO
1366
1367       IF ( humidity )  THEN
1368          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1369                             TRIM( gradients ), TRIM( slices )
1370       ELSE
1371          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1372                             TRIM( gradients ), TRIM( slices )
1373       ENDIF
1374    ENDIF
1375
1376!
1377!-- Initial salinity profile
1378!-- Building output strings, starting with surface salinity
1379    IF ( ocean )  THEN
1380       WRITE ( temperatures, '(F6.2)' )  sa_surface
1381       gradients = '------'
1382       slices = '     0'
1383       coordinates = '   0.0'
1384       i = 1
1385       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1386
1387          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1388          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1389
1390          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1391          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1392
1393          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1394          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1395
1396          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1397          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1398
1399          IF ( i == 10 )  THEN
1400             EXIT
1401          ELSE
1402             i = i + 1
1403          ENDIF
1404
1405       ENDDO
1406
1407       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1408                          TRIM( gradients ), TRIM( slices )
1409    ENDIF
1410
1411!
1412!-- Profile for the large scale vertial velocity
1413!-- Building output strings, starting with surface value
1414    IF ( large_scale_subsidence )  THEN
1415       temperatures = '   0.0'
1416       gradients = '------'
1417       slices = '     0'
1418       coordinates = '   0.0'
1419       i = 1
1420       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
1421
1422          WRITE (coor_chr,'(E10.2,7X)')  &
1423                                w_subs(subs_vertical_gradient_level_i(i))
1424          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1425
1426          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
1427          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1428
1429          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
1430          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1431
1432          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
1433          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1434
1435          IF ( i == 10 )  THEN
1436             EXIT
1437          ELSE
1438             i = i + 1
1439          ENDIF
1440
1441       ENDDO
1442
1443       WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
1444                          TRIM( gradients ), TRIM( slices )
1445    ENDIF
1446
1447!
1448!-- Cloud physcis parameters / quantities / numerical methods
1449    WRITE ( io, 430 )
1450    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1451       WRITE ( io, 431 )
1452    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1453       WRITE ( io, 432 )
1454       IF ( radiation )      WRITE ( io, 132 )
1455       IF ( precipitation )  WRITE ( io, 133 )
1456    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1457       WRITE ( io, 433 )
1458       IF ( curvature_solution_effects )  WRITE ( io, 434 )
1459       IF ( collision_kernel /= 'none' )  THEN
1460          WRITE ( io, 435 )  TRIM( collision_kernel )
1461          IF ( collision_kernel(6:9) == 'fast' )  THEN
1462             WRITE ( io, 436 )  radius_classes, dissipation_classes
1463          ENDIF
1464       ELSE
1465          WRITE ( io, 437 )
1466       ENDIF
1467    ENDIF
1468
1469!
1470!-- LES / turbulence parameters
1471    WRITE ( io, 450 )
1472
1473!--
1474! ... LES-constants used must still be added here
1475!--
1476    IF ( constant_diffusion )  THEN
1477       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1478                          prandtl_number
1479    ENDIF
1480    IF ( .NOT. constant_diffusion)  THEN
1481       IF ( e_init > 0.0 )  WRITE ( io, 455 )  e_init
1482       IF ( e_min > 0.0 )  WRITE ( io, 454 )  e_min
1483       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1484       IF ( adjust_mixing_length  .AND.  prandtl_layer )  WRITE ( io, 452 )
1485    ENDIF
1486
1487!
1488!-- Special actions during the run
1489    WRITE ( io, 470 )
1490    IF ( create_disturbances )  THEN
1491       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1492                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1493                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1494       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1495          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1496       ELSE
1497          WRITE ( io, 473 )  disturbance_energy_limit
1498       ENDIF
1499       WRITE ( io, 474 )  TRIM( random_generator )
1500    ENDIF
1501    IF ( pt_surface_initial_change /= 0.0 )  THEN
1502       WRITE ( io, 475 )  pt_surface_initial_change
1503    ENDIF
1504    IF ( humidity  .AND.  q_surface_initial_change /= 0.0 )  THEN
1505       WRITE ( io, 476 )  q_surface_initial_change       
1506    ENDIF
1507    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0 )  THEN
1508       WRITE ( io, 477 )  q_surface_initial_change       
1509    ENDIF
1510
1511    IF ( particle_advection )  THEN
1512!
1513!--    Particle attributes
1514       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1515                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
1516                          end_time_prel, dt_sort_particles
1517       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1518       IF ( random_start_position )  WRITE ( io, 481 )
1519       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1520       WRITE ( io, 495 )  total_number_of_particles
1521       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
1522          WRITE ( io, 483 )  maximum_number_of_tailpoints
1523          IF ( minimum_tailpoint_distance /= 0 )  THEN
1524             WRITE ( io, 484 )  total_number_of_tails,      &
1525                                minimum_tailpoint_distance, &
1526                                maximum_tailpoint_age
1527          ENDIF
1528       ENDIF
1529       IF ( dt_write_particle_data /= 9999999.9 )  THEN
1530          WRITE ( io, 485 )  dt_write_particle_data
1531          output_format = ''
1532          IF ( netcdf_output )  THEN
1533             IF ( netcdf_data_format > 1 )  THEN
1534                output_format = 'netcdf (64 bit offset) and binary'
1535             ELSE
1536                output_format = 'netcdf and binary'
1537             ENDIF
1538          ELSE
1539             output_format = 'binary'
1540          ENDIF
1541          WRITE ( io, 344 )  output_format
1542       ENDIF
1543       IF ( dt_dopts /= 9999999.9 )  WRITE ( io, 494 )  dt_dopts
1544       IF ( write_particle_statistics )  WRITE ( io, 486 )
1545
1546       WRITE ( io, 487 )  number_of_particle_groups
1547
1548       DO  i = 1, number_of_particle_groups
1549          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9 )  THEN
1550             WRITE ( io, 490 )  i, 0.0
1551             WRITE ( io, 492 )
1552          ELSE
1553             WRITE ( io, 490 )  i, radius(i)
1554             IF ( density_ratio(i) /= 0.0 )  THEN
1555                WRITE ( io, 491 )  density_ratio(i)
1556             ELSE
1557                WRITE ( io, 492 )
1558             ENDIF
1559          ENDIF
1560          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1561                             pdx(i), pdy(i), pdz(i)
1562          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
1563       ENDDO
1564
1565    ENDIF
1566
1567
1568!
1569!-- Parameters of 1D-model
1570    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1571       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1572                          mixing_length_1d, dissipation_1d
1573       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1574          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1575       ENDIF
1576    ENDIF
1577
1578!
1579!-- User-defined informations
1580    CALL user_header( io )
1581
1582    WRITE ( io, 99 )
1583
1584!
1585!-- Write buffer contents to disc immediately
1586    CALL local_flush( io )
1587
1588!
1589!-- Here the FORMATs start
1590
1591 99 FORMAT (1X,78('-'))
1592100 FORMAT (/1X,'***************************',9X,42('-')/        &
1593            1X,'* ',A,' *',9X,A/                               &
1594            1X,'***************************',9X,42('-'))
1595101 FORMAT (37X,'coupled run using MPI-',I1,': ',A/ &
1596            37X,42('-'))
1597102 FORMAT (/' Date:              ',A8,9X,'Run:       ',A20/      &
1598            ' Time:              ',A8,9X,'Run-No.:   ',I2.2/     &
1599            ' Run on host:     ',A10)
1600#if defined( __parallel )
1601103 FORMAT (' Number of PEs:',8X,I5,9X,'Processor grid (x,y): (',I3,',',I3, &
1602              ')',1X,A)
1603104 FORMAT (' Number of PEs:',8X,I5,9X,'Tasks:',I4,'   threads per task:',I4/ &
1604              37X,'Processor grid (x,y): (',I3,',',I3,')',1X,A)
1605105 FORMAT (37X,'One additional PE is used to handle'/37X,'the dvrp output!')
1606106 FORMAT (37X,'A 1d-decomposition along x is forced'/ &
1607            37X,'because the job is running on an SMP-cluster')
1608107 FORMAT (37X,'A 1d-decomposition along ',A,' is used')
1609108 FORMAT (37X,'Max. # of parallel I/O streams is ',I5)
1610#endif
1611110 FORMAT (/' Numerical Schemes:'/ &
1612             ' -----------------'/)
1613111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1614112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1615            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1616113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1617                  ' or Upstream')
1618116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1619                  ' or Upstream')
1620118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1621119 FORMAT (' --> Galilei-Transform applied to horizontal advection', &
1622            '     Translation velocity = ',A/ &
1623            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1624122 FORMAT (' --> Time differencing scheme: ',A)
1625123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1626            '     maximum damping coefficient: ',F5.3, ' 1/s')
1627129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1628130 FORMAT (' --> Additional prognostic equation for the total water content')
1629131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1630                  F6.2, ' K assumed')
1631132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
1632            '     effective emissivity scheme')
1633133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
1634134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1635135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1636                  A,'-cycle)'/ &
1637            '     number of grid levels:                   ',I2/ &
1638            '     Gauss-Seidel red/black iterations:       ',I2)
1639136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1640                  I3,')')
1641137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1642            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1643                  I3,')'/ &
1644            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1645                  I3,')')
1646138 FORMAT ('     Using hybrid version for 1d-domain-decomposition')
1647139 FORMAT (' --> Loop optimization method: ',A)
1648140 FORMAT ('     maximum residual allowed:                ',E10.3)
1649141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1650142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1651                  'step')
1652143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1653                  'kinetic energy')
1654144 FORMAT ('     masking method is used')
1655150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1656                  'conserved'/ &
1657            '     using the ',A,' mode')
1658151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1659152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1660           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1661           /'     starting from dp_level_b =', F8.3, 'm', A /)
1662153 FORMAT (' --> Large-scale vertical motion is used in the ', &
1663                  'prognostic equation for')
1664154 FORMAT ('     the potential temperature')
1665200 FORMAT (//' Run time and time step information:'/ &
1666             ' ----------------------------------'/)
1667201 FORMAT ( ' Timestep:          variable     maximum value: ',F6.3,' s', &
1668             '    CFL-factor: ',F4.2)
1669202 FORMAT ( ' Timestep:       dt = ',F6.3,' s'/)
1670203 FORMAT ( ' Start time:       ',F9.3,' s'/ &
1671             ' End time:         ',F9.3,' s')
1672204 FORMAT ( A,F9.3,' s')
1673205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
1674206 FORMAT (/' Time reached:     ',F9.3,' s'/ &
1675             ' CPU-time used:    ',F9.3,' s     per timestep:               ', &
1676               '  ',F9.3,' s'/                                                 &
1677             '                                   per second of simulated tim', &
1678               'e: ',F9.3,' s')
1679207 FORMAT ( A/' Coupling start time:',F9.3,' s')
1680250 FORMAT (//' Computational grid and domain size:'/ &
1681              ' ----------------------------------'// &
1682              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1683              ' m    dz =    ',F7.3,' m'/ &
1684              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1685              ' m  z(u) = ',F10.3,' m'/)
1686252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1687              ' factor: ',F5.3/ &
1688            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1689254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1690            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1691260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1692             ' degrees')
1693270 FORMAT (//' Topography informations:'/ &
1694              ' -----------------------'// &
1695              1X,'Topography: ',A)
1696271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1697              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1698                ' / ',I4)
1699272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1700              ' direction' / &
1701              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1702              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1703278 FORMAT (' Topography grid definition convention:'/ &
1704            ' cell edge (staggered grid points'/  &
1705            ' (u in x-direction, v in y-direction))' /)
1706279 FORMAT (' Topography grid definition convention:'/ &
1707            ' cell center (scalar grid points)' /)
1708280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1709              ' ------------------------------'// &
1710              ' Canopy mode: ', A / &
1711              ' Canopy top: ',I4 / &
1712              ' Leaf drag coefficient: ',F6.2 /)
1713281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
1714              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1715282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1716283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
1717              ' Height:              ',A,'  m'/ &
1718              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1719              ' Gradient:            ',A,'  m**2/m**4'/ &
1720              ' Gridpoint:           ',A)
1721               
1722300 FORMAT (//' Boundary conditions:'/ &
1723             ' -------------------'// &
1724             '                     p                    uv             ', &
1725             '                   pt'// &
1726             ' B. bound.: ',A/ &
1727             ' T. bound.: ',A)
1728301 FORMAT (/'                     ',A// &
1729             ' B. bound.: ',A/ &
1730             ' T. bound.: ',A)
1731303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1732304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1733305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1734               'computational u,v-level:'// &
1735             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1736             ' m   kappa = ',F4.2/ &
1737             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1738306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1739307 FORMAT ('       Heatflux has a random normal distribution')
1740308 FORMAT ('       Predefined surface temperature')
1741309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1742310 FORMAT (//'    1D-Model:'// &
1743             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1744311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1745312 FORMAT ('       Predefined surface humidity')
1746313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1747314 FORMAT ('       Predefined scalar value at the surface')
1748315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
1749316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1750                    'atmosphere model')
1751317 FORMAT (//' Lateral boundaries:'/ &
1752            '       left/right:  ',A/    &
1753            '       north/south: ',A)
1754318 FORMAT (/'       pt damping layer width = ',F7.2,' m, pt ', &
1755                    'damping factor = ',F6.4)
1756319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1757            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1758            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1759320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1760            '                                          v: ',F9.6,' m**2/s**2')
1761325 FORMAT (//' List output:'/ &
1762             ' -----------'//  &
1763            '    1D-Profiles:'/    &
1764            '       Output every             ',F8.2,' s')
1765326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1766            '       Averaging input every    ',F8.2,' s')
1767330 FORMAT (//' Data output:'/ &
1768             ' -----------'/)
1769331 FORMAT (/'    1D-Profiles:')
1770332 FORMAT (/'       ',A)
1771333 FORMAT ('       Output every             ',F8.2,' s',/ &
1772            '       Time averaged over       ',F8.2,' s'/ &
1773            '       Averaging input every    ',F8.2,' s')
1774334 FORMAT (/'    2D-Arrays',A,':')
1775335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1776            '       Output every             ',F8.2,' s  ',A/ &
1777            '       Cross sections at ',A1,' = ',A/ &
1778            '       scalar-coordinates:   ',A,' m'/)
1779336 FORMAT (/'    3D-Arrays',A,':')
1780337 FORMAT (/'       Arrays: ',A/ &
1781            '       Output every             ',F8.2,' s  ',A/ &
1782            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1783338 FORMAT ('       Compressed data output'/ &
1784            '       Decimal precision: ',A/)
1785339 FORMAT ('       No output during initial ',F8.2,' s')
1786340 FORMAT (/'    Time series:')
1787341 FORMAT ('       Output every             ',F8.2,' s'/)
1788342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1789            '       Output every             ',F8.2,' s  ',A/ &
1790            '       Time averaged over       ',F8.2,' s'/ &
1791            '       Averaging input every    ',F8.2,' s'/ &
1792            '       Cross sections at ',A1,' = ',A/ &
1793            '       scalar-coordinates:   ',A,' m'/)
1794343 FORMAT (/'       Arrays: ',A/ &
1795            '       Output every             ',F8.2,' s  ',A/ &
1796            '       Time averaged over       ',F8.2,' s'/ &
1797            '       Averaging input every    ',F8.2,' s'/ &
1798            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1799344 FORMAT ('       Output format: ',A/)
1800345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1801            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1802            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1803            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1804346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1805347 FORMAT ('       Variables: ',A/ &
1806            '       Output every             ',F8.2,' s')
1807348 FORMAT ('       Variables: ',A/ &
1808            '       Output every             ',F8.2,' s'/ &
1809            '       Time averaged over       ',F8.2,' s'/ &
1810            '       Averaging input every    ',F8.2,' s')
1811349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1812            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1813            13('       ',8(F8.2,',')/) )
1814350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1815            'all gridpoints along ',A,'-direction (default).' )
1816351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1817            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1818            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1819#if defined( __dvrp_graphics )
1820360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
1821            '       Output every      ',F7.1,' s'/ &
1822            '       Output mode:      ',A/ &
1823            '       Host / User:      ',A,' / ',A/ &
1824            '       Directory:        ',A// &
1825            '       The sequence contains:')
1826361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
1827            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1828362 FORMAT (/'       Slicer plane ',A/ &
1829            '       Slicer limits: [',F6.2,',',F6.2,']')
1830363 FORMAT (/'       Particles'/ &
1831            '          particle size:  ',F7.2,' m')
1832364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
1833                       F6.2,',',F6.2,']')
1834365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
1835            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
1836                     ')'/ &
1837            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
1838            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
1839366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
1840367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
1841#endif
1842#if defined( __spectra )
1843370 FORMAT ('    Spectra:')
1844371 FORMAT ('       Output every ',F7.1,' s'/)
1845372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
1846            '       Directions: ', 10(A5,',')/                         &
1847            '       height levels  k = ', 20(I3,',')/                  &
1848            '                          ', 20(I3,',')/                  &
1849            '                          ', 20(I3,',')/                  &
1850            '                          ', 20(I3,',')/                  &
1851            '                          ', 19(I3,','),I3,'.'/           &
1852            '       height levels selected for standard plot:'/        &
1853            '                      k = ', 20(I3,',')/                  &
1854            '                          ', 20(I3,',')/                  &
1855            '                          ', 20(I3,',')/                  &
1856            '                          ', 20(I3,',')/                  &
1857            '                          ', 19(I3,','),I3,'.'/           &
1858            '       Time averaged over ', F7.1, ' s,' /                &
1859            '       Profiles for the time averaging are taken every ', &
1860                    F6.1,' s')
1861#endif
1862400 FORMAT (//' Physical quantities:'/ &
1863              ' -------------------'/)
1864410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
1865            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
1866            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
1867            '                            f*    = ',F9.6,' 1/s')
1868411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
1869412 FORMAT (/'    Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1870413 FORMAT (/'    Reference temperature in buoyancy terms: ',F8.4,' K')
1871415 FORMAT (/'    Cloud physics parameters:'/ &
1872             '    ------------------------'/)
1873416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
1874            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
1875            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
1876            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
1877            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
1878420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1879            '       Height:        ',A,'  m'/ &
1880            '       Temperature:   ',A,'  K'/ &
1881            '       Gradient:      ',A,'  K/100m'/ &
1882            '       Gridpoint:     ',A)
1883421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1884            '       Height:      ',A,'  m'/ &
1885            '       Humidity:    ',A,'  kg/kg'/ &
1886            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1887            '       Gridpoint:   ',A)
1888422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1889            '       Height:                  ',A,'  m'/ &
1890            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1891            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1892            '       Gridpoint:               ',A)
1893423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1894            '       Height:      ',A,'  m'/ &
1895            '       ug:          ',A,'  m/s'/ &
1896            '       Gradient:    ',A,'  1/100s'/ &
1897            '       Gridpoint:   ',A)
1898424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1899            '       Height:      ',A,'  m'/ &
1900            '       vg:          ',A,'  m/s'/ &
1901            '       Gradient:    ',A,'  1/100s'/ &
1902            '       Gridpoint:   ',A)
1903425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1904            '       Height:     ',A,'  m'/ &
1905            '       Salinity:   ',A,'  psu'/ &
1906            '       Gradient:   ',A,'  psu/100m'/ &
1907            '       Gridpoint:  ',A)
1908426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1909            '       Height:      ',A,'  m'/ &
1910            '       w_subs:      ',A,'  m/s'/ &
1911            '       Gradient:    ',A,'  (m/s)/100m'/ &
1912            '       Gridpoint:   ',A)
1913427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1914                  ' profiles')
1915430 FORMAT (//' Cloud physics quantities / methods:'/ &
1916              ' ----------------------------------'/)
1917431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
1918                 'on)')
1919432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
1920            '    total water content is used.'/ &
1921            '    Condensation is parameterized via 0% - or 100% scheme.')
1922433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
1923                 'icle model')
1924434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
1925                 ' droplets < 1.0E-6 m')
1926435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
1927436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
1928                    'are used'/ &
1929            '          number of radius classes:       ',I3,'    interval ', &
1930                       '[1.0E-6,2.0E-4] m'/ &
1931            '          number of dissipation classes:   ',I2,'    interval ', &
1932                       '[0,1000] cm**2/s**3')
1933437 FORMAT ('    Droplet collision is switched off')
1934450 FORMAT (//' LES / Turbulence quantities:'/ &
1935              ' ---------------------------'/)
1936451 FORMAT ('    Diffusion coefficients are constant:'/ &
1937            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1938452 FORMAT ('    Mixing length is limited to the Prandtl mixing lenth.')
1939453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
1940454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1941455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
1942470 FORMAT (//' Actions during the simulation:'/ &
1943              ' -----------------------------'/)
1944471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1945            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
1946            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1947            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1948472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1949                 ' to i/j =',I4)
1950473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1951                 1X,F5.3, ' m**2/s**2')
1952474 FORMAT ('    Random number generator used    : ',A/)
1953475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1954                 'respectively, if'/ &
1955            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1956                 ' 3D-simulation'/)
1957476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1958                 'respectively, if the'/ &
1959            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1960                 ' the 3D-simulation'/)
1961477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1962                 'respectively, if the'/ &
1963            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1964                 ' the 3D-simulation'/)
1965480 FORMAT ('    Particles:'/ &
1966            '    ---------'// &
1967            '       Particle advection is active (switched on at t = ', F7.1, &
1968                    ' s)'/ &
1969            '       Start of new particle generations every  ',F6.1,' s'/ &
1970            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
1971            '                            bottom:     ', A, ' top:         ', A/&
1972            '       Maximum particle age:                 ',F9.1,' s'/ &
1973            '       Advection stopped at t = ',F9.1,' s'/ &
1974            '       Particles are sorted every ',F9.1,' s'/)
1975481 FORMAT ('       Particles have random start positions'/)
1976482 FORMAT ('          Particles are advected only horizontally'/)
1977483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
1978484 FORMAT ('            Number of tails of the total domain: ',I10/ &
1979            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
1980            '            Maximum age of the end of the tail:  ',F8.2,' s')
1981485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
1982486 FORMAT ('       Particle statistics are written on file'/)
1983487 FORMAT ('       Number of particle groups: ',I2/)
1984488 FORMAT ('       SGS velocity components are used for particle advection'/ &
1985            '          minimum timestep for advection: ', F7.5/)
1986489 FORMAT ('       Number of particles simultaneously released at each ', &
1987                    'point: ', I5/)
1988490 FORMAT ('       Particle group ',I2,':'/ &
1989            '          Particle radius: ',E10.3, 'm')
1990491 FORMAT ('          Particle inertia is activated'/ &
1991            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
1992492 FORMAT ('          Particles are advected only passively (no inertia)'/)
1993493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
1994            '                                         y:',F8.1,' - ',F8.1,' m'/&
1995            '                                         z:',F8.1,' - ',F8.1,' m'/&
1996            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
1997                       ' m  dz = ',F8.1,' m'/)
1998494 FORMAT ('       Output of particle time series in NetCDF format every ', &
1999                    F8.2,' s'/)
2000495 FORMAT ('       Number of particles in total domain: ',I10/)
2001500 FORMAT (//' 1D-Model parameters:'/                           &
2002              ' -------------------'//                           &
2003            '    Simulation time:                   ',F8.1,' s'/ &
2004            '    Run-controll output every:         ',F8.1,' s'/ &
2005            '    Vertical profile output every:     ',F8.1,' s'/ &
2006            '    Mixing length calculation:         ',A/         &
2007            '    Dissipation calculation:           ',A/)
2008502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
2009503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2010504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
2011
2012
2013 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.