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

Last change on this file since 1485 was 1485, checked in by kanani, 9 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 85.0 KB
RevLine 
[1]1 SUBROUTINE header
2
[1036]3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[1310]17! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]18!--------------------------------------------------------------------------------!
19!
[254]20! Current revisions:
[1]21! -----------------
[1485]22!
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 1485 2014-10-21 11:09:54Z kanani $
27!
28! 1484 2014-10-21 10:53:05Z kanani
[1484]29! Changes due to new module structure of the plant canopy model:
30!   module plant_canopy_model_mod and output for new canopy model parameters
31!   (alpha_lad, beta_lad, lai_beta,...) added,
32!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
33!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
34!   learde renamed leaf_area_density.
35! Bugfix: DO-WHILE-loop for lad header information additionally restricted
36! by maximum number of gradient levels (currently 10)
[1483]37!
38! 1482 2014-10-18 12:34:45Z raasch
39! information about calculated or predefined virtual processor topology adjusted
40!
[1469]41! 1468 2014-09-24 14:06:57Z maronga
42! Adapted for use on up to 6-digit processor cores
43!
[1430]44! 1429 2014-07-15 12:53:45Z knoop
45! header exended to provide ensemble_member_nr if specified
46!
[1377]47! 1376 2014-04-26 11:21:22Z boeske
48! Correction of typos
49!
[1366]50! 1365 2014-04-22 15:03:56Z boeske
51! New section 'Large scale forcing and nudging':
52! output of large scale forcing and nudging information,
53! new section for initial profiles created
54!
[1360]55! 1359 2014-04-11 17:15:14Z hoffmann
56! dt_sort_particles removed
57!
[1354]58! 1353 2014-04-08 15:21:23Z heinze
59! REAL constants provided with KIND-attribute
60!
[1329]61! 1327 2014-03-21 11:00:16Z raasch
62! parts concerning iso2d and avs output removed,
63! -netcdf output queries
64!
[1325]65! 1324 2014-03-21 09:13:16Z suehring
66! Bugfix: module spectrum added
67!
[1323]68! 1322 2014-03-20 16:38:49Z raasch
69! REAL functions provided with KIND-attribute,
70! some REAL constants defined as wp-kind
71!
[1321]72! 1320 2014-03-20 08:40:49Z raasch
[1320]73! ONLY-attribute added to USE-statements,
74! kind-parameters added to all INTEGER and REAL declaration statements,
75! kinds are defined in new module kinds,
76! revision history before 2012 removed,
77! comment fields (!:) to be used for variable explanations added to
78! all variable declaration statements
[1321]79!
[1309]80! 1308 2014-03-13 14:58:42Z fricke
81! output of the fixed number of output time levels
82! output_format adjusted for masked data if netcdf_data_format > 5
83!
[1300]84! 1299 2014-03-06 13:15:21Z heinze
85! output for using large_scale subsidence in combination
86! with large_scale_forcing
87! reformatting, more detailed explanations
88!
[1242]89! 1241 2013-10-30 11:36:58Z heinze
90! output for nudging + large scale forcing from external file
91!
[1217]92! 1216 2013-08-26 09:31:42Z raasch
93! output for transpose_compute_overlap
94!
[1213]95! 1212 2013-08-15 08:46:27Z raasch
96! output for poisfft_hybrid removed
97!
[1182]98! 1179 2013-06-14 05:57:58Z raasch
99! output of reference_state, use_reference renamed use_single_reference_value
100!
[1160]101! 1159 2013-05-21 11:58:22Z fricke
102! +use_cmax
103!
[1116]104! 1115 2013-03-26 18:16:16Z hoffmann
105! descriptions for Seifert-Beheng-cloud-physics-scheme added
106!
[1112]107! 1111 2013-03-08 23:54:10Z raasch
108! output of accelerator board information
109! ibc_p_b = 2 removed
110!
[1109]111! 1108 2013-03-05 07:03:32Z raasch
112! bugfix for r1106
113!
[1107]114! 1106 2013-03-04 05:31:38Z raasch
115! some format changes for coupled runs
116!
[1093]117! 1092 2013-02-02 11:24:22Z raasch
118! unused variables removed
119!
[1037]120! 1036 2012-10-22 13:43:42Z raasch
121! code put under GPL (PALM 3.9)
122!
[1035]123! 1031 2012-10-19 14:35:30Z raasch
124! output of netCDF data format modified
125!
[1017]126! 1015 2012-09-27 09:23:24Z raasch
[1365]127! output of Adjustment of mixing length to the Prandtl mixing length at first
[1017]128! grid point above ground removed
129!
[1004]130! 1003 2012-09-14 14:35:53Z raasch
131! output of information about equal/unequal subdomain size removed
132!
[1002]133! 1001 2012-09-13 14:08:46Z raasch
134! all actions concerning leapfrog- and upstream-spline-scheme removed
135!
[979]136! 978 2012-08-09 08:28:32Z fricke
137! -km_damp_max, outflow_damping_width
138! +pt_damping_factor, pt_damping_width
139! +z0h
140!
[965]141! 964 2012-07-26 09:14:24Z raasch
142! output of profil-related quantities removed
143!
[941]144! 940 2012-07-09 14:31:00Z raasch
145! Output in case of simulations for pure neutral stratification (no pt-equation
146! solved)
147!
[928]148! 927 2012-06-06 19:15:04Z raasch
149! output of masking_method for mg-solver
150!
[869]151! 868 2012-03-28 12:21:07Z raasch
152! translation velocity in Galilean transformation changed to 0.6 * ug
153!
[834]154! 833 2012-02-22 08:55:55Z maronga
155! Adjusted format for leaf area density
156!
[829]157! 828 2012-02-21 12:00:36Z raasch
158! output of dissipation_classes + radius_classes
159!
[826]160! 825 2012-02-19 03:03:44Z raasch
161! Output of cloud physics parameters/quantities complemented and restructured
162!
[1]163! Revision 1.1  1997/08/11 06:17:20  raasch
164! Initial revision
165!
166!
167! Description:
168! ------------
169! Writing a header with all important informations about the actual run.
170! This subroutine is called three times, two times at the beginning
171! (writing information on files RUN_CONTROL and HEADER) and one time at the
172! end of the run, then writing additional information about CPU-usage on file
173! header.
[411]174!-----------------------------------------------------------------------------!
[1]175
[1320]176    USE arrays_3d,                                                             &
[1484]177        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
[1320]178       
[1]179    USE control_parameters
[1320]180       
181    USE cloud_parameters,                                                      &
182        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
183               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
184       
185    USE cpulog,                                                                &
186        ONLY:  log_point_s
187       
188    USE dvrp_variables,                                                        &
189        ONLY:  use_seperate_pe_for_dvrp_output
190       
191    USE grid_variables,                                                        &
192        ONLY:  dx, dy
193       
194    USE indices,                                                               &
195        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
196               nys_mg, nzt, nzt_mg
197       
198    USE kinds
199   
200    USE model_1d,                                                              &
201        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
202       
203    USE particle_attributes,                                                   &
204        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
205               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
[1359]206               dt_write_particle_data, end_time_prel,                          &
[1320]207               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
208               minimum_tailpoint_distance, number_of_particle_groups,          &
209               particle_advection, particle_advection_start,                   &
210               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
211               pst, radius, radius_classes, random_start_position,             &
212               total_number_of_particles, use_particle_tails,                  &
213               use_sgs_for_particles, total_number_of_tails,                   &
214               vertical_particle_advection, write_particle_statistics
215       
[1]216    USE pegrid
[1484]217
218    USE plant_canopy_model_mod,                                                &
219        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
220               canopy_mode, cthf, lad, lad_surface, lad_vertical_gradient,     &
221               lad_vertical_gradient_level, lad_vertical_gradient_level_ind,   &
222               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
223               plant_canopy
[1324]224   
225    USE spectrum,                                                              &
226        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
227               spectra_direction
[1]228
229    IMPLICIT NONE
230
[1320]231    CHARACTER (LEN=1)  ::  prec                !:
232   
233    CHARACTER (LEN=2)  ::  do2d_mode           !:
234   
235    CHARACTER (LEN=5)  ::  section_chr         !:
236   
237    CHARACTER (LEN=10) ::  coor_chr            !:
238    CHARACTER (LEN=10) ::  host_chr            !:
239   
240    CHARACTER (LEN=16) ::  begin_chr           !:
241   
242    CHARACTER (LEN=26) ::  ver_rev             !:
243   
244    CHARACTER (LEN=40) ::  output_format       !:
245   
246    CHARACTER (LEN=70) ::  char1               !:
247    CHARACTER (LEN=70) ::  char2               !:
248    CHARACTER (LEN=70) ::  dopr_chr            !:
249    CHARACTER (LEN=70) ::  do2d_xy             !:
250    CHARACTER (LEN=70) ::  do2d_xz             !:
251    CHARACTER (LEN=70) ::  do2d_yz             !:
252    CHARACTER (LEN=70) ::  do3d_chr            !:
253    CHARACTER (LEN=70) ::  domask_chr          !:
254    CHARACTER (LEN=70) ::  run_classification  !:
255   
256    CHARACTER (LEN=85) ::  roben               !:
257    CHARACTER (LEN=85) ::  runten              !:
258   
259    CHARACTER (LEN=86) ::  coordinates         !:
260    CHARACTER (LEN=86) ::  gradients           !:
[1484]261    CHARACTER (LEN=86) ::  leaf_area_density   !:
[1320]262    CHARACTER (LEN=86) ::  slices              !:
263    CHARACTER (LEN=86) ::  temperatures        !:
264    CHARACTER (LEN=86) ::  ugcomponent         !:
265    CHARACTER (LEN=86) ::  vgcomponent         !:
[1]266
[1320]267    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
[410]268
[1320]269    INTEGER(iwp) ::  av        !:
270    INTEGER(iwp) ::  bh        !:
271    INTEGER(iwp) ::  blx       !:
272    INTEGER(iwp) ::  bly       !:
273    INTEGER(iwp) ::  bxl       !:
274    INTEGER(iwp) ::  bxr       !:
275    INTEGER(iwp) ::  byn       !:
276    INTEGER(iwp) ::  bys       !:
277    INTEGER(iwp) ::  ch        !:
278    INTEGER(iwp) ::  count     !:
279    INTEGER(iwp) ::  cwx       !:
280    INTEGER(iwp) ::  cwy       !:
281    INTEGER(iwp) ::  cxl       !:
282    INTEGER(iwp) ::  cxr       !:
283    INTEGER(iwp) ::  cyn       !:
284    INTEGER(iwp) ::  cys       !:
285    INTEGER(iwp) ::  dim       !:
286    INTEGER(iwp) ::  i         !:
287    INTEGER(iwp) ::  io        !:
288    INTEGER(iwp) ::  j         !:
[1484]289    INTEGER(iwp) ::  k         !:
[1320]290    INTEGER(iwp) ::  l         !:
291    INTEGER(iwp) ::  ll        !:
292    INTEGER(iwp) ::  mpi_type  !:
293   
[1484]294    REAL(wp) ::  canopy_height                    !: canopy height (in m)
[1320]295    REAL(wp) ::  cpuseconds_per_simulated_second  !:
[1]296
297!
298!-- Open the output file. At the end of the simulation, output is directed
299!-- to unit 19.
300    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
301         .NOT. simulated_time_at_begin /= simulated_time )  THEN
302       io = 15   !  header output on file RUN_CONTROL
303    ELSE
304       io = 19   !  header output on file HEADER
305    ENDIF
306    CALL check_open( io )
307
308!
309!-- At the end of the run, output file (HEADER) will be rewritten with
310!-- new informations
311    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
312
313!
314!-- Determine kind of model run
315    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
316       run_classification = '3D - restart run'
[328]317    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
318       run_classification = '3D - run with cyclic fill of 3D - prerun data'
[147]319    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
320       run_classification = '3D - run without 1D - prerun'
[197]321    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
[147]322       run_classification = '3D - run with 1D - prerun'
[197]323    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
324       run_classification = '3D - run initialized by user'
[1]325    ELSE
[254]326       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
327       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
[1]328    ENDIF
[97]329    IF ( ocean )  THEN
330       run_classification = 'ocean - ' // run_classification
331    ELSE
332       run_classification = 'atmosphere - ' // run_classification
333    ENDIF
[1]334
335!
336!-- Run-identification, date, time, host
337    host_chr = host(1:10)
[75]338    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
[102]339    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
[291]340    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
341#if defined( __mpi2 )
342       mpi_type = 2
343#else
344       mpi_type = 1
345#endif
346       WRITE ( io, 101 )  mpi_type, coupling_mode
347    ENDIF
[1108]348#if defined( __parallel )
[1353]349    IF ( coupling_start_time /= 0.0_wp )  THEN
[1106]350       IF ( coupling_start_time > simulated_time_at_begin )  THEN
351          WRITE ( io, 109 )
352       ELSE
353          WRITE ( io, 114 )
354       ENDIF
355    ENDIF
[1108]356#endif
[1429]357    IF ( ensemble_member_nr /= 0 )  THEN
358       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
359                       ADJUSTR( host_chr ), ensemble_member_nr
360    ELSE
361       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
[102]362                       ADJUSTR( host_chr )
[1429]363    ENDIF
[1]364#if defined( __parallel )
[1482]365    IF ( npex == -1  .AND.  npey == -1 )  THEN
[1]366       char1 = 'calculated'
367    ELSE
368       char1 = 'predefined'
369    ENDIF
370    IF ( threads_per_task == 1 )  THEN
[102]371       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
[1]372    ELSE
[102]373       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
[1]374                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
375    ENDIF
[1111]376    IF ( num_acc_per_node /= 0 )  WRITE ( io, 117 )  num_acc_per_node   
[1]377    IF ( ( host(1:3) == 'ibm'  .OR.  host(1:3) == 'nec'  .OR.    &
378           host(1:2) == 'lc'   .OR.  host(1:3) == 'dec' )  .AND. &
379         npex == -1  .AND.  pdims(2) == 1 )                      &
380    THEN
[102]381       WRITE ( io, 106 )
[1]382    ELSEIF ( pdims(2) == 1 )  THEN
[102]383       WRITE ( io, 107 )  'x'
[1]384    ELSEIF ( pdims(1) == 1 )  THEN
[102]385       WRITE ( io, 107 )  'y'
[1]386    ENDIF
[102]387    IF ( use_seperate_pe_for_dvrp_output )  WRITE ( io, 105 )
[759]388    IF ( numprocs /= maximum_parallel_io_streams )  THEN
389       WRITE ( io, 108 )  maximum_parallel_io_streams
390    ENDIF
[1111]391#else
392    IF ( num_acc_per_node /= 0 )  WRITE ( io, 120 )  num_acc_per_node
[1]393#endif
394    WRITE ( io, 99 )
395
396!
397!-- Numerical schemes
398    WRITE ( io, 110 )
399    IF ( psolver(1:7) == 'poisfft' )  THEN
400       WRITE ( io, 111 )  TRIM( fft_method )
[1216]401       IF ( transpose_compute_overlap )  WRITE( io, 115 )
[1]402    ELSEIF ( psolver == 'sor' )  THEN
403       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
404    ELSEIF ( psolver == 'multigrid' )  THEN
405       WRITE ( io, 135 )  cycle_mg, maximum_grid_level, ngsrb
406       IF ( mg_cycles == -1 )  THEN
407          WRITE ( io, 140 )  residual_limit
408       ELSE
409          WRITE ( io, 141 )  mg_cycles
410       ENDIF
411       IF ( mg_switch_to_pe0_level == 0 )  THEN
412          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
413                             nzt_mg(1)
[197]414       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
[1]415          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
416                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
417                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
418                             nzt_mg(mg_switch_to_pe0_level),    &
419                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
420                             nzt_mg(1)
421       ENDIF
[927]422       IF ( masking_method )  WRITE ( io, 144 )
[1]423    ENDIF
424    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
425    THEN
426       WRITE ( io, 142 )
427    ENDIF
428
429    IF ( momentum_advec == 'pw-scheme' )  THEN
430       WRITE ( io, 113 )
[1299]431    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
[667]432       WRITE ( io, 503 )
[1]433    ENDIF
434    IF ( scalar_advec == 'pw-scheme' )  THEN
435       WRITE ( io, 116 )
[667]436    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
437       WRITE ( io, 504 )
[1]438    ELSE
439       WRITE ( io, 118 )
440    ENDIF
[63]441
442    WRITE ( io, 139 )  TRIM( loop_optimization )
443
[1]444    IF ( galilei_transformation )  THEN
445       IF ( use_ug_for_galilei_tr )  THEN
[868]446          char1 = '0.6 * geostrophic wind'
[1]447       ELSE
448          char1 = 'mean wind in model domain'
449       ENDIF
450       IF ( simulated_time_at_begin == simulated_time )  THEN
451          char2 = 'at the start of the run'
452       ELSE
453          char2 = 'at the end of the run'
454       ENDIF
[1353]455       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
456                          advected_distance_x/1000.0_wp,                       &
457                          advected_distance_y/1000.0_wp
[1]458    ENDIF
[1001]459    WRITE ( io, 122 )  timestep_scheme
[87]460    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
[1353]461    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
[108]462       IF ( .NOT. ocean )  THEN
463          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
464               rayleigh_damping_factor
465       ELSE
466          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
467               rayleigh_damping_factor
468       ENDIF
[1]469    ENDIF
[940]470    IF ( neutral )  WRITE ( io, 131 )  pt_surface
[75]471    IF ( humidity )  THEN
[1]472       IF ( .NOT. cloud_physics )  THEN
473          WRITE ( io, 129 )
474       ELSE
475          WRITE ( io, 130 )
476       ENDIF
477    ENDIF
478    IF ( passive_scalar )  WRITE ( io, 134 )
[240]479    IF ( conserve_volume_flow )  THEN
[241]480       WRITE ( io, 150 )  conserve_volume_flow_mode
481       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
482          WRITE ( io, 151 )  u_bulk, v_bulk
483       ENDIF
[240]484    ELSEIF ( dp_external )  THEN
485       IF ( dp_smooth )  THEN
[241]486          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
[240]487       ELSE
[241]488          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
[240]489       ENDIF
490    ENDIF
[1]491    WRITE ( io, 99 )
492
493!
494!-- Runtime and timestep informations
495    WRITE ( io, 200 )
496    IF ( .NOT. dt_fixed )  THEN
497       WRITE ( io, 201 )  dt_max, cfl_factor
498    ELSE
499       WRITE ( io, 202 )  dt
500    ENDIF
501    WRITE ( io, 203 )  simulated_time_at_begin, end_time
502
[1322]503    IF ( time_restart /= 9999999.9_wp  .AND. &
[1]504         simulated_time_at_begin == simulated_time )  THEN
[1322]505       IF ( dt_restart == 9999999.9_wp )  THEN
[1]506          WRITE ( io, 204 )  ' Restart at:       ',time_restart
507       ELSE
508          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
509       ENDIF
510    ENDIF
511
512    IF ( simulated_time_at_begin /= simulated_time )  THEN
513       i = MAX ( log_point_s(10)%counts, 1 )
[1353]514       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
515          cpuseconds_per_simulated_second = 0.0_wp
[1]516       ELSE
517          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
518                                            ( simulated_time -    &
519                                              simulated_time_at_begin )
520       ENDIF
[1322]521       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
522                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
[1]523                          cpuseconds_per_simulated_second
[1322]524       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
525          IF ( dt_restart == 9999999.9_wp )  THEN
[1106]526             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
[1]527          ELSE
[1106]528             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
[1]529          ENDIF
530       ENDIF
531    ENDIF
532
[1324]533
[1]534!
[291]535!-- Start time for coupled runs, if independent precursor runs for atmosphere
[1106]536!-- and ocean are used or have been used. In this case, coupling_start_time
537!-- defines the time when the coupling is switched on.
[1353]538    IF ( coupling_start_time /= 0.0_wp )  THEN
[1106]539       WRITE ( io, 207 )  coupling_start_time
[291]540    ENDIF
541
542!
[1]543!-- Computational grid
[94]544    IF ( .NOT. ocean )  THEN
545       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
546       IF ( dz_stretch_level_index < nzt+1 )  THEN
547          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
548                             dz_stretch_factor, dz_max
549       ENDIF
550    ELSE
551       WRITE ( io, 250 )  dx, dy, dz, (nx+1)*dx, (ny+1)*dy, zu(0)
552       IF ( dz_stretch_level_index > 0 )  THEN
553          WRITE ( io, 252 )  dz_stretch_level, dz_stretch_level_index, &
554                             dz_stretch_factor, dz_max
555       ENDIF
[1]556    ENDIF
557    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), &
558                       MIN( nnz+2, nzt+2 )
559    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
560
561!
[1365]562!-- Large scale forcing and nudging
563    WRITE ( io, 160 )
564    IF ( large_scale_forcing )  THEN
565       WRITE ( io, 162 )
566       WRITE ( io, 163 )
567
568       IF ( large_scale_subsidence )  THEN
569          IF ( .NOT. use_subsidence_tendencies )  THEN
570             WRITE ( io, 164 )
571          ELSE
572             WRITE ( io, 165 )
573          ENDIF
574       ENDIF
575
576       IF ( bc_pt_b == 'dirichlet' )  THEN
577          WRITE ( io, 180 )
578       ELSEIF ( bc_pt_b == 'neumann' )  THEN
579          WRITE ( io, 181 )
580       ENDIF
581
582       IF ( bc_q_b == 'dirichlet' )  THEN
583          WRITE ( io, 182 )
584       ELSEIF ( bc_q_b == 'neumann' )  THEN
585          WRITE ( io, 183 )
586       ENDIF
587
588       WRITE ( io, 167 )
589       IF ( nudging )  THEN
590          WRITE ( io, 170 )
591       ENDIF
592    ELSE
593       WRITE ( io, 161 )
594       WRITE ( io, 171 )
595    ENDIF
596    IF ( large_scale_subsidence )  THEN
597       WRITE ( io, 168 )
598       WRITE ( io, 169 )
599    ENDIF
600
601!
602!-- Profile for the large scale vertial velocity
603!-- Building output strings, starting with surface value
604    IF ( large_scale_subsidence )  THEN
605       temperatures = '   0.0'
606       gradients = '------'
607       slices = '     0'
608       coordinates = '   0.0'
609       i = 1
610       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
611
612          WRITE (coor_chr,'(E10.2,7X)')  &
613                                w_subs(subs_vertical_gradient_level_i(i))
614          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
615
616          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
617          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
618
619          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
620          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
621
622          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
623          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
624
625          IF ( i == 10 )  THEN
626             EXIT
627          ELSE
628             i = i + 1
629          ENDIF
630
631       ENDDO
632
633 
634       IF ( .NOT. large_scale_forcing )  THEN
635          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
636                             TRIM( gradients ), TRIM( slices )
637       ENDIF
638
639
640    ENDIF
641
642!-- Profile of the geostrophic wind (component ug)
643!-- Building output strings
644    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
645    gradients = '------'
646    slices = '     0'
647    coordinates = '   0.0'
648    i = 1
649    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
650     
651       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
652       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
653
654       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
655       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
656
657       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
658       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
659
660       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
661       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
662
663       IF ( i == 10 )  THEN
664          EXIT
665       ELSE
666          i = i + 1
667       ENDIF
668
669    ENDDO
670
671    IF ( .NOT. large_scale_forcing )  THEN
672       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
673                          TRIM( gradients ), TRIM( slices )
674    ENDIF
675
676!-- Profile of the geostrophic wind (component vg)
677!-- Building output strings
678    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
679    gradients = '------'
680    slices = '     0'
681    coordinates = '   0.0'
682    i = 1
683    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
684
685       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
686       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
687
688       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
689       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
690
691       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
692       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
693
694       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
695       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
696
697       IF ( i == 10 )  THEN
698          EXIT
699       ELSE
700          i = i + 1
701       ENDIF
702 
703    ENDDO
704
705    IF ( .NOT. large_scale_forcing )  THEN
706       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
707                          TRIM( gradients ), TRIM( slices )
708    ENDIF
709
710!
[1]711!-- Topography
712    WRITE ( io, 270 )  topography
713    SELECT CASE ( TRIM( topography ) )
714
715       CASE ( 'flat' )
716          ! no actions necessary
717
718       CASE ( 'single_building' )
719          blx = INT( building_length_x / dx )
720          bly = INT( building_length_y / dy )
721          bh  = INT( building_height / dz )
722
[1322]723          IF ( building_wall_left == 9999999.9_wp )  THEN
[1]724             building_wall_left = ( nx + 1 - blx ) / 2 * dx
725          ENDIF
[1353]726          bxl = INT ( building_wall_left / dx + 0.5_wp )
[1]727          bxr = bxl + blx
728
[1322]729          IF ( building_wall_south == 9999999.9_wp )  THEN
[1]730             building_wall_south = ( ny + 1 - bly ) / 2 * dy
731          ENDIF
[1353]732          bys = INT ( building_wall_south / dy + 0.5_wp )
[1]733          byn = bys + bly
734
735          WRITE ( io, 271 )  building_length_x, building_length_y, &
736                             building_height, bxl, bxr, bys, byn
737
[240]738       CASE ( 'single_street_canyon' )
739          ch  = NINT( canyon_height / dz )
[1322]740          IF ( canyon_width_x /= 9999999.9_wp )  THEN
[240]741!
742!--          Street canyon in y direction
743             cwx = NINT( canyon_width_x / dx )
[1322]744             IF ( canyon_wall_left == 9999999.9_wp )  THEN
[240]745                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
746             ENDIF
747             cxl = NINT( canyon_wall_left / dx )
748             cxr = cxl + cwx
749             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
750
[1322]751          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
[240]752!
753!--          Street canyon in x direction
754             cwy = NINT( canyon_width_y / dy )
[1322]755             IF ( canyon_wall_south == 9999999.9_wp )  THEN
[240]756                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
757             ENDIF
758             cys = NINT( canyon_wall_south / dy )
759             cyn = cys + cwy
760             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
761          ENDIF
762
[1]763    END SELECT
764
[256]765    IF ( TRIM( topography ) /= 'flat' )  THEN
766       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
767          IF ( TRIM( topography ) == 'single_building' .OR.  &
768               TRIM( topography ) == 'single_street_canyon' )  THEN
769             WRITE ( io, 278 )
770          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
771             WRITE ( io, 279 )
772          ENDIF
773       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
774          WRITE ( io, 278 )
775       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
776          WRITE ( io, 279 )
777       ENDIF
778    ENDIF
779
[1299]780    IF ( plant_canopy )  THEN
[1484]781   
782       canopy_height = pch_index * dz
[138]783
[1484]784       WRITE ( io, 280 )  canopy_mode, canopy_height, pch_index,               &
785                          canopy_drag_coeff
[1299]786       IF ( passive_scalar )  THEN
[1484]787          WRITE ( io, 281 )  leaf_scalar_exch_coeff,                           &
788                             leaf_surface_conc
[153]789       ENDIF
[138]790
[1]791!
[153]792!--    Heat flux at the top of vegetation
[1484]793       WRITE ( io, 282 )  cthf
[153]794
795!
[1484]796!--    Leaf area density profile, calculated either from given vertical
797!--    gradients or from beta probability density function.
798       IF (  .NOT.  calc_beta_lad_profile )  THEN
[138]799
[1484]800!--       Building output strings, starting with surface value
801          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
802          gradients = '------'
803          slices = '     0'
804          coordinates = '   0.0'
805          i = 1
806          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i) /= -9999 )
[138]807
[1484]808             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
809             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
810 
811             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
812             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
[138]813
[1484]814             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
815             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
[138]816
[1484]817             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
818             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
[138]819
[1484]820             i = i + 1
821          ENDDO
[138]822
[1484]823          WRITE ( io, 283 )  TRIM( coordinates ), TRIM( leaf_area_density ),              &
824                             TRIM( gradients ), TRIM( slices )
[138]825
[1484]826       ELSE
827       
828          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
829          coordinates = '   0.0'
830         
831          DO  k = 1, pch_index
832
833             WRITE (coor_chr,'(F7.2)')  lad(k)
834             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
835 
836             WRITE (coor_chr,'(F7.1)')  zu(k)
837             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
838
839          ENDDO       
840
841          WRITE ( io, 284 ) TRIM( coordinates ), TRIM( leaf_area_density ), alpha_lad,    &
842                            beta_lad, lai_beta
843
844       ENDIF 
845
[138]846    ENDIF
847
[1484]848
[138]849!
[1]850!-- Boundary conditions
851    IF ( ibc_p_b == 0 )  THEN
852       runten = 'p(0)     = 0      |'
853    ELSEIF ( ibc_p_b == 1 )  THEN
854       runten = 'p(0)     = p(1)   |'
855    ENDIF
856    IF ( ibc_p_t == 0 )  THEN
857       roben  = 'p(nzt+1) = 0      |'
858    ELSE
859       roben  = 'p(nzt+1) = p(nzt) |'
860    ENDIF
861
862    IF ( ibc_uv_b == 0 )  THEN
863       runten = TRIM( runten ) // ' uv(0)     = -uv(1)                |'
864    ELSE
865       runten = TRIM( runten ) // ' uv(0)     = uv(1)                 |'
866    ENDIF
[132]867    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
868       roben  = TRIM( roben  ) // ' uv(nzt+1) = 0                     |'
869    ELSEIF ( ibc_uv_t == 0 )  THEN
[1]870       roben  = TRIM( roben  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
871    ELSE
872       roben  = TRIM( roben  ) // ' uv(nzt+1) = uv(nzt)               |'
873    ENDIF
874
875    IF ( ibc_pt_b == 0 )  THEN
876       runten = TRIM( runten ) // ' pt(0)   = pt_surface'
[102]877    ELSEIF ( ibc_pt_b == 1 )  THEN
[1]878       runten = TRIM( runten ) // ' pt(0)   = pt(1)'
[102]879    ELSEIF ( ibc_pt_b == 2 )  THEN
880       runten = TRIM( runten ) // ' pt(0) = from coupled model'
[1]881    ENDIF
882    IF ( ibc_pt_t == 0 )  THEN
[19]883       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt_top'
884    ELSEIF( ibc_pt_t == 1 )  THEN
885       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt)'
886    ELSEIF( ibc_pt_t == 2 )  THEN
887       roben  = TRIM( roben  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
[667]888
[1]889    ENDIF
890
891    WRITE ( io, 300 )  runten, roben
892
893    IF ( .NOT. constant_diffusion )  THEN
894       IF ( ibc_e_b == 1 )  THEN
895          runten = 'e(0)     = e(1)'
896       ELSE
897          runten = 'e(0)     = e(1) = (u*/0.1)**2'
898       ENDIF
899       roben = 'e(nzt+1) = e(nzt) = e(nzt-1)'
900
[97]901       WRITE ( io, 301 )  'e', runten, roben       
[1]902
903    ENDIF
904
[97]905    IF ( ocean )  THEN
906       runten = 'sa(0)    = sa(1)'
907       IF ( ibc_sa_t == 0 )  THEN
908          roben =  'sa(nzt+1) = sa_surface'
[1]909       ELSE
[97]910          roben =  'sa(nzt+1) = sa(nzt)'
[1]911       ENDIF
[97]912       WRITE ( io, 301 ) 'sa', runten, roben
913    ENDIF
[1]914
[97]915    IF ( humidity )  THEN
916       IF ( ibc_q_b == 0 )  THEN
917          runten = 'q(0)     = q_surface'
918       ELSE
919          runten = 'q(0)     = q(1)'
920       ENDIF
921       IF ( ibc_q_t == 0 )  THEN
922          roben =  'q(nzt)   = q_top'
923       ELSE
924          roben =  'q(nzt)   = q(nzt-1) + dq/dz'
925       ENDIF
926       WRITE ( io, 301 ) 'q', runten, roben
927    ENDIF
[1]928
[97]929    IF ( passive_scalar )  THEN
930       IF ( ibc_q_b == 0 )  THEN
931          runten = 's(0)     = s_surface'
932       ELSE
933          runten = 's(0)     = s(1)'
934       ENDIF
935       IF ( ibc_q_t == 0 )  THEN
936          roben =  's(nzt)   = s_top'
937       ELSE
938          roben =  's(nzt)   = s(nzt-1) + ds/dz'
939       ENDIF
940       WRITE ( io, 301 ) 's', runten, roben
[1]941    ENDIF
942
943    IF ( use_surface_fluxes )  THEN
944       WRITE ( io, 303 )
945       IF ( constant_heatflux )  THEN
[1299]946          IF ( large_scale_forcing .AND. lsf_surf )  THEN
[1241]947             WRITE ( io, 306 )  shf(0,0)
948          ELSE
949             WRITE ( io, 306 )  surface_heatflux
950          ENDIF
[1]951          IF ( random_heatflux )  WRITE ( io, 307 )
952       ENDIF
[75]953       IF ( humidity  .AND.  constant_waterflux )  THEN
[1299]954          IF ( large_scale_forcing .AND. lsf_surf )  THEN
[1241]955             WRITE ( io, 311 ) qsws(0,0)
956          ELSE
957             WRITE ( io, 311 ) surface_waterflux
958          ENDIF
[1]959       ENDIF
960       IF ( passive_scalar  .AND.  constant_waterflux )  THEN
961          WRITE ( io, 313 ) surface_waterflux
962       ENDIF
963    ENDIF
964
[19]965    IF ( use_top_fluxes )  THEN
966       WRITE ( io, 304 )
[102]967       IF ( coupling_mode == 'uncoupled' )  THEN
[151]968          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
[102]969          IF ( constant_top_heatflux )  THEN
970             WRITE ( io, 306 )  top_heatflux
971          ENDIF
972       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
973          WRITE ( io, 316 )
[19]974       ENDIF
[97]975       IF ( ocean  .AND.  constant_top_salinityflux )  THEN
976          WRITE ( io, 309 )  top_salinityflux
977       ENDIF
[75]978       IF ( humidity  .OR.  passive_scalar )  THEN
[19]979          WRITE ( io, 315 )
980       ENDIF
981    ENDIF
982
[1]983    IF ( prandtl_layer )  THEN
[978]984       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, &
985                          z0h_factor*roughness_length, kappa, &
[94]986                          rif_min, rif_max
[1]987       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
[75]988       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
[1]989          WRITE ( io, 312 )
990       ENDIF
991       IF ( passive_scalar  .AND.  .NOT. constant_waterflux )  THEN
992          WRITE ( io, 314 )
993       ENDIF
994    ELSE
995       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
996          WRITE ( io, 310 )  rif_min, rif_max
997       ENDIF
998    ENDIF
999
1000    WRITE ( io, 317 )  bc_lr, bc_ns
[707]1001    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1159]1002       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
[151]1003       IF ( turbulent_inflow )  THEN
1004          WRITE ( io, 319 )  recycling_width, recycling_plane, &
1005                             inflow_damping_height, inflow_damping_width
1006       ENDIF
[1]1007    ENDIF
1008
1009!
[1365]1010!-- Initial Profiles
1011    WRITE ( io, 321 )
1012!
1013!-- Initial wind profiles
1014    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
1015
1016!
1017!-- Initial temperature profile
1018!-- Building output strings, starting with surface temperature
1019    WRITE ( temperatures, '(F6.2)' )  pt_surface
1020    gradients = '------'
1021    slices = '     0'
1022    coordinates = '   0.0'
1023    i = 1
1024    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
1025
1026       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
1027       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1028
1029       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
1030       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1031
1032       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
1033       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1034
1035       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
1036       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1037
1038       IF ( i == 10 )  THEN
1039          EXIT
1040       ELSE
1041          i = i + 1
1042       ENDIF
1043
1044    ENDDO
1045
1046    IF ( .NOT. nudging )  THEN
1047       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
1048                          TRIM( gradients ), TRIM( slices )
1049    ELSE
1050       WRITE ( io, 428 ) 
1051    ENDIF
1052
1053!
1054!-- Initial humidity profile
1055!-- Building output strings, starting with surface humidity
1056    IF ( humidity  .OR.  passive_scalar )  THEN
1057       WRITE ( temperatures, '(E8.1)' )  q_surface
1058       gradients = '--------'
1059       slices = '       0'
1060       coordinates = '     0.0'
1061       i = 1
1062       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1063         
1064          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1065          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1066
1067          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1068          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1069         
1070          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1071          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1072         
1073          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1074          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1075
1076          IF ( i == 10 )  THEN
1077             EXIT
1078          ELSE
1079             i = i + 1
1080          ENDIF
1081
1082       ENDDO
1083
1084       IF ( humidity )  THEN
1085          IF ( .NOT. nudging )  THEN
1086             WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), &
1087                                TRIM( gradients ), TRIM( slices )
1088          ENDIF
1089       ELSE
1090          WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), &
1091                             TRIM( gradients ), TRIM( slices )
1092       ENDIF
1093    ENDIF
1094
1095!
1096!-- Initial salinity profile
1097!-- Building output strings, starting with surface salinity
1098    IF ( ocean )  THEN
1099       WRITE ( temperatures, '(F6.2)' )  sa_surface
1100       gradients = '------'
1101       slices = '     0'
1102       coordinates = '   0.0'
1103       i = 1
1104       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1105
1106          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1107          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1108
1109          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1110          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1111
1112          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1113          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1114
1115          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1116          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1117
1118          IF ( i == 10 )  THEN
1119             EXIT
1120          ELSE
1121             i = i + 1
1122          ENDIF
1123
1124       ENDDO
1125
1126       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1127                          TRIM( gradients ), TRIM( slices )
1128    ENDIF
1129
1130
1131!
[1]1132!-- Listing of 1D-profiles
[151]1133    WRITE ( io, 325 )  dt_dopr_listing
[1353]1134    IF ( averaging_interval_pr /= 0.0_wp )  THEN
[151]1135       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]1136    ENDIF
1137
1138!
1139!-- DATA output
1140    WRITE ( io, 330 )
[1353]1141    IF ( averaging_interval_pr /= 0.0_wp )  THEN
[151]1142       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
[1]1143    ENDIF
1144
1145!
1146!-- 1D-profiles
[346]1147    dopr_chr = 'Profile:'
[1]1148    IF ( dopr_n /= 0 )  THEN
1149       WRITE ( io, 331 )
1150
1151       output_format = ''
[1327]1152       output_format = output_format_netcdf
[292]1153       WRITE ( io, 344 )  output_format
[1]1154
1155       DO  i = 1, dopr_n
1156          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1157          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1158             WRITE ( io, 332 )  dopr_chr
1159             dopr_chr = '       :'
1160          ENDIF
1161       ENDDO
1162
1163       IF ( dopr_chr /= '' )  THEN
1164          WRITE ( io, 332 )  dopr_chr
1165       ENDIF
1166       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
[1353]1167       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
[1]1168    ENDIF
1169
1170!
1171!-- 2D-arrays
1172    DO  av = 0, 1
1173
1174       i = 1
1175       do2d_xy = ''
1176       do2d_xz = ''
1177       do2d_yz = ''
1178       DO  WHILE ( do2d(av,i) /= ' ' )
1179
1180          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1181          do2d_mode = do2d(av,i)(l-1:l)
1182
1183          SELECT CASE ( do2d_mode )
1184             CASE ( 'xy' )
1185                ll = LEN_TRIM( do2d_xy )
1186                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1187             CASE ( 'xz' )
1188                ll = LEN_TRIM( do2d_xz )
1189                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1190             CASE ( 'yz' )
1191                ll = LEN_TRIM( do2d_yz )
1192                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1193          END SELECT
1194
1195          i = i + 1
1196
1197       ENDDO
1198
1199       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1200              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
[1327]1201              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
[1]1202
1203          IF (  av == 0 )  THEN
1204             WRITE ( io, 334 )  ''
1205          ELSE
1206             WRITE ( io, 334 )  '(time-averaged)'
1207          ENDIF
1208
1209          IF ( do2d_at_begin )  THEN
1210             begin_chr = 'and at the start'
1211          ELSE
1212             begin_chr = ''
1213          ENDIF
1214
1215          output_format = ''
[1327]1216          output_format = output_format_netcdf
[292]1217          WRITE ( io, 344 )  output_format
[1]1218
1219          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1220             i = 1
1221             slices = '/'
1222             coordinates = '/'
1223!
1224!--          Building strings with index and coordinate informations of the
1225!--          slices
1226             DO  WHILE ( section(i,1) /= -9999 )
1227
1228                WRITE (section_chr,'(I5)')  section(i,1)
1229                section_chr = ADJUSTL( section_chr )
1230                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1231
[206]1232                IF ( section(i,1) == -1 )  THEN
[1353]1233                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
[206]1234                ELSE
1235                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1236                ENDIF
[1]1237                coor_chr = ADJUSTL( coor_chr )
1238                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1239
1240                i = i + 1
1241             ENDDO
1242             IF ( av == 0 )  THEN
1243                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1244                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1245                                   TRIM( coordinates )
[1353]1246                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
[1]1247                   WRITE ( io, 339 )  skip_time_do2d_xy
1248                ENDIF
1249             ELSE
1250                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1251                                   TRIM( begin_chr ), averaging_interval, &
1252                                   dt_averaging_input, 'k', TRIM( slices ), &
1253                                   TRIM( coordinates )
[1353]1254                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1255                   WRITE ( io, 339 )  skip_time_data_output_av
1256                ENDIF
1257             ENDIF
[1308]1258             IF ( netcdf_data_format > 4 )  THEN
1259                WRITE ( io, 352 )  ntdim_2d_xy(av)
1260             ELSE
1261                WRITE ( io, 353 )
1262             ENDIF
[1]1263          ENDIF
1264
1265          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1266             i = 1
1267             slices = '/'
1268             coordinates = '/'
1269!
1270!--          Building strings with index and coordinate informations of the
1271!--          slices
1272             DO  WHILE ( section(i,2) /= -9999 )
1273
1274                WRITE (section_chr,'(I5)')  section(i,2)
1275                section_chr = ADJUSTL( section_chr )
1276                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1277
1278                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1279                coor_chr = ADJUSTL( coor_chr )
1280                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1281
1282                i = i + 1
1283             ENDDO
1284             IF ( av == 0 )  THEN
1285                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1286                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1287                                   TRIM( coordinates )
[1353]1288                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
[1]1289                   WRITE ( io, 339 )  skip_time_do2d_xz
1290                ENDIF
1291             ELSE
1292                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1293                                   TRIM( begin_chr ), averaging_interval, &
1294                                   dt_averaging_input, 'j', TRIM( slices ), &
1295                                   TRIM( coordinates )
[1353]1296                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1297                   WRITE ( io, 339 )  skip_time_data_output_av
1298                ENDIF
1299             ENDIF
[1308]1300             IF ( netcdf_data_format > 4 )  THEN
1301                WRITE ( io, 352 )  ntdim_2d_xz(av)
1302             ELSE
1303                WRITE ( io, 353 )
1304             ENDIF
[1]1305          ENDIF
1306
1307          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1308             i = 1
1309             slices = '/'
1310             coordinates = '/'
1311!
1312!--          Building strings with index and coordinate informations of the
1313!--          slices
1314             DO  WHILE ( section(i,3) /= -9999 )
1315
1316                WRITE (section_chr,'(I5)')  section(i,3)
1317                section_chr = ADJUSTL( section_chr )
1318                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1319
1320                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1321                coor_chr = ADJUSTL( coor_chr )
1322                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1323
1324                i = i + 1
1325             ENDDO
1326             IF ( av == 0 )  THEN
1327                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1328                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1329                                   TRIM( coordinates )
[1353]1330                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
[1]1331                   WRITE ( io, 339 )  skip_time_do2d_yz
1332                ENDIF
1333             ELSE
1334                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1335                                   TRIM( begin_chr ), averaging_interval, &
1336                                   dt_averaging_input, 'i', TRIM( slices ), &
1337                                   TRIM( coordinates )
[1353]1338                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1339                   WRITE ( io, 339 )  skip_time_data_output_av
1340                ENDIF
1341             ENDIF
[1308]1342             IF ( netcdf_data_format > 4 )  THEN
1343                WRITE ( io, 352 )  ntdim_2d_yz(av)
1344             ELSE
1345                WRITE ( io, 353 )
1346             ENDIF
[1]1347          ENDIF
1348
1349       ENDIF
1350
1351    ENDDO
1352
1353!
1354!-- 3d-arrays
1355    DO  av = 0, 1
1356
1357       i = 1
1358       do3d_chr = ''
1359       DO  WHILE ( do3d(av,i) /= ' ' )
1360
1361          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1362          i = i + 1
1363
1364       ENDDO
1365
1366       IF ( do3d_chr /= '' )  THEN
1367          IF ( av == 0 )  THEN
1368             WRITE ( io, 336 )  ''
1369          ELSE
1370             WRITE ( io, 336 )  '(time-averaged)'
1371          ENDIF
1372
[1327]1373          output_format = output_format_netcdf
[292]1374          WRITE ( io, 344 )  output_format
[1]1375
1376          IF ( do3d_at_begin )  THEN
1377             begin_chr = 'and at the start'
1378          ELSE
1379             begin_chr = ''
1380          ENDIF
1381          IF ( av == 0 )  THEN
1382             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1383                                zu(nz_do3d), nz_do3d
1384          ELSE
1385             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1386                                TRIM( begin_chr ), averaging_interval, &
1387                                dt_averaging_input, zu(nz_do3d), nz_do3d
1388          ENDIF
1389
[1308]1390          IF ( netcdf_data_format > 4 )  THEN
1391             WRITE ( io, 352 )  ntdim_3d(av)
1392          ELSE
1393             WRITE ( io, 353 )
1394          ENDIF
1395
[1]1396          IF ( av == 0 )  THEN
[1353]1397             IF ( skip_time_do3d /= 0.0_wp )  THEN
[1]1398                WRITE ( io, 339 )  skip_time_do3d
1399             ENDIF
1400          ELSE
[1353]1401             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[1]1402                WRITE ( io, 339 )  skip_time_data_output_av
1403             ENDIF
1404          ENDIF
1405
1406       ENDIF
1407
1408    ENDDO
1409
1410!
[410]1411!-- masked arrays
1412    IF ( masks > 0 )  WRITE ( io, 345 )  &
1413         mask_scale_x, mask_scale_y, mask_scale_z
1414    DO  mid = 1, masks
1415       DO  av = 0, 1
1416
1417          i = 1
1418          domask_chr = ''
1419          DO  WHILE ( domask(mid,av,i) /= ' ' )
1420             domask_chr = TRIM( domask_chr ) // ' ' //  &
1421                          TRIM( domask(mid,av,i) ) // ','
1422             i = i + 1
1423          ENDDO
1424
1425          IF ( domask_chr /= '' )  THEN
1426             IF ( av == 0 )  THEN
1427                WRITE ( io, 346 )  '', mid
1428             ELSE
1429                WRITE ( io, 346 )  ' (time-averaged)', mid
1430             ENDIF
1431
[1327]1432             output_format = output_format_netcdf
[1308]1433!--          Parallel output not implemented for mask data, hence
1434!--          output_format must be adjusted.
1435             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1436             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
[410]1437             WRITE ( io, 344 )  output_format
1438
1439             IF ( av == 0 )  THEN
1440                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1441             ELSE
1442                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1443                                   averaging_interval, dt_averaging_input
1444             ENDIF
1445
1446             IF ( av == 0 )  THEN
[1353]1447                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
[410]1448                   WRITE ( io, 339 )  skip_time_domask(mid)
1449                ENDIF
1450             ELSE
[1353]1451                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
[410]1452                   WRITE ( io, 339 )  skip_time_data_output_av
1453                ENDIF
1454             ENDIF
1455!
1456!--          output locations
1457             DO  dim = 1, 3
[1353]1458                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
[410]1459                   count = 0
[1353]1460                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
[410]1461                      count = count + 1
1462                   ENDDO
1463                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1464                                      mask(mid,dim,:count)
[1353]1465                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1466                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1467                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
[410]1468                   WRITE ( io, 350 )  dir(dim), dir(dim)
[1353]1469                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
[410]1470                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1471                                      mask_loop(mid,dim,1:2)
1472                ELSE
1473                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1474                                      mask_loop(mid,dim,1:3)
1475                ENDIF
1476             ENDDO
1477          ENDIF
1478
1479       ENDDO
1480    ENDDO
1481
1482!
[1]1483!-- Timeseries
[1322]1484    IF ( dt_dots /= 9999999.9_wp )  THEN
[1]1485       WRITE ( io, 340 )
1486
[1327]1487       output_format = output_format_netcdf
[292]1488       WRITE ( io, 344 )  output_format
[1]1489       WRITE ( io, 341 )  dt_dots
1490    ENDIF
1491
1492#if defined( __dvrp_graphics )
1493!
1494!-- Dvrp-output
[1322]1495    IF ( dt_dvrp /= 9999999.9_wp )  THEN
[1]1496       WRITE ( io, 360 )  dt_dvrp, TRIM( dvrp_output ), TRIM( dvrp_host ), &
1497                          TRIM( dvrp_username ), TRIM( dvrp_directory )
1498       i = 1
1499       l = 0
[336]1500       m = 0
[1]1501       DO WHILE ( mode_dvrp(i) /= ' ' )
1502          IF ( mode_dvrp(i)(1:10) == 'isosurface' )  THEN
[130]1503             READ ( mode_dvrp(i), '(10X,I2)' )  j
[1]1504             l = l + 1
1505             IF ( do3d(0,j) /= ' ' )  THEN
[336]1506                WRITE ( io, 361 )  TRIM( do3d(0,j) ), threshold(l), &
1507                                   isosurface_color(:,l)
[1]1508             ENDIF
1509          ELSEIF ( mode_dvrp(i)(1:6) == 'slicer' )  THEN
[130]1510             READ ( mode_dvrp(i), '(6X,I2)' )  j
[336]1511             m = m + 1
1512             IF ( do2d(0,j) /= ' ' )  THEN
1513                WRITE ( io, 362 )  TRIM( do2d(0,j) ), &
1514                                   slicer_range_limits_dvrp(:,m)
1515             ENDIF
[1]1516          ELSEIF ( mode_dvrp(i)(1:9) == 'particles' )  THEN
[336]1517             WRITE ( io, 363 )  dvrp_psize
1518             IF ( particle_dvrpsize /= 'none' )  THEN
1519                WRITE ( io, 364 )  'size', TRIM( particle_dvrpsize ), &
1520                                   dvrpsize_interval
1521             ENDIF
1522             IF ( particle_color /= 'none' )  THEN
1523                WRITE ( io, 364 )  'color', TRIM( particle_color ), &
1524                                   color_interval
1525             ENDIF
[1]1526          ENDIF
1527          i = i + 1
1528       ENDDO
[237]1529
[336]1530       WRITE ( io, 365 )  groundplate_color, superelevation_x, &
1531                          superelevation_y, superelevation, clip_dvrp_l, &
1532                          clip_dvrp_r, clip_dvrp_s, clip_dvrp_n
1533
1534       IF ( TRIM( topography ) /= 'flat' )  THEN
1535          WRITE ( io, 366 )  topography_color
1536          IF ( cluster_size > 1 )  THEN
1537             WRITE ( io, 367 )  cluster_size
1538          ENDIF
[237]1539       ENDIF
1540
[1]1541    ENDIF
1542#endif
1543
1544#if defined( __spectra )
1545!
1546!-- Spectra output
[1322]1547    IF ( dt_dosp /= 9999999.9_wp )  THEN
[1]1548       WRITE ( io, 370 )
1549
[1327]1550       output_format = output_format_netcdf
[292]1551       WRITE ( io, 344 )  output_format
[1]1552       WRITE ( io, 371 )  dt_dosp
[1353]1553       IF ( skip_time_dosp /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dosp
[1]1554       WRITE ( io, 372 )  ( data_output_sp(i), i = 1,10 ),     &
1555                          ( spectra_direction(i), i = 1,10 ),  &
[189]1556                          ( comp_spectra_level(i), i = 1,100 ), &
1557                          ( plot_spectra_level(i), i = 1,100 ), &
[1]1558                          averaging_interval_sp, dt_averaging_input_pr
1559    ENDIF
1560#endif
1561
1562    WRITE ( io, 99 )
1563
1564!
1565!-- Physical quantities
1566    WRITE ( io, 400 )
1567
1568!
1569!-- Geostrophic parameters
1570    WRITE ( io, 410 )  omega, phi, f, fs
1571
1572!
1573!-- Other quantities
1574    WRITE ( io, 411 )  g
[1179]1575    WRITE ( io, 412 )  TRIM( reference_state )
1576    IF ( use_single_reference_value )  THEN
[97]1577       IF ( ocean )  THEN
[1179]1578          WRITE ( io, 413 )  prho_reference
[97]1579       ELSE
[1179]1580          WRITE ( io, 414 )  pt_reference
[97]1581       ENDIF
1582    ENDIF
[1]1583
1584!
1585!-- Cloud physics parameters
[1299]1586    IF ( cloud_physics )  THEN
[57]1587       WRITE ( io, 415 )
1588       WRITE ( io, 416 ) surface_pressure, r_d, rho_surface, cp, l_v
[1115]1589       IF ( icloud_scheme == 0 )  THEN
[1353]1590          WRITE ( io, 510 ) 1.0E-6_wp * nc_const
[1115]1591          IF ( precipitation )  WRITE ( io, 511 ) c_sedimentation
1592       ENDIF
[1]1593    ENDIF
1594
1595!
[824]1596!-- Cloud physcis parameters / quantities / numerical methods
1597    WRITE ( io, 430 )
1598    IF ( humidity .AND. .NOT. cloud_physics .AND. .NOT. cloud_droplets)  THEN
1599       WRITE ( io, 431 )
1600    ELSEIF ( humidity  .AND.  cloud_physics )  THEN
1601       WRITE ( io, 432 )
[1115]1602       IF ( radiation )  WRITE ( io, 132 )
1603       IF ( icloud_scheme == 1 )  THEN
1604          IF ( precipitation )  WRITE ( io, 133 )
1605       ELSEIF ( icloud_scheme == 0 )  THEN
1606          IF ( drizzle )  WRITE ( io, 506 )
1607          IF ( precipitation )  THEN
1608             WRITE ( io, 505 )
1609             IF ( turbulence )  WRITE ( io, 507 )
1610             IF ( ventilation_effect )  WRITE ( io, 508 )
1611             IF ( limiter_sedimentation )  WRITE ( io, 509 )
1612          ENDIF
1613       ENDIF
[824]1614    ELSEIF ( humidity  .AND.  cloud_droplets )  THEN
1615       WRITE ( io, 433 )
1616       IF ( curvature_solution_effects )  WRITE ( io, 434 )
[825]1617       IF ( collision_kernel /= 'none' )  THEN
1618          WRITE ( io, 435 )  TRIM( collision_kernel )
[828]1619          IF ( collision_kernel(6:9) == 'fast' )  THEN
1620             WRITE ( io, 436 )  radius_classes, dissipation_classes
1621          ENDIF
[825]1622       ELSE
[828]1623          WRITE ( io, 437 )
[825]1624       ENDIF
[824]1625    ENDIF
1626
1627!
[1]1628!-- LES / turbulence parameters
1629    WRITE ( io, 450 )
1630
1631!--
1632! ... LES-constants used must still be added here
1633!--
1634    IF ( constant_diffusion )  THEN
1635       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1636                          prandtl_number
1637    ENDIF
1638    IF ( .NOT. constant_diffusion)  THEN
[1353]1639       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1640       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
[1]1641       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1642    ENDIF
1643
1644!
1645!-- Special actions during the run
1646    WRITE ( io, 470 )
1647    IF ( create_disturbances )  THEN
1648       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1649                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1650                          zu(disturbance_level_ind_t), disturbance_level_ind_t
[707]1651       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
[1]1652          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1653       ELSE
1654          WRITE ( io, 473 )  disturbance_energy_limit
1655       ENDIF
1656       WRITE ( io, 474 )  TRIM( random_generator )
1657    ENDIF
[1353]1658    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
[1]1659       WRITE ( io, 475 )  pt_surface_initial_change
1660    ENDIF
[1353]1661    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
[1]1662       WRITE ( io, 476 )  q_surface_initial_change       
1663    ENDIF
[1353]1664    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
[1]1665       WRITE ( io, 477 )  q_surface_initial_change       
1666    ENDIF
1667
[60]1668    IF ( particle_advection )  THEN
[1]1669!
[60]1670!--    Particle attributes
1671       WRITE ( io, 480 )  particle_advection_start, dt_prel, bc_par_lr, &
1672                          bc_par_ns, bc_par_b, bc_par_t, particle_maximum_age, &
[1359]1673                          end_time_prel
[60]1674       IF ( use_sgs_for_particles )  WRITE ( io, 488 )  dt_min_part
1675       IF ( random_start_position )  WRITE ( io, 481 )
1676       IF ( particles_per_point > 1 )  WRITE ( io, 489 )  particles_per_point
1677       WRITE ( io, 495 )  total_number_of_particles
[824]1678       IF ( use_particle_tails  .AND.  maximum_number_of_tailpoints /= 0 )  THEN
[60]1679          WRITE ( io, 483 )  maximum_number_of_tailpoints
1680          IF ( minimum_tailpoint_distance /= 0 )  THEN
1681             WRITE ( io, 484 )  total_number_of_tails,      &
1682                                minimum_tailpoint_distance, &
1683                                maximum_tailpoint_age
1684          ENDIF
[1]1685       ENDIF
[1322]1686       IF ( dt_write_particle_data /= 9999999.9_wp )  THEN
[60]1687          WRITE ( io, 485 )  dt_write_particle_data
[1327]1688          IF ( netcdf_data_format > 1 )  THEN
1689             output_format = 'netcdf (64 bit offset) and binary'
[1]1690          ELSE
[1327]1691             output_format = 'netcdf and binary'
[1]1692          ENDIF
[292]1693          WRITE ( io, 344 )  output_format
[1]1694       ENDIF
[1322]1695       IF ( dt_dopts /= 9999999.9_wp )  WRITE ( io, 494 )  dt_dopts
[60]1696       IF ( write_particle_statistics )  WRITE ( io, 486 )
[1]1697
[60]1698       WRITE ( io, 487 )  number_of_particle_groups
[1]1699
[60]1700       DO  i = 1, number_of_particle_groups
[1322]1701          IF ( i == 1  .AND.  density_ratio(i) == 9999999.9_wp )  THEN
[1353]1702             WRITE ( io, 490 )  i, 0.0_wp
[60]1703             WRITE ( io, 492 )
[1]1704          ELSE
[60]1705             WRITE ( io, 490 )  i, radius(i)
[1353]1706             IF ( density_ratio(i) /= 0.0_wp )  THEN
[60]1707                WRITE ( io, 491 )  density_ratio(i)
1708             ELSE
1709                WRITE ( io, 492 )
1710             ENDIF
[1]1711          ENDIF
[60]1712          WRITE ( io, 493 )  psl(i), psr(i), pss(i), psn(i), psb(i), pst(i), &
1713                             pdx(i), pdy(i), pdz(i)
[336]1714          IF ( .NOT. vertical_particle_advection(i) )  WRITE ( io, 482 )
[60]1715       ENDDO
[1]1716
[60]1717    ENDIF
[1]1718
[60]1719
[1]1720!
1721!-- Parameters of 1D-model
1722    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1723       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1724                          mixing_length_1d, dissipation_1d
1725       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1726          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1727       ENDIF
1728    ENDIF
1729
1730!
1731!-- User-defined informations
1732    CALL user_header( io )
1733
1734    WRITE ( io, 99 )
1735
1736!
1737!-- Write buffer contents to disc immediately
[82]1738    CALL local_flush( io )
[1]1739
1740!
1741!-- Here the FORMATs start
1742
1743 99 FORMAT (1X,78('-'))
[1468]1744100 FORMAT (/1X,'******************************',4X,44('-')/        &
1745            1X,'* ',A,' *',4X,A/                               &
1746            1X,'******************************',4X,44('-'))
1747101 FORMAT (35X,'coupled run using MPI-',I1,': ',A/ &
1748            35X,42('-'))
1749102 FORMAT (/' Date:                 ',A8,4X,'Run:       ',A20/      &
1750            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
[1106]1751            ' Run on host:        ',A10)
[1]1752#if defined( __parallel )
[1468]1753103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
[1]1754              ')',1X,A)
[1468]1755104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1756              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1757105 FORMAT (35X,'One additional PE is used to handle'/37X,'the dvrp output!')
1758106 FORMAT (35X,'A 1d-decomposition along x is forced'/ &
1759            35X,'because the job is running on an SMP-cluster')
1760107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1761108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1762109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1763            35X,42('-'))
1764114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1765            35X,'independent precursor runs'/             &
1766            35X,42('-'))
[1111]1767117 FORMAT (' Accelerator boards / node:  ',I2)
[1]1768#endif
1769110 FORMAT (/' Numerical Schemes:'/ &
1770             ' -----------------'/)
1771111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1772112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1773            '     Iterations (initial/other): ',I3,'/',I3,'  omega = ',F5.3)
1774113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1775                  ' or Upstream')
[1216]1776115 FORMAT ('     FFT and transpositions are overlapping')
[1]1777116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1778                  ' or Upstream')
1779118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
[1106]1780119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1781            '     translation velocity = ',A/ &
[1]1782            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
[1111]1783120 FORMAT (' Accelerator boards: ',8X,I2)
[1]1784122 FORMAT (' --> Time differencing scheme: ',A)
[108]1785123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
[1]1786            '     maximum damping coefficient: ',F5.3, ' 1/s')
1787129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1788130 FORMAT (' --> Additional prognostic equation for the total water content')
[940]1789131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1790                  F6.2, ' K assumed')
[824]1791132 FORMAT ('     Parameterization of long-wave radiation processes via'/ &
[1]1792            '     effective emissivity scheme')
[824]1793133 FORMAT ('     Precipitation parameterization via Kessler-Scheme')
[1]1794134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1795135 FORMAT (' --> Solve perturbation pressure via multigrid method (', &
1796                  A,'-cycle)'/ &
1797            '     number of grid levels:                   ',I2/ &
1798            '     Gauss-Seidel red/black iterations:       ',I2)
1799136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1800                  I3,')')
1801137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1802            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1803                  I3,')'/ &
1804            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1805                  I3,')')
[63]1806139 FORMAT (' --> Loop optimization method: ',A)
[1]1807140 FORMAT ('     maximum residual allowed:                ',E10.3)
1808141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1809142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1810                  'step')
[87]1811143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1812                  'kinetic energy')
[927]1813144 FORMAT ('     masking method is used')
[1]1814150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
[241]1815                  'conserved'/ &
1816            '     using the ',A,' mode')
1817151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
[306]1818152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1819           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1820           /'     starting from dp_level_b =', F8.3, 'm', A /)
[1365]1821160 FORMAT (//' Large scale forcing and nudging:'/ &
1822              ' -------------------------------'/)
1823161 FORMAT (' --> No large scale forcing from external is used (default) ')
1824162 FORMAT (' --> Large scale forcing from external file LSF_DATA is used: ')
1825163 FORMAT ('     - large scale advection tendencies ')
1826164 FORMAT ('     - large scale subsidence velocity w_subs ')
1827165 FORMAT ('     - large scale subsidence tendencies ')
1828167 FORMAT ('     - and geostrophic wind components ug and vg')
1829168 FORMAT (' --> Large-scale vertical motion is used in the ', &
[1299]1830                  'prognostic equation(s) for')
[1365]1831169 FORMAT ('     the scalar(s) only')
1832170 FORMAT (' --> Nudging is used')
1833171 FORMAT (' --> No nudging is used (default) ')
1834180 FORMAT ('     - prescribed surface values for temperature')
[1376]1835181 FORMAT ('     - prescribed surface fluxes for temperature')
1836182 FORMAT ('     - prescribed surface values for humidity')
[1365]1837183 FORMAT ('     - prescribed surface fluxes for humidity')
[1]1838200 FORMAT (//' Run time and time step information:'/ &
1839             ' ----------------------------------'/)
[1106]1840201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
[1]1841             '    CFL-factor: ',F4.2)
[1106]1842202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1843203 FORMAT ( ' Start time:          ',F9.3,' s'/ &
1844             ' End time:            ',F9.3,' s')
[1]1845204 FORMAT ( A,F9.3,' s')
1846205 FORMAT ( A,F9.3,' s',5X,'restart every',17X,F9.3,' s')
[1106]1847206 FORMAT (/' Time reached:        ',F9.3,' s'/ &
1848             ' CPU-time used:       ',F9.3,' s     per timestep:               ', &
1849               '  ',F9.3,' s'/                                                    &
[1111]1850             '                                      per second of simulated tim', &
[1]1851               'e: ',F9.3,' s')
[1106]1852207 FORMAT ( ' Coupling start time: ',F9.3,' s')
[1]1853250 FORMAT (//' Computational grid and domain size:'/ &
1854              ' ----------------------------------'// &
1855              ' Grid length:      dx =    ',F7.3,' m    dy =    ',F7.3, &
1856              ' m    dz =    ',F7.3,' m'/ &
1857              ' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1858              ' m  z(u) = ',F10.3,' m'/)
1859252 FORMAT (' dz constant up to ',F10.3,' m (k=',I4,'), then stretched by', &
1860              ' factor: ',F5.3/ &
1861            ' maximum dz not to be exceeded is dz_max = ',F10.3,' m'/)
1862254 FORMAT (' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1863            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1864260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1865             ' degrees')
1866270 FORMAT (//' Topography informations:'/ &
1867              ' -----------------------'// &
1868              1X,'Topography: ',A)
1869271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1870              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1871                ' / ',I4)
[240]1872272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1873              ' direction' / &
1874              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1875              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
[256]1876278 FORMAT (' Topography grid definition convention:'/ &
1877            ' cell edge (staggered grid points'/  &
1878            ' (u in x-direction, v in y-direction))' /)
1879279 FORMAT (' Topography grid definition convention:'/ &
1880            ' cell center (scalar grid points)' /)
[138]1881280 FORMAT (//' Vegetation canopy (drag) model:'/ &
1882              ' ------------------------------'// &
1883              ' Canopy mode: ', A / &
[1484]1884              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
[138]1885              ' Leaf drag coefficient: ',F6.2 /)
[1484]1886281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
[153]1887              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
1888282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
1889283 FORMAT (/ ' Characteristic levels of the leaf area density:'// &
[138]1890              ' Height:              ',A,'  m'/ &
1891              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1892              ' Gradient:            ',A,'  m**2/m**4'/ &
1893              ' Gridpoint:           ',A)
[1484]1894284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
1895              ' Height:              ',A,'  m'/ &
1896              ' Leaf area density:   ',A,'  m**2/m**3'/ &
1897              ' Coefficient alpha: ',F6.2 / &
1898              ' Coefficient beta: ',F6.2 / &
1899              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
[138]1900               
[1]1901300 FORMAT (//' Boundary conditions:'/ &
1902             ' -------------------'// &
1903             '                     p                    uv             ', &
1904             '                   pt'// &
1905             ' B. bound.: ',A/ &
1906             ' T. bound.: ',A)
[97]1907301 FORMAT (/'                     ',A// &
[1]1908             ' B. bound.: ',A/ &
1909             ' T. bound.: ',A)
[19]1910303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1911304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1912305 FORMAT (//'    Prandtl-Layer between bottom surface and first ', &
1913               'computational u,v-level:'// &
[978]1914             '       zp = ',F6.2,' m   z0 = ',F6.4,' m   z0h = ',F7.5,&
1915             ' m   kappa = ',F4.2/ &
[1]1916             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
[97]1917306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
[1]1918307 FORMAT ('       Heatflux has a random normal distribution')
1919308 FORMAT ('       Predefined surface temperature')
[97]1920309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
[1]1921310 FORMAT (//'    1D-Model:'// &
1922             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1923311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' m/s')
1924312 FORMAT ('       Predefined surface humidity')
1925313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1926314 FORMAT ('       Predefined scalar value at the surface')
[19]1927315 FORMAT ('       Humidity / scalar flux at top surface is 0.0')
[102]1928316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1929                    'atmosphere model')
[1]1930317 FORMAT (//' Lateral boundaries:'/ &
1931            '       left/right:  ',A/    &
1932            '       north/south: ',A)
[1159]1933318 FORMAT (/'       use_cmax: ',L1 / &
1934            '       pt damping layer width = ',F8.2,' m, pt ', &
[978]1935                    'damping factor = ',F6.4)
[151]1936319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1937            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1938            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1939320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
[103]1940            '                                          v: ',F9.6,' m**2/s**2')
[1365]1941321 FORMAT (//' Initial profiles:'/ &
1942              ' ----------------')
[151]1943325 FORMAT (//' List output:'/ &
[1]1944             ' -----------'//  &
1945            '    1D-Profiles:'/    &
1946            '       Output every             ',F8.2,' s')
[151]1947326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
[1]1948            '       Averaging input every    ',F8.2,' s')
1949330 FORMAT (//' Data output:'/ &
1950             ' -----------'/)
1951331 FORMAT (/'    1D-Profiles:')
1952332 FORMAT (/'       ',A)
1953333 FORMAT ('       Output every             ',F8.2,' s',/ &
1954            '       Time averaged over       ',F8.2,' s'/ &
1955            '       Averaging input every    ',F8.2,' s')
1956334 FORMAT (/'    2D-Arrays',A,':')
1957335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1958            '       Output every             ',F8.2,' s  ',A/ &
1959            '       Cross sections at ',A1,' = ',A/ &
1960            '       scalar-coordinates:   ',A,' m'/)
1961336 FORMAT (/'    3D-Arrays',A,':')
1962337 FORMAT (/'       Arrays: ',A/ &
1963            '       Output every             ',F8.2,' s  ',A/ &
1964            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1965339 FORMAT ('       No output during initial ',F8.2,' s')
1966340 FORMAT (/'    Time series:')
1967341 FORMAT ('       Output every             ',F8.2,' s'/)
1968342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1969            '       Output every             ',F8.2,' s  ',A/ &
1970            '       Time averaged over       ',F8.2,' s'/ &
1971            '       Averaging input every    ',F8.2,' s'/ &
1972            '       Cross sections at ',A1,' = ',A/ &
1973            '       scalar-coordinates:   ',A,' m'/)
1974343 FORMAT (/'       Arrays: ',A/ &
1975            '       Output every             ',F8.2,' s  ',A/ &
1976            '       Time averaged over       ',F8.2,' s'/ &
1977            '       Averaging input every    ',F8.2,' s'/ &
1978            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
[292]1979344 FORMAT ('       Output format: ',A/)
[410]1980345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1981            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1982            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1983            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1984346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1985347 FORMAT ('       Variables: ',A/ &
1986            '       Output every             ',F8.2,' s')
1987348 FORMAT ('       Variables: ',A/ &
1988            '       Output every             ',F8.2,' s'/ &
1989            '       Time averaged over       ',F8.2,' s'/ &
1990            '       Averaging input every    ',F8.2,' s')
1991349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1992            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1993            13('       ',8(F8.2,',')/) )
1994350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1995            'all gridpoints along ',A,'-direction (default).' )
1996351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1997            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1998            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
[1313]1999352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
2000353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
[1]2001#if defined( __dvrp_graphics )
2002360 FORMAT ('    Plot-Sequence with dvrp-software:'/ &
2003            '       Output every      ',F7.1,' s'/ &
2004            '       Output mode:      ',A/ &
2005            '       Host / User:      ',A,' / ',A/ &
2006            '       Directory:        ',A// &
2007            '       The sequence contains:')
[337]2008361 FORMAT (/'       Isosurface of "',A,'"    Threshold value: ', E12.3/ &
2009            '          Isosurface color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
2010362 FORMAT (/'       Slicer plane ',A/ &
[336]2011            '       Slicer limits: [',F6.2,',',F6.2,']')
[337]2012363 FORMAT (/'       Particles'/ &
[336]2013            '          particle size:  ',F7.2,' m')
2014364 FORMAT ('          particle ',A,' controlled by "',A,'" with interval [', &
2015                       F6.2,',',F6.2,']')
[337]2016365 FORMAT (/'       Groundplate color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)'/ &
[336]2017            '       Superelevation along (x,y,z): (',F4.1,',',F4.1,',',F4.1, &
2018                     ')'/ &
2019            '       Clipping limits: from x = ',F9.1,' m to x = ',F9.1,' m'/ &
2020            '                        from y = ',F9.1,' m to y = ',F9.1,' m')
[337]2021366 FORMAT (/'       Topography color: (',F4.2,',',F4.2,',',F4.2,') (R,G,B)')
[336]2022367 FORMAT ('       Polygon reduction for topography: cluster_size = ', I1)
[1]2023#endif
2024#if defined( __spectra )
2025370 FORMAT ('    Spectra:')
2026371 FORMAT ('       Output every ',F7.1,' s'/)
2027372 FORMAT ('       Arrays:     ', 10(A5,',')/                         &
2028            '       Directions: ', 10(A5,',')/                         &
[189]2029            '       height levels  k = ', 20(I3,',')/                  &
2030            '                          ', 20(I3,',')/                  &
2031            '                          ', 20(I3,',')/                  &
2032            '                          ', 20(I3,',')/                  &
2033            '                          ', 19(I3,','),I3,'.'/           &
[1]2034            '       height levels selected for standard plot:'/        &
[189]2035            '                      k = ', 20(I3,',')/                  &
2036            '                          ', 20(I3,',')/                  &
2037            '                          ', 20(I3,',')/                  &
2038            '                          ', 20(I3,',')/                  &
2039            '                          ', 19(I3,','),I3,'.'/           &
[1]2040            '       Time averaged over ', F7.1, ' s,' /                &
2041            '       Profiles for the time averaging are taken every ', &
2042                    F6.1,' s')
2043#endif
2044400 FORMAT (//' Physical quantities:'/ &
2045              ' -------------------'/)
2046410 FORMAT ('    Angular velocity    :   omega = ',E9.3,' rad/s'/  &
2047            '    Geograph. latitude  :   phi   = ',F4.1,' degr'/   &
2048            '    Coriolis parameter  :   f     = ',F9.6,' 1/s'/    &
2049            '                            f*    = ',F9.6,' 1/s')
2050411 FORMAT (/'    Gravity             :   g     = ',F4.1,' m/s**2')
[1179]2051412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
2052413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
2053414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
[57]2054415 FORMAT (/'    Cloud physics parameters:'/ &
[1]2055             '    ------------------------'/)
[57]2056416 FORMAT ('        Surface pressure   :   p_0   = ',F7.2,' hPa'/      &
[1]2057            '        Gas constant       :   R     = ',F5.1,' J/(kg K)'/ &
2058            '        Density of air     :   rho_0 = ',F5.3,' kg/m**3'/  &
2059            '        Specific heat cap. :   c_p   = ',F6.1,' J/(kg K)'/ &
2060            '        Vapourization heat :   L_v   = ',E8.2,' J/kg')
2061420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
2062            '       Height:        ',A,'  m'/ &
2063            '       Temperature:   ',A,'  K'/ &
2064            '       Gradient:      ',A,'  K/100m'/ &
2065            '       Gridpoint:     ',A)
2066421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
2067            '       Height:      ',A,'  m'/ &
2068            '       Humidity:    ',A,'  kg/kg'/ &
2069            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
2070            '       Gridpoint:   ',A)
2071422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
2072            '       Height:                  ',A,'  m'/ &
2073            '       Scalar concentration:    ',A,'  kg/m**3'/ &
2074            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
2075            '       Gridpoint:               ',A)
2076423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
2077            '       Height:      ',A,'  m'/ &
2078            '       ug:          ',A,'  m/s'/ &
2079            '       Gradient:    ',A,'  1/100s'/ &
2080            '       Gridpoint:   ',A)
2081424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
2082            '       Height:      ',A,'  m'/ &
[97]2083            '       vg:          ',A,'  m/s'/ &
[1]2084            '       Gradient:    ',A,'  1/100s'/ &
2085            '       Gridpoint:   ',A)
[97]2086425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
2087            '       Height:     ',A,'  m'/ &
2088            '       Salinity:   ',A,'  psu'/ &
2089            '       Gradient:   ',A,'  psu/100m'/ &
2090            '       Gridpoint:  ',A)
[411]2091426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
2092            '       Height:      ',A,'  m'/ &
2093            '       w_subs:      ',A,'  m/s'/ &
2094            '       Gradient:    ',A,'  (m/s)/100m'/ &
2095            '       Gridpoint:   ',A)
[767]2096427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
2097                  ' profiles')
[1241]2098428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
2099             '    NUDGING_DATA')
[824]2100430 FORMAT (//' Cloud physics quantities / methods:'/ &
2101              ' ----------------------------------'/)
2102431 FORMAT ('    Humidity is treated as purely passive scalar (no condensati', &
2103                 'on)')
2104432 FORMAT ('    Bulk scheme with liquid water potential temperature and'/ &
2105            '    total water content is used.'/ &
2106            '    Condensation is parameterized via 0% - or 100% scheme.')
2107433 FORMAT ('    Cloud droplets treated explicitly using the Lagrangian part', &
2108                 'icle model')
2109434 FORMAT ('    Curvature and solution effecs are considered for growth of', &
2110                 ' droplets < 1.0E-6 m')
[825]2111435 FORMAT ('    Droplet collision is handled by ',A,'-kernel')
[828]2112436 FORMAT ('       Fast kernel with fixed radius- and dissipation classes ', &
2113                    'are used'/ &
2114            '          number of radius classes:       ',I3,'    interval ', &
2115                       '[1.0E-6,2.0E-4] m'/ &
2116            '          number of dissipation classes:   ',I2,'    interval ', &
2117                       '[0,1000] cm**2/s**3')
2118437 FORMAT ('    Droplet collision is switched off')
[1]2119450 FORMAT (//' LES / Turbulence quantities:'/ &
2120              ' ---------------------------'/)
[824]2121451 FORMAT ('    Diffusion coefficients are constant:'/ &
2122            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
2123453 FORMAT ('    Mixing length is limited to ',F4.2,' * z')
2124454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
2125455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
[1]2126470 FORMAT (//' Actions during the simulation:'/ &
2127              ' -----------------------------'/)
[94]2128471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
2129            '    Disturbance amplitude           :     ',F4.2, ' m/s'/       &
2130            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
2131            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
[1]2132472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
2133                 ' to i/j =',I4)
2134473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
2135                 1X,F5.3, ' m**2/s**2')
2136474 FORMAT ('    Random number generator used    : ',A/)
2137475 FORMAT ('    The surface temperature is increased (or decreased, ', &
2138                 'respectively, if'/ &
2139            '    the value is negative) by ',F5.2,' K at the beginning of the',&
2140                 ' 3D-simulation'/)
2141476 FORMAT ('    The surface humidity is increased (or decreased, ',&
2142                 'respectively, if the'/ &
2143            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
2144                 ' the 3D-simulation'/)
2145477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
2146                 'respectively, if the'/ &
2147            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
2148                 ' the 3D-simulation'/)
2149480 FORMAT ('    Particles:'/ &
2150            '    ---------'// &
2151            '       Particle advection is active (switched on at t = ', F7.1, &
2152                    ' s)'/ &
2153            '       Start of new particle generations every  ',F6.1,' s'/ &
2154            '       Boundary conditions: left/right: ', A, ' north/south: ', A/&
2155            '                            bottom:     ', A, ' top:         ', A/&
2156            '       Maximum particle age:                 ',F9.1,' s'/ &
[1359]2157            '       Advection stopped at t = ',F9.1,' s'/)
[1]2158481 FORMAT ('       Particles have random start positions'/)
[336]2159482 FORMAT ('          Particles are advected only horizontally'/)
[1]2160483 FORMAT ('       Particles have tails with a maximum of ',I3,' points')
2161484 FORMAT ('            Number of tails of the total domain: ',I10/ &
2162            '            Minimum distance between tailpoints: ',F8.2,' m'/ &
2163            '            Maximum age of the end of the tail:  ',F8.2,' s')
2164485 FORMAT ('       Particle data are written on file every ', F9.1, ' s')
2165486 FORMAT ('       Particle statistics are written on file'/)
2166487 FORMAT ('       Number of particle groups: ',I2/)
2167488 FORMAT ('       SGS velocity components are used for particle advection'/ &
2168            '          minimum timestep for advection: ', F7.5/)
2169489 FORMAT ('       Number of particles simultaneously released at each ', &
2170                    'point: ', I5/)
2171490 FORMAT ('       Particle group ',I2,':'/ &
2172            '          Particle radius: ',E10.3, 'm')
2173491 FORMAT ('          Particle inertia is activated'/ &
2174            '             density_ratio (rho_fluid/rho_particle) = ',F5.3/)
2175492 FORMAT ('          Particles are advected only passively (no inertia)'/)
2176493 FORMAT ('          Boundaries of particle source: x:',F8.1,' - ',F8.1,' m'/&
2177            '                                         y:',F8.1,' - ',F8.1,' m'/&
2178            '                                         z:',F8.1,' - ',F8.1,' m'/&
2179            '          Particle distances:  dx = ',F8.1,' m  dy = ',F8.1, &
2180                       ' m  dz = ',F8.1,' m'/)
2181494 FORMAT ('       Output of particle time series in NetCDF format every ', &
2182                    F8.2,' s'/)
2183495 FORMAT ('       Number of particles in total domain: ',I10/)
2184500 FORMAT (//' 1D-Model parameters:'/                           &
2185              ' -------------------'//                           &
2186            '    Simulation time:                   ',F8.1,' s'/ &
2187            '    Run-controll output every:         ',F8.1,' s'/ &
2188            '    Vertical profile output every:     ',F8.1,' s'/ &
2189            '    Mixing length calculation:         ',A/         &
2190            '    Dissipation calculation:           ',A/)
2191502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
[667]2192503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
2193504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
[1115]2194505 FORMAT ('    Precipitation parameterization via Seifert-Beheng-Scheme')
2195506 FORMAT ('    Drizzle parameterization via Stokes law')
2196507 FORMAT ('    Turbulence effects on precipitation process')
2197508 FORMAT ('    Ventilation effects on evaporation of rain drops')
2198509 FORMAT ('    Slope limiter used for sedimentation process')
2199510 FORMAT ('        Droplet density    :   N_c   = ',F6.1,' 1/cm**3')
2200511 FORMAT ('        Sedimentation Courant number:                  '/&
2201            '                               C_s   = ',F3.1,'        ')
[1429]2202512 FORMAT (/' Date:                 ',A8,6X,'Run:       ',A20/      &
2203            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
2204            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
[1]2205
2206 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.