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

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

leapfrog timestep scheme and upstream-spline advection scheme completely removed from the code,
reading of dt_fixed from restart file removed

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