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

Last change on this file since 4313 was 4309, checked in by suehring, 4 years ago

Synthetic turbulence generator: Computation of velocity seeds optimized. This implies that random numbers are computed now using the parallel random number generator. Random number are now only computed and normalized locally, while distributed over all mpi ranks afterwards, instead of computing random numbers on a global array. urther, the number of calls for the time-consuming velocity-seed generation is reduced - now the left and right, as well as the north and south boundary share the same velocity-seed matrices.

  • Property svn:keywords set to Id
File size: 76.6 KB
Line 
1! !> @file header.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: header.f90 4309 2019-11-26 18:49:59Z suehring $
27! replaced recycling_yshift by y_shift
28!
29! 4301 2019-11-22 12:09:09Z oliver.maas
30!
31! 4297 2019-11-21 10:37:50Z oliver.maas
32! Adjusted format for simulated time and related quantities
33!
34! 4297 2019-11-21 10:37:50Z oliver.maas
35! adjusted message to the changed parameter recycling_yshift
36!
37! 4227 2019-09-10 18:04:34Z gronemeier
38! implement new palm_date_time_mod
39!
40! 4223 2019-09-10 09:20:47Z gronemeier
41! Write information about rotation angle
42!
43! 4182 2019-08-22 15:20:23Z scharf
44! Corrected "Former revisions" section
45!
46! 4168 2019-08-16 13:50:17Z suehring
47! Replace function get_topography_top_index by topo_top_ind
48!
49! 4069 2019-07-01 14:05:51Z Giersch
50! Masked output running index mid has been introduced as a local variable to
51! avoid runtime error (Loop variable has been modified) in time_integration
52!
53! 4023 2019-06-12 13:20:01Z maronga
54! Renamed "coupling start time" to "spinup time"
55!
56! 4017 2019-06-06 12:16:46Z schwenkel
57! unused variable removed
58!
59! 3655 2019-01-07 16:51:22Z knoop
60! Implementation of the PALM module interface
61!
62! Revision 1.1  1997/08/11 06:17:20  raasch
63! Initial revision
64!
65!
66! Description:
67! ------------
68!> Writing a header with all important information about the current run.
69!> This subroutine is called three times, two times at the beginning
70!> (writing information on files RUN_CONTROL and HEADER) and one time at the
71!> end of the run, then writing additional information about CPU-usage on file
72!> header.
73!-----------------------------------------------------------------------------!
74 SUBROUTINE header
75 
76
77    USE arrays_3d,                                                             &
78        ONLY:  pt_init, q_init, s_init, sa_init, ug, vg, w_subs, zu, zw
79
80    USE basic_constants_and_equations_mod,                                     &
81        ONLY:  g, kappa
82
83    USE bulk_cloud_model_mod,                                                  &
84        ONLY:  bulk_cloud_model
85
86    USE control_parameters
87
88    USE cpulog,                                                                &
89        ONLY:  log_point_s
90
91    USE grid_variables,                                                        &
92        ONLY:  dx, dy
93
94    USE indices,                                                               &
95        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
96               nys_mg, nzt, nzt_mg, topo_top_ind
97
98    USE kinds
99
100    USE model_1d_mod,                                                          &
101        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
102
103    USE module_interface,                                                      &
104        ONLY:  module_interface_header
105
106    USE netcdf_interface,                                                      &
107        ONLY:  netcdf_data_format, netcdf_data_format_string, netcdf_deflate
108
109    USE ocean_mod,                                                             &
110        ONLY:  ibc_sa_t, prho_reference, sa_surface,                           &
111               sa_vertical_gradient, sa_vertical_gradient_level,               &
112               sa_vertical_gradient_level_ind
113
114    USE palm_date_time_mod,                                                    &
115        ONLY:  get_date_time
116
117    USE pegrid
118
119#if defined( __parallel )
120    USE pmc_handle_communicator,                                               &
121        ONLY:  pmc_get_model_info
122#endif
123
124    USE pmc_interface,                                                         &
125        ONLY:  nested_run, nesting_datatransfer_mode, nesting_mode
126
127    USE surface_mod,                                                           &
128        ONLY:  surf_def_h
129
130    USE turbulence_closure_mod,                                                &
131        ONLY:  rans_const_c, rans_const_sigma
132
133    IMPLICIT NONE
134
135   
136    CHARACTER (LEN=2)  ::  do2d_mode           !< mode of 2D data output (xy, xz, yz)
137   
138    CHARACTER (LEN=5)  ::  section_chr         !< string indicating grid information where to output 2D slices
139   
140    CHARACTER (LEN=10) ::  coor_chr            !< string for subsidence velocities in large-scale forcing
141    CHARACTER (LEN=10) ::  host_chr            !< string for hostname
142   
143    CHARACTER (LEN=16) ::  begin_chr           !< string indication start time for the data output
144   
145    CHARACTER (LEN=26) ::  ver_rev             !< string for run identification
146
147    CHARACTER (LEN=32) ::  cpl_name            !< name of child domain (nesting mode only)
148   
149    CHARACTER (LEN=40) ::  output_format       !< netcdf format
150       
151    CHARACTER (LEN=70) ::  char1               !< dummy varialbe used for various strings
152    CHARACTER (LEN=70) ::  char2               !< string containing informating about the advected distance in case of Galilei transformation
153    CHARACTER (LEN=23) ::  date_time_str       !< string for date and time information
154    CHARACTER (LEN=70) ::  dopr_chr            !< string indicating profile output variables
155    CHARACTER (LEN=70) ::  do2d_xy             !< string indicating 2D-xy output variables
156    CHARACTER (LEN=70) ::  do2d_xz             !< string indicating 2D-xz output variables
157    CHARACTER (LEN=70) ::  do2d_yz             !< string indicating 2D-yz output variables
158    CHARACTER (LEN=70) ::  do3d_chr            !< string indicating 3D output variables
159    CHARACTER (LEN=70) ::  domask_chr          !< string indicating masked output variables
160    CHARACTER (LEN=70) ::  run_classification  !< string classifying type of run, e.g. nested, coupled, etc.
161   
162    CHARACTER (LEN=85) ::  r_upper             !< string indicating model top boundary condition for various quantities
163    CHARACTER (LEN=85) ::  r_lower             !< string indicating bottom boundary condition for various quantities
164   
165    CHARACTER (LEN=86) ::  coordinates         !< string indicating height coordinates for profile-prescribed variables
166    CHARACTER (LEN=86) ::  gradients           !< string indicating gradients of profile-prescribed variables between the prescribed height coordinates
167    CHARACTER (LEN=86) ::  slices              !< string indicating grid coordinates of profile-prescribed subsidence velocity
168    CHARACTER (LEN=86) ::  temperatures        !< string indicating profile-prescribed subsidence velocities
169    CHARACTER (LEN=86) ::  ugcomponent         !< string indicating profile-prescribed geostrophic u-component
170    CHARACTER (LEN=86) ::  vgcomponent         !< string indicating profile-prescribed geostrophic v-component
171
172    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !< string indicating masking steps along certain direction
173
174    INTEGER(iwp) ::  av             !< index indicating average output quantities
175    INTEGER(iwp) ::  bh             !< building height in generic single-building setup
176    INTEGER(iwp) ::  blx            !< building width in grid points along x in generic single-building setup
177    INTEGER(iwp) ::  bly            !< building width in grid points along y in generic single-building setup
178    INTEGER(iwp) ::  bxl            !< index for left building wall in generic single-building setup
179    INTEGER(iwp) ::  bxr            !< index for right building wall in generic single-building setup
180    INTEGER(iwp) ::  byn            !< index for north building wall in generic single-building setup
181    INTEGER(iwp) ::  bys            !< index for south building wall in generic single-building setup
182    INTEGER(iwp) ::  ch             !< canyon depth in generic street-canyon setup
183    INTEGER(iwp) ::  count          !< number of masked output locations
184    INTEGER(iwp) ::  cpl_parent_id  !< parent ID for the respective child model
185    INTEGER(iwp) ::  cwx            !< canyon width along x in generic street-canyon setup
186    INTEGER(iwp) ::  cwy            !< canyon width along y in generic street-canyon setup
187    INTEGER(iwp) ::  cxl            !< index for left canyon wall in generic street-canyon setup
188    INTEGER(iwp) ::  cxr            !< index for right canyon wall in generic street-canyon setup
189    INTEGER(iwp) ::  cyn            !< index for north canyon wall in generic street-canyon setup
190    INTEGER(iwp) ::  cys            !< index for south canyon wall in generic street-canyon setup
191    INTEGER(iwp) ::  dim            !< running index for masking output locations
192    INTEGER(iwp) ::  i              !< running index for various loops
193    INTEGER(iwp) ::  io             !< file unit of HEADER file
194    INTEGER(iwp) ::  l              !< substring length
195    INTEGER(iwp) ::  ll             !< substring length
196    INTEGER(iwp) ::  mid            !< masked output running index
197    INTEGER(iwp) ::  my_cpl_id      !< run id in a nested model setup
198    INTEGER(iwp) ::  n              !< running index over number of couplers in a nested model setup
199    INTEGER(iwp) ::  ncpl           !< number of coupler in a nested model setup
200    INTEGER(iwp) ::  npe_total      !< number of total PEs in a coupler (parent + child)
201   
202
203    REAL(wp) ::  cpuseconds_per_simulated_second  !< CPU time (in s) per simulated second
204    REAL(wp) ::  lower_left_coord_x               !< x-coordinate of nest domain
205    REAL(wp) ::  lower_left_coord_y               !< y-coordinate of nest domain
206
207!
208!-- Open the output file. At the end of the simulation, output is directed
209!-- to unit 19.
210    IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
211         .NOT. simulated_time_at_begin /= simulated_time )  THEN
212       io = 15   !  header output on file RUN_CONTROL
213    ELSE
214       io = 19   !  header output on file HEADER
215    ENDIF
216    CALL check_open( io )
217
218!
219!-- At the end of the run, output file (HEADER) will be rewritten with
220!-- new information
221    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
222
223!
224!-- Determine kind of model run
225    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
226       run_classification = 'restart run'
227    ELSEIF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
228       run_classification = 'run with cyclic fill of 3D - prerun data'
229    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
230       run_classification = 'run without 1D - prerun'
231    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
232       run_classification = 'run with 1D - prerun'
233    ELSEIF ( INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
234       run_classification = 'run initialized with COSMO data'
235    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
236       run_classification = 'run initialized by user'
237    ELSEIF ( INDEX( initializing_actions, 'initialize_vortex' ) /=0 )  THEN
238       run_classification = 'run additionally initialized by a Rankine-vortex'
239    ELSEIF ( INDEX( initializing_actions, 'initialize_ptanom' ) /=0 )  THEN
240       run_classification = 'run additionally initialized by temperature anomaly'
241    ELSE
242       message_string = ' unknown action(s): ' // TRIM( initializing_actions )
243       CALL message( 'header', 'PA0191', 0, 0, 0, 6, 0 )
244    ENDIF
245    IF ( nested_run )  run_classification = 'nested ' // run_classification(1:63)
246    IF ( ocean_mode )  THEN
247       run_classification = 'ocean - ' // run_classification(1:61)
248    ELSE
249       run_classification = 'atmosphere - ' // run_classification(1:57)
250    ENDIF
251
252!
253!-- Run-identification, date, time, host
254    host_chr = host(1:10)
255    ver_rev = TRIM( version ) // '  ' // TRIM( revision )
256    WRITE ( io, 100 )  ver_rev, TRIM( run_classification )
257    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
258       WRITE ( io, 101 )  coupling_mode
259    ENDIF
260#if defined( __parallel )
261    IF ( coupling_start_time /= 0.0_wp  .AND. .NOT. spinup )  THEN
262       IF ( coupling_start_time > simulated_time_at_begin )  THEN
263          WRITE ( io, 109 )
264       ELSE
265          WRITE ( io, 114 )
266       ENDIF
267    ENDIF
268#endif
269    IF ( ensemble_member_nr /= 0 )  THEN
270       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
271                       ADJUSTR( host_chr ), ensemble_member_nr
272    ELSE
273       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
274                       ADJUSTR( host_chr )
275    ENDIF
276#if defined( __parallel )
277    IF ( npex == -1  .AND.  npey == -1 )  THEN
278       char1 = 'calculated'
279    ELSE
280       char1 = 'predefined'
281    ENDIF
282    IF ( threads_per_task == 1 )  THEN
283       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
284    ELSE
285       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
286                          threads_per_task, pdims(1), pdims(2), TRIM( char1 )
287    ENDIF
288
289    IF ( pdims(2) == 1 )  THEN
290       WRITE ( io, 107 )  'x'
291    ELSEIF ( pdims(1) == 1 )  THEN
292       WRITE ( io, 107 )  'y'
293    ENDIF
294    IF ( numprocs /= maximum_parallel_io_streams )  THEN
295       WRITE ( io, 108 )  maximum_parallel_io_streams
296    ENDIF
297#endif
298
299!
300!-- Nesting informations
301    IF ( nested_run )  THEN
302
303#if defined( __parallel )
304       WRITE ( io, 600 )  TRIM( nesting_mode ),                                &
305                          TRIM( nesting_datatransfer_mode )
306       CALL pmc_get_model_info( ncpl = ncpl, cpl_id = my_cpl_id )
307
308       DO  n = 1, ncpl
309          CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,&
310                                   cpl_parent_id = cpl_parent_id,              &
311                                   lower_left_x = lower_left_coord_x,          &
312                                   lower_left_y = lower_left_coord_y,          &
313                                   npe_total = npe_total )
314          IF ( n == my_cpl_id )  THEN
315             char1 = '*'
316          ELSE
317             char1 = ' '
318          ENDIF
319          WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total,       &
320                             lower_left_coord_x, lower_left_coord_y,           &
321                             TRIM( cpl_name )
322       ENDDO
323#endif
324
325    ENDIF
326    WRITE ( io, 99 )
327
328!
329!-- Numerical schemes
330    WRITE ( io, 110 )
331    IF ( rans_mode )  THEN
332       WRITE ( io, 124 )  TRIM( turbulence_closure ), 'RANS'
333    ELSE
334       WRITE ( io, 124 )  TRIM( turbulence_closure ), 'LES'
335    ENDIF
336    WRITE ( io, 121 )  TRIM( approximation )
337    IF ( psolver(1:7) == 'poisfft' )  THEN
338       WRITE ( io, 111 )  TRIM( fft_method )
339       IF ( transpose_compute_overlap )  WRITE( io, 115 )
340    ELSEIF ( psolver == 'sor' )  THEN
341       WRITE ( io, 112 )  nsor_ini, nsor, omega_sor
342    ELSEIF ( psolver(1:9) == 'multigrid' )  THEN
343       WRITE ( io, 135 )  TRIM(psolver), cycle_mg, maximum_grid_level, ngsrb
344       IF ( mg_cycles == -1 )  THEN
345          WRITE ( io, 140 )  residual_limit
346       ELSE
347          WRITE ( io, 141 )  mg_cycles
348       ENDIF
349       IF ( mg_switch_to_pe0_level == 0 )  THEN
350          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
351                             nzt_mg(1)
352       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
353          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
354                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
355                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
356                             nzt_mg(mg_switch_to_pe0_level),    &
357                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
358                             nzt_mg(1)
359       ENDIF
360       IF ( psolver == 'multigrid_noopt' .AND. masking_method )  WRITE ( io, 144 )
361    ENDIF
362    IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
363    THEN
364       WRITE ( io, 142 )
365    ENDIF
366
367    IF ( momentum_advec == 'pw-scheme' )  THEN
368       WRITE ( io, 113 )
369    ELSEIF (momentum_advec == 'ws-scheme' )  THEN
370       WRITE ( io, 503 )
371    ENDIF
372    IF ( scalar_advec == 'pw-scheme' )  THEN
373       WRITE ( io, 116 )
374    ELSEIF ( scalar_advec == 'ws-scheme' )  THEN
375       WRITE ( io, 504 )
376    ELSE
377       WRITE ( io, 118 )
378    ENDIF
379
380    WRITE ( io, 139 )  TRIM( loop_optimization )
381
382    IF ( galilei_transformation )  THEN
383       IF ( use_ug_for_galilei_tr )  THEN
384          char1 = '0.6 * geostrophic wind'
385       ELSE
386          char1 = 'mean wind in model domain'
387       ENDIF
388       IF ( simulated_time_at_begin == simulated_time )  THEN
389          char2 = 'at the start of the run'
390       ELSE
391          char2 = 'at the end of the run'
392       ENDIF
393       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
394                          advected_distance_x/1000.0_wp,                       &
395                          advected_distance_y/1000.0_wp
396    ENDIF
397    WRITE ( io, 122 )  timestep_scheme
398    IF ( use_upstream_for_tke )  WRITE ( io, 143 )
399    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
400       IF ( .NOT. ocean_mode )  THEN
401          WRITE ( io, 123 )  'above', rayleigh_damping_height, &
402               rayleigh_damping_factor
403       ELSE
404          WRITE ( io, 123 )  'below', rayleigh_damping_height, &
405               rayleigh_damping_factor
406       ENDIF
407    ENDIF
408    IF ( neutral )  WRITE ( io, 131 )  pt_surface
409    IF ( humidity )  THEN
410       IF ( .NOT. bulk_cloud_model )  THEN
411          WRITE ( io, 129 )
412       ELSE
413          WRITE ( io, 130 )
414       ENDIF
415    ENDIF
416    IF ( passive_scalar )  WRITE ( io, 134 )
417    IF ( conserve_volume_flow )  THEN
418       WRITE ( io, 150 )  conserve_volume_flow_mode
419       IF ( TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
420          WRITE ( io, 151 )  u_bulk, v_bulk
421       ENDIF
422    ELSEIF ( dp_external )  THEN
423       IF ( dp_smooth )  THEN
424          WRITE ( io, 152 )  dpdxy, dp_level_b, ', vertically smoothed.'
425       ELSE
426          WRITE ( io, 152 )  dpdxy, dp_level_b, '.'
427       ENDIF
428    ENDIF
429    WRITE ( io, 99 )
430
431!
432!-- Runtime and timestep information
433    WRITE ( io, 200 )
434    IF ( .NOT. dt_fixed )  THEN
435       WRITE ( io, 201 )  dt_max, cfl_factor
436    ELSE
437       WRITE ( io, 202 )  dt
438    ENDIF
439    WRITE ( io, 203 )  simulated_time_at_begin, end_time
440
441    IF ( time_restart /= 9999999.9_wp  .AND. &
442         simulated_time_at_begin == simulated_time )  THEN
443       IF ( dt_restart == 9999999.9_wp )  THEN
444          WRITE ( io, 204 )  ' Restart at:       ',time_restart
445       ELSE
446          WRITE ( io, 205 )  ' Restart at:       ',time_restart, dt_restart
447       ENDIF
448    ENDIF
449
450    IF ( simulated_time_at_begin /= simulated_time )  THEN
451       i = MAX ( log_point_s(10)%counts, 1 )
452       IF ( ( simulated_time - simulated_time_at_begin ) == 0.0_wp )  THEN
453          cpuseconds_per_simulated_second = 0.0_wp
454       ELSE
455          cpuseconds_per_simulated_second = log_point_s(10)%sum / &
456                                            ( simulated_time -    &
457                                              simulated_time_at_begin )
458       ENDIF
459       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
460                          log_point_s(10)%sum / REAL( i, KIND=wp ), &
461                          cpuseconds_per_simulated_second
462       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
463          IF ( dt_restart == 9999999.9_wp )  THEN
464             WRITE ( io, 204 )  ' Next restart at:     ',time_restart
465          ELSE
466             WRITE ( io, 205 )  ' Next restart at:     ',time_restart, dt_restart
467          ENDIF
468       ENDIF
469    ENDIF
470
471
472!
473!-- Start time for coupled runs, if independent precursor runs for atmosphere
474!-- and ocean are used or have been used. In this case, coupling_start_time
475!-- defines the time when the coupling is switched on.
476    IF ( coupling_start_time /= 0.0_wp )  THEN
477       WRITE ( io, 207 )  coupling_start_time
478    ENDIF
479
480!
481!-- Computational grid
482    IF ( .NOT. ocean_mode )  THEN
483       WRITE ( io, 250 )  dx, dy
484       
485       DO i = 1, number_stretch_level_start+1
486          WRITE ( io, 253 )  i, dz(i)
487       ENDDO
488       
489       WRITE( io, 251 ) (nx+1)*dx, (ny+1)*dy, zu(nzt+1)
490       
491       IF ( ANY( dz_stretch_level_start_index < nzt+1 ) )  THEN
492          WRITE( io, '(A)', advance='no') ' Vertical stretching starts at height:'
493          DO i = 1, number_stretch_level_start
494             WRITE ( io, '(F10.1,A3)', advance='no' )  dz_stretch_level_start(i), ' m,'
495          ENDDO
496          WRITE( io, '(/,A)', advance='no') ' Vertical stretching starts at index: '
497          DO i = 1, number_stretch_level_start
498             WRITE ( io, '(I12,A1)', advance='no' )  dz_stretch_level_start_index(i), ','
499          ENDDO
500          WRITE( io, '(/,A)', advance='no') ' Vertical stretching ends at height:  '
501          DO i = 1, number_stretch_level_start
502             WRITE ( io, '(F10.1,A3)', advance='no' )  dz_stretch_level_end(i), ' m,'
503          ENDDO
504          WRITE( io, '(/,A)', advance='no') ' Vertical stretching ends at index:   '
505          DO i = 1, number_stretch_level_start
506             WRITE ( io, '(I12,A1)', advance='no' )  dz_stretch_level_end_index(i), ','
507          ENDDO
508          WRITE( io, '(/,A)', advance='no') ' Factor used for stretching:          '
509          DO i = 1, number_stretch_level_start
510             WRITE ( io, '(F12.3,A1)', advance='no' )  dz_stretch_factor_array(i), ','
511          ENDDO
512       ENDIF
513       
514    ELSE
515       WRITE ( io, 250 )  dx, dy
516       DO i = 1, number_stretch_level_start+1
517          WRITE ( io, 253 )  i, dz(i)
518       ENDDO
519       
520       WRITE ( io, 251 ) (nx+1)*dx, (ny+1)*dy, zu(0)
521       
522       IF ( ANY( dz_stretch_level_start_index > 0 ) )  THEN
523          WRITE( io, '(A)', advance='no') ' Vertical stretching starts at height:'
524          DO i = 1, number_stretch_level_start
525             WRITE ( io, '(F10.1,A3)', advance='no' )  dz_stretch_level_start(i), ' m,'
526          ENDDO
527          WRITE( io, '(/,A)', advance='no') ' Vertical stretching starts at index: '
528          DO i = 1, number_stretch_level_start
529             WRITE ( io, '(I12,A1)', advance='no' )  dz_stretch_level_start_index(i), ','
530          ENDDO
531          WRITE( io, '(/,A)', advance='no') ' Vertical stretching ends at height:  '
532          DO i = 1, number_stretch_level_start
533             WRITE ( io, '(F10.1,A3)', advance='no' )  dz_stretch_level_end(i), ' m,'
534          ENDDO
535          WRITE( io, '(/,A)', advance='no') ' Vertical stretching ends at index:   '
536          DO i = 1, number_stretch_level_start
537             WRITE ( io, '(I12,A1)', advance='no' )  dz_stretch_level_end_index(i), ','
538          ENDDO
539          WRITE( io, '(/,A)', advance='no') ' Factor used for stretching:          '
540          DO i = 1, number_stretch_level_start
541             WRITE ( io, '(F12.3,A1)', advance='no' )  dz_stretch_factor_array(i), ','
542          ENDDO
543       ENDIF
544    ENDIF
545    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ),      &
546                       MIN( nnz+2, nzt+2 )
547    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
548
549!
550!-- Profile for the large scale vertial velocity
551!-- Building output strings, starting with surface value
552    IF ( large_scale_subsidence )  THEN
553       temperatures = '   0.0'
554       gradients = '------'
555       slices = '     0'
556       coordinates = '   0.0'
557       i = 1
558       DO  WHILE ( subs_vertical_gradient_level_i(i) /= -9999 )
559
560          WRITE (coor_chr,'(E10.2,7X)')  &
561                                w_subs(subs_vertical_gradient_level_i(i))
562          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
563
564          WRITE (coor_chr,'(E10.2,7X)')  subs_vertical_gradient(i)
565          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
566
567          WRITE (coor_chr,'(I10,7X)')  subs_vertical_gradient_level_i(i)
568          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
569
570          WRITE (coor_chr,'(F10.2,7X)')  subs_vertical_gradient_level(i)
571          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
572
573          IF ( i == 10 )  THEN
574             EXIT
575          ELSE
576             i = i + 1
577          ENDIF
578
579       ENDDO
580
581 
582       IF ( .NOT. large_scale_forcing )  THEN
583          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
584                             TRIM( gradients ), TRIM( slices )
585       ENDIF
586
587
588    ENDIF
589
590!-- Profile of the geostrophic wind (component ug)
591!-- Building output strings
592    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
593    gradients = '------'
594    slices = '     0'
595    coordinates = '   0.0'
596    i = 1
597    DO  WHILE ( ug_vertical_gradient_level_ind(i) /= -9999 )
598     
599       WRITE (coor_chr,'(F6.2,1X)')  ug(ug_vertical_gradient_level_ind(i))
600       ugcomponent = TRIM( ugcomponent ) // '  ' // TRIM( coor_chr )
601
602       WRITE (coor_chr,'(F6.2,1X)')  ug_vertical_gradient(i)
603       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
604
605       WRITE (coor_chr,'(I6,1X)')  ug_vertical_gradient_level_ind(i)
606       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
607
608       WRITE (coor_chr,'(F6.1,1X)')  ug_vertical_gradient_level(i)
609       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
610
611       IF ( i == 10 )  THEN
612          EXIT
613       ELSE
614          i = i + 1
615       ENDIF
616
617    ENDDO
618
619    IF ( .NOT. large_scale_forcing )  THEN
620       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
621                          TRIM( gradients ), TRIM( slices )
622    ENDIF
623
624!-- Profile of the geostrophic wind (component vg)
625!-- Building output strings
626    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
627    gradients = '------'
628    slices = '     0'
629    coordinates = '   0.0'
630    i = 1
631    DO  WHILE ( vg_vertical_gradient_level_ind(i) /= -9999 )
632
633       WRITE (coor_chr,'(F6.2,1X)')  vg(vg_vertical_gradient_level_ind(i))
634       vgcomponent = TRIM( vgcomponent ) // '  ' // TRIM( coor_chr )
635
636       WRITE (coor_chr,'(F6.2,1X)')  vg_vertical_gradient(i)
637       gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
638
639       WRITE (coor_chr,'(I6,1X)')  vg_vertical_gradient_level_ind(i)
640       slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
641
642       WRITE (coor_chr,'(F6.1,1X)')  vg_vertical_gradient_level(i)
643       coordinates = TRIM( coordinates ) // '  ' // TRIM( coor_chr )
644
645       IF ( i == 10 )  THEN
646          EXIT
647       ELSE
648          i = i + 1
649       ENDIF
650 
651    ENDDO
652
653    IF ( .NOT. large_scale_forcing )  THEN
654       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
655                          TRIM( gradients ), TRIM( slices )
656    ENDIF
657
658!
659!-- Topography
660    WRITE ( io, 270 )  topography
661    SELECT CASE ( TRIM( topography ) )
662
663       CASE ( 'flat' )
664          ! no actions necessary
665
666       CASE ( 'single_building' )
667          blx = INT( building_length_x / dx )
668          bly = INT( building_length_y / dy )
669          bh  = MINLOC( ABS( zw - building_height ), 1 ) - 1
670          IF ( ABS( zw(bh  ) - building_height ) == &
671               ABS( zw(bh+1) - building_height )    )  bh = bh + 1
672
673          IF ( building_wall_left == 9999999.9_wp )  THEN
674             building_wall_left = ( nx + 1 - blx ) / 2 * dx
675          ENDIF
676          bxl = INT ( building_wall_left / dx + 0.5_wp )
677          bxr = bxl + blx
678
679          IF ( building_wall_south == 9999999.9_wp )  THEN
680             building_wall_south = ( ny + 1 - bly ) / 2 * dy
681          ENDIF
682          bys = INT ( building_wall_south / dy + 0.5_wp )
683          byn = bys + bly
684
685          WRITE ( io, 271 )  building_length_x, building_length_y, &
686                             building_height, bxl, bxr, bys, byn
687
688       CASE ( 'single_street_canyon' )
689          ch  = MINLOC( ABS( zw - canyon_height ), 1 ) - 1
690          IF ( ABS( zw(ch  ) - canyon_height ) == &
691               ABS( zw(ch+1) - canyon_height )    )  ch = ch + 1
692          IF ( canyon_width_x /= 9999999.9_wp )  THEN
693!
694!--          Street canyon in y direction
695             cwx = NINT( canyon_width_x / dx )
696             IF ( canyon_wall_left == 9999999.9_wp )  THEN
697                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
698             ENDIF
699             cxl = NINT( canyon_wall_left / dx )
700             cxr = cxl + cwx
701             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
702
703          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
704!
705!--          Street canyon in x direction
706             cwy = NINT( canyon_width_y / dy )
707             IF ( canyon_wall_south == 9999999.9_wp )  THEN
708                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
709             ENDIF
710             cys = NINT( canyon_wall_south / dy )
711             cyn = cys + cwy
712             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
713          ENDIF
714
715       CASE ( 'tunnel' )
716          IF ( tunnel_width_x /= 9999999.9_wp )  THEN
717!
718!--          Tunnel axis in y direction
719             IF ( tunnel_length == 9999999.9_wp  .OR.                          &
720                  tunnel_length >= ( nx + 1 ) * dx )  THEN
721                WRITE ( io, 273 )  'y', tunnel_height, tunnel_wall_depth,      &
722                                        tunnel_width_x
723             ELSE
724                WRITE ( io, 274 )  'y', tunnel_height, tunnel_wall_depth,      &
725                                        tunnel_width_x, tunnel_length
726             ENDIF
727
728          ELSEIF ( tunnel_width_y /= 9999999.9_wp )  THEN
729!
730!--          Tunnel axis in x direction
731             IF ( tunnel_length == 9999999.9_wp  .OR.                          &
732                  tunnel_length >= ( ny + 1 ) * dy )  THEN
733                WRITE ( io, 273 )  'x', tunnel_height, tunnel_wall_depth,      &
734                                        tunnel_width_y
735             ELSE
736                WRITE ( io, 274 )  'x', tunnel_height, tunnel_wall_depth,      &
737                                        tunnel_width_y, tunnel_length
738             ENDIF
739          ENDIF
740
741    END SELECT
742
743    IF ( TRIM( topography ) /= 'flat' )  THEN
744       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
745          IF ( TRIM( topography ) == 'single_building' .OR.  &
746               TRIM( topography ) == 'single_street_canyon' )  THEN
747             WRITE ( io, 278 )
748          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
749             WRITE ( io, 279 )
750          ENDIF
751       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_edge' )  THEN
752          WRITE ( io, 278 )
753       ELSEIF ( TRIM( topography_grid_convention ) == 'cell_center' )  THEN
754          WRITE ( io, 279 )
755       ENDIF
756    ENDIF
757
758!-- Complex terrain
759    IF ( complex_terrain )  THEN
760       WRITE( io, 280 ) 
761       IF ( turbulent_inflow )  THEN
762          WRITE( io, 281 )  zu(topo_top_ind(0,0,0))
763       ENDIF
764       IF ( TRIM( initializing_actions ) == 'cyclic_fill' )  THEN
765          WRITE( io, 282 )
766       ENDIF
767    ENDIF
768!
769!-- Boundary conditions
770    IF ( ibc_p_b == 0 )  THEN
771       r_lower = 'p(0)     = 0      |'
772    ELSEIF ( ibc_p_b == 1 )  THEN
773       r_lower = 'p(0)     = p(1)   |'
774    ENDIF
775    IF ( ibc_p_t == 0 )  THEN
776       r_upper  = 'p(nzt+1) = 0      |'
777    ELSE
778       r_upper  = 'p(nzt+1) = p(nzt) |'
779    ENDIF
780
781    IF ( ibc_uv_b == 0 )  THEN
782       r_lower = TRIM( r_lower ) // ' uv(0)     = -uv(1)                |'
783    ELSE
784       r_lower = TRIM( r_lower ) // ' uv(0)     = uv(1)                 |'
785    ENDIF
786    IF ( TRIM( bc_uv_t ) == 'dirichlet_0' )  THEN
787       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = 0                     |'
788    ELSEIF ( ibc_uv_t == 0 )  THEN
789       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = ug(nzt+1), vg(nzt+1)  |'
790    ELSE
791       r_upper  = TRIM( r_upper  ) // ' uv(nzt+1) = uv(nzt)               |'
792    ENDIF
793
794    IF ( ibc_pt_b == 0 )  THEN
795       IF ( land_surface )  THEN
796          r_lower = TRIM( r_lower ) // ' pt(0)     = from soil model'
797       ELSE
798          r_lower = TRIM( r_lower ) // ' pt(0)     = pt_surface'
799       ENDIF
800    ELSEIF ( ibc_pt_b == 1 )  THEN
801       r_lower = TRIM( r_lower ) // ' pt(0)     = pt(1)'
802    ELSEIF ( ibc_pt_b == 2 )  THEN
803       r_lower = TRIM( r_lower ) // ' pt(0)     = from coupled model'
804    ENDIF
805    IF ( ibc_pt_t == 0 )  THEN
806       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt_top'
807    ELSEIF( ibc_pt_t == 1 )  THEN
808       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt)'
809    ELSEIF( ibc_pt_t == 2 )  THEN
810       r_upper  = TRIM( r_upper  ) // ' pt(nzt+1) = pt(nzt) + dpt/dz_ini'
811
812    ENDIF
813
814    WRITE ( io, 300 )  r_lower, r_upper
815
816    IF ( .NOT. constant_diffusion )  THEN
817       IF ( ibc_e_b == 1 )  THEN
818          r_lower = 'e(0)     = e(1)'
819       ELSE
820          r_lower = 'e(0)     = e(1) = (u*/0.1)**2'
821       ENDIF
822       r_upper = 'e(nzt+1) = e(nzt) = e(nzt-1)'
823
824       WRITE ( io, 301 )  'e', r_lower, r_upper       
825
826    ENDIF
827
828    IF ( ocean_mode )  THEN
829       r_lower = 'sa(0)    = sa(1)'
830       IF ( ibc_sa_t == 0 )  THEN
831          r_upper =  'sa(nzt+1) = sa_surface'
832       ELSE
833          r_upper =  'sa(nzt+1) = sa(nzt)'
834       ENDIF
835       WRITE ( io, 301 ) 'sa', r_lower, r_upper
836    ENDIF
837
838    IF ( humidity )  THEN
839       IF ( ibc_q_b == 0 )  THEN
840          IF ( land_surface )  THEN
841             r_lower = 'q(0)     = from soil model'
842          ELSE
843             r_lower = 'q(0)     = q_surface'
844          ENDIF
845
846       ELSE
847          r_lower = 'q(0)      = q(1)'
848       ENDIF
849       IF ( ibc_q_t == 0 )  THEN
850          r_upper =  'q(nzt+1) = q_top'
851       ELSE
852          r_upper =  'q(nzt+1) = q(nzt) + dq/dz'
853       ENDIF
854       WRITE ( io, 301 ) 'q', r_lower, r_upper
855    ENDIF
856
857    IF ( passive_scalar )  THEN
858       IF ( ibc_s_b == 0 )  THEN
859          r_lower = 's(0)      = s_surface'
860       ELSE
861          r_lower = 's(0)      = s(1)'
862       ENDIF
863       IF ( ibc_s_t == 0 )  THEN
864          r_upper =  's(nzt+1) = s_top'
865       ELSEIF ( ibc_s_t == 1 )  THEN
866          r_upper =  's(nzt+1) = s(nzt)'
867       ELSEIF ( ibc_s_t == 2 )  THEN
868          r_upper =  's(nzt+1) = s(nzt) + ds/dz'
869       ENDIF
870       WRITE ( io, 301 ) 's', r_lower, r_upper
871    ENDIF
872
873    IF ( use_surface_fluxes )  THEN
874       WRITE ( io, 303 )
875       IF ( constant_heatflux )  THEN
876          IF ( large_scale_forcing .AND. lsf_surf )  THEN
877             IF ( surf_def_h(0)%ns >= 1 )  WRITE ( io, 306 )  surf_def_h(0)%shf(1)
878          ELSE
879             WRITE ( io, 306 )  surface_heatflux
880          ENDIF
881          IF ( random_heatflux )  WRITE ( io, 307 )
882       ENDIF
883       IF ( humidity  .AND.  constant_waterflux )  THEN
884          IF ( large_scale_forcing .AND. lsf_surf )  THEN
885             WRITE ( io, 311 ) surf_def_h(0)%qsws(1)
886          ELSE
887             WRITE ( io, 311 ) surface_waterflux
888          ENDIF
889       ENDIF
890       IF ( passive_scalar  .AND.  constant_scalarflux )  THEN
891          WRITE ( io, 313 ) surface_scalarflux
892       ENDIF
893    ENDIF
894
895    IF ( use_top_fluxes )  THEN
896       WRITE ( io, 304 )
897       IF ( coupling_mode == 'uncoupled' )  THEN
898          WRITE ( io, 320 )  top_momentumflux_u, top_momentumflux_v
899          IF ( constant_top_heatflux )  THEN
900             WRITE ( io, 306 )  top_heatflux
901          ENDIF
902       ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
903          WRITE ( io, 316 )
904       ENDIF
905       IF ( ocean_mode  .AND.  constant_top_salinityflux )                          &
906          WRITE ( io, 309 )  top_salinityflux
907       IF ( humidity       )  WRITE ( io, 315 )
908       IF ( passive_scalar .AND.  constant_top_scalarflux )                    &
909          WRITE ( io, 302 ) top_scalarflux
910    ENDIF
911
912    IF ( constant_flux_layer )  THEN
913       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
914                          z0h_factor*roughness_length, kappa,                  &
915                          zeta_min, zeta_max
916       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
917       IF ( humidity  .AND.  .NOT. constant_waterflux )  THEN
918          WRITE ( io, 312 )
919       ENDIF
920       IF ( passive_scalar  .AND.  .NOT. constant_scalarflux )  THEN
921          WRITE ( io, 314 )
922       ENDIF
923    ELSE
924       IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
925          WRITE ( io, 310 )  zeta_min, zeta_max
926       ENDIF
927    ENDIF
928
929    WRITE ( io, 317 )  bc_lr, bc_ns
930    IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
931       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor       
932       IF ( turbulent_inflow )  THEN
933          IF ( y_shift == 0 ) THEN
934             WRITE ( io, 319 )  recycling_width, recycling_plane, &
935                                inflow_damping_height, inflow_damping_width
936          ELSE
937             WRITE ( io, 322 )  y_shift, recycling_width, recycling_plane, &
938                                inflow_damping_height, inflow_damping_width
939          END IF
940       ENDIF
941       IF ( turbulent_outflow )  THEN
942          WRITE ( io, 323 )  outflow_source_plane, INT(outflow_source_plane/dx)
943       ENDIF
944    ENDIF
945
946!
947!-- Initial Profiles
948    WRITE ( io, 321 )
949!
950!-- Initial wind profiles
951    IF ( u_profile(1) /= 9999999.9_wp )  WRITE ( io, 427 )
952
953!
954!-- Initial temperature profile
955!-- Building output strings, starting with surface temperature
956    WRITE ( temperatures, '(F6.2)' )  pt_surface
957    gradients = '------'
958    slices = '     0'
959    coordinates = '   0.0'
960    i = 1
961    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
962
963       WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
964       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
965
966       WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
967       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
968
969       WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
970       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
971
972       WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
973       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
974
975       IF ( i == 10 )  THEN
976          EXIT
977       ELSE
978          i = i + 1
979       ENDIF
980
981    ENDDO
982
983    IF ( .NOT. nudging )  THEN
984       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
985                          TRIM( gradients ), TRIM( slices )
986    ELSE
987       WRITE ( io, 428 ) 
988    ENDIF
989
990!
991!-- Initial humidity profile
992!-- Building output strings, starting with surface humidity
993    IF ( humidity )  THEN
994       WRITE ( temperatures, '(E8.1)' )  q_surface
995       gradients = '--------'
996       slices = '       0'
997       coordinates = '     0.0'
998       i = 1
999       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
1000         
1001          WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
1002          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1003
1004          WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
1005          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1006         
1007          WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
1008          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1009         
1010          WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
1011          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1012
1013          IF ( i == 10 )  THEN
1014             EXIT
1015          ELSE
1016             i = i + 1
1017          ENDIF
1018
1019       ENDDO
1020
1021       IF ( .NOT. nudging )  THEN
1022          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ),        &
1023                             TRIM( gradients ), TRIM( slices )
1024       ENDIF
1025    ENDIF
1026!
1027!-- Initial scalar profile
1028!-- Building output strings, starting with surface humidity
1029    IF ( passive_scalar )  THEN
1030       WRITE ( temperatures, '(E8.1)' )  s_surface
1031       gradients = '--------'
1032       slices = '       0'
1033       coordinates = '     0.0'
1034       i = 1
1035       DO  WHILE ( s_vertical_gradient_level_ind(i) /= -9999 )
1036         
1037          WRITE (coor_chr,'(E8.1,4X)')  s_init(s_vertical_gradient_level_ind(i))
1038          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
1039
1040          WRITE (coor_chr,'(E8.1,4X)')  s_vertical_gradient(i)
1041          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
1042         
1043          WRITE (coor_chr,'(I8,4X)')  s_vertical_gradient_level_ind(i)
1044          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
1045         
1046          WRITE (coor_chr,'(F8.1,4X)')  s_vertical_gradient_level(i)
1047          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
1048
1049          IF ( i == 10 )  THEN
1050             EXIT
1051          ELSE
1052             i = i + 1
1053          ENDIF
1054
1055       ENDDO
1056
1057       WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ),           &
1058                          TRIM( gradients ), TRIM( slices )
1059    ENDIF   
1060
1061!
1062!-- Initial salinity profile
1063!-- Building output strings, starting with surface salinity
1064    IF ( ocean_mode )  THEN
1065       WRITE ( temperatures, '(F6.2)' )  sa_surface
1066       gradients = '------'
1067       slices = '     0'
1068       coordinates = '   0.0'
1069       i = 1
1070       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
1071
1072          WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
1073          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
1074
1075          WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
1076          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
1077
1078          WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
1079          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
1080
1081          WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
1082          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
1083
1084          IF ( i == 10 )  THEN
1085             EXIT
1086          ELSE
1087             i = i + 1
1088          ENDIF
1089
1090       ENDDO
1091
1092       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
1093                          TRIM( gradients ), TRIM( slices )
1094    ENDIF
1095
1096
1097!
1098!-- Listing of 1D-profiles
1099    WRITE ( io, 325 )  dt_dopr_listing
1100    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1101       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1102    ENDIF
1103
1104!
1105!-- DATA output
1106    WRITE ( io, 330 )
1107    IF ( averaging_interval_pr /= 0.0_wp )  THEN
1108       WRITE ( io, 326 )  averaging_interval_pr, dt_averaging_input_pr
1109    ENDIF
1110
1111!
1112!-- 1D-profiles
1113    dopr_chr = 'Profile:'
1114    IF ( dopr_n /= 0 )  THEN
1115       WRITE ( io, 331 )
1116
1117       output_format = ''
1118       output_format = netcdf_data_format_string
1119       IF ( netcdf_deflate == 0 )  THEN
1120          WRITE ( io, 344 )  output_format
1121       ELSE
1122          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1123       ENDIF
1124
1125       DO  i = 1, dopr_n
1126          dopr_chr = TRIM( dopr_chr ) // ' ' // TRIM( data_output_pr(i) ) // ','
1127          IF ( LEN_TRIM( dopr_chr ) >= 60 )  THEN
1128             WRITE ( io, 332 )  dopr_chr
1129             dopr_chr = '       :'
1130          ENDIF
1131       ENDDO
1132
1133       IF ( dopr_chr /= '' )  THEN
1134          WRITE ( io, 332 )  dopr_chr
1135       ENDIF
1136       WRITE ( io, 333 )  dt_dopr, averaging_interval_pr, dt_averaging_input_pr
1137       IF ( skip_time_dopr /= 0.0_wp )  WRITE ( io, 339 )  skip_time_dopr
1138    ENDIF
1139
1140!
1141!-- 2D-arrays
1142    DO  av = 0, 1
1143
1144       i = 1
1145       do2d_xy = ''
1146       do2d_xz = ''
1147       do2d_yz = ''
1148       DO  WHILE ( do2d(av,i) /= ' ' )
1149
1150          l = MAX( 2, LEN_TRIM( do2d(av,i) ) )
1151          do2d_mode = do2d(av,i)(l-1:l)
1152
1153          SELECT CASE ( do2d_mode )
1154             CASE ( 'xy' )
1155                ll = LEN_TRIM( do2d_xy )
1156                do2d_xy = do2d_xy(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1157             CASE ( 'xz' )
1158                ll = LEN_TRIM( do2d_xz )
1159                do2d_xz = do2d_xz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1160             CASE ( 'yz' )
1161                ll = LEN_TRIM( do2d_yz )
1162                do2d_yz = do2d_yz(1:ll) // ' ' // do2d(av,i)(1:l-3) // ','
1163          END SELECT
1164
1165          i = i + 1
1166
1167       ENDDO
1168
1169       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
1170              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
1171              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
1172
1173          IF (  av == 0 )  THEN
1174             WRITE ( io, 334 )  ''
1175          ELSE
1176             WRITE ( io, 334 )  '(time-averaged)'
1177          ENDIF
1178
1179          IF ( do2d_at_begin )  THEN
1180             begin_chr = 'and at the start'
1181          ELSE
1182             begin_chr = ''
1183          ENDIF
1184
1185          output_format = ''
1186          output_format = netcdf_data_format_string
1187          IF ( netcdf_deflate == 0 )  THEN
1188             WRITE ( io, 344 )  output_format
1189          ELSE
1190             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1191          ENDIF
1192
1193          IF ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  THEN
1194             i = 1
1195             slices = '/'
1196             coordinates = '/'
1197!
1198!--          Building strings with index and coordinate information of the
1199!--          slices
1200             DO  WHILE ( section(i,1) /= -9999 )
1201
1202                WRITE (section_chr,'(I5)')  section(i,1)
1203                section_chr = ADJUSTL( section_chr )
1204                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1205
1206                IF ( section(i,1) == -1 )  THEN
1207                   WRITE (coor_chr,'(F10.1)')  -1.0_wp
1208                ELSE
1209                   WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
1210                ENDIF
1211                coor_chr = ADJUSTL( coor_chr )
1212                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1213
1214                i = i + 1
1215             ENDDO
1216             IF ( av == 0 )  THEN
1217                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
1218                                   TRIM( begin_chr ), 'k', TRIM( slices ), &
1219                                   TRIM( coordinates )
1220                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
1221                   WRITE ( io, 339 )  skip_time_do2d_xy
1222                ENDIF
1223             ELSE
1224                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
1225                                   TRIM( begin_chr ), averaging_interval, &
1226                                   dt_averaging_input, 'k', TRIM( slices ), &
1227                                   TRIM( coordinates )
1228                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1229                   WRITE ( io, 339 )  skip_time_data_output_av
1230                ENDIF
1231             ENDIF
1232             IF ( netcdf_data_format > 4 )  THEN
1233                WRITE ( io, 352 )  ntdim_2d_xy(av)
1234             ELSE
1235                WRITE ( io, 353 )
1236             ENDIF
1237          ENDIF
1238
1239          IF ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  THEN
1240             i = 1
1241             slices = '/'
1242             coordinates = '/'
1243!
1244!--          Building strings with index and coordinate information of the
1245!--          slices
1246             DO  WHILE ( section(i,2) /= -9999 )
1247
1248                WRITE (section_chr,'(I5)')  section(i,2)
1249                section_chr = ADJUSTL( section_chr )
1250                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1251
1252                WRITE (coor_chr,'(F10.1)')  section(i,2) * dy
1253                coor_chr = ADJUSTL( coor_chr )
1254                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1255
1256                i = i + 1
1257             ENDDO
1258             IF ( av == 0 )  THEN
1259                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
1260                                   TRIM( begin_chr ), 'j', TRIM( slices ), &
1261                                   TRIM( coordinates )
1262                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
1263                   WRITE ( io, 339 )  skip_time_do2d_xz
1264                ENDIF
1265             ELSE
1266                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
1267                                   TRIM( begin_chr ), averaging_interval, &
1268                                   dt_averaging_input, 'j', TRIM( slices ), &
1269                                   TRIM( coordinates )
1270                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1271                   WRITE ( io, 339 )  skip_time_data_output_av
1272                ENDIF
1273             ENDIF
1274             IF ( netcdf_data_format > 4 )  THEN
1275                WRITE ( io, 352 )  ntdim_2d_xz(av)
1276             ELSE
1277                WRITE ( io, 353 )
1278             ENDIF
1279          ENDIF
1280
1281          IF ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 )  THEN
1282             i = 1
1283             slices = '/'
1284             coordinates = '/'
1285!
1286!--          Building strings with index and coordinate information of the
1287!--          slices
1288             DO  WHILE ( section(i,3) /= -9999 )
1289
1290                WRITE (section_chr,'(I5)')  section(i,3)
1291                section_chr = ADJUSTL( section_chr )
1292                slices = TRIM( slices ) // TRIM( section_chr ) // '/'
1293
1294                WRITE (coor_chr,'(F10.1)')  section(i,3) * dx
1295                coor_chr = ADJUSTL( coor_chr )
1296                coordinates = TRIM( coordinates ) // TRIM( coor_chr ) // '/'
1297
1298                i = i + 1
1299             ENDDO
1300             IF ( av == 0 )  THEN
1301                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
1302                                   TRIM( begin_chr ), 'i', TRIM( slices ), &
1303                                   TRIM( coordinates )
1304                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
1305                   WRITE ( io, 339 )  skip_time_do2d_yz
1306                ENDIF
1307             ELSE
1308                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
1309                                   TRIM( begin_chr ), averaging_interval, &
1310                                   dt_averaging_input, 'i', TRIM( slices ), &
1311                                   TRIM( coordinates )
1312                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1313                   WRITE ( io, 339 )  skip_time_data_output_av
1314                ENDIF
1315             ENDIF
1316             IF ( netcdf_data_format > 4 )  THEN
1317                WRITE ( io, 352 )  ntdim_2d_yz(av)
1318             ELSE
1319                WRITE ( io, 353 )
1320             ENDIF
1321          ENDIF
1322
1323       ENDIF
1324
1325    ENDDO
1326
1327!
1328!-- 3d-arrays
1329    DO  av = 0, 1
1330
1331       i = 1
1332       do3d_chr = ''
1333       DO  WHILE ( do3d(av,i) /= ' ' )
1334
1335          do3d_chr = TRIM( do3d_chr ) // ' ' // TRIM( do3d(av,i) ) // ','
1336          i = i + 1
1337
1338       ENDDO
1339
1340       IF ( do3d_chr /= '' )  THEN
1341          IF ( av == 0 )  THEN
1342             WRITE ( io, 336 )  ''
1343          ELSE
1344             WRITE ( io, 336 )  '(time-averaged)'
1345          ENDIF
1346
1347          output_format = netcdf_data_format_string
1348          IF ( netcdf_deflate == 0 )  THEN
1349             WRITE ( io, 344 )  output_format
1350          ELSE
1351             WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1352          ENDIF
1353
1354          IF ( do3d_at_begin )  THEN
1355             begin_chr = 'and at the start'
1356          ELSE
1357             begin_chr = ''
1358          ENDIF
1359          IF ( av == 0 )  THEN
1360             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
1361                                zu(nz_do3d), nz_do3d
1362          ELSE
1363             WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
1364                                TRIM( begin_chr ), averaging_interval, &
1365                                dt_averaging_input, zu(nz_do3d), nz_do3d
1366          ENDIF
1367
1368          IF ( netcdf_data_format > 4 )  THEN
1369             WRITE ( io, 352 )  ntdim_3d(av)
1370          ELSE
1371             WRITE ( io, 353 )
1372          ENDIF
1373
1374          IF ( av == 0 )  THEN
1375             IF ( skip_time_do3d /= 0.0_wp )  THEN
1376                WRITE ( io, 339 )  skip_time_do3d
1377             ENDIF
1378          ELSE
1379             IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1380                WRITE ( io, 339 )  skip_time_data_output_av
1381             ENDIF
1382          ENDIF
1383
1384       ENDIF
1385
1386    ENDDO
1387
1388!
1389!-- masked arrays
1390    IF ( masks > 0 )  WRITE ( io, 345 )  &
1391         mask_scale_x, mask_scale_y, mask_scale_z
1392    DO  mid = 1, masks
1393       DO  av = 0, 1
1394
1395          i = 1
1396          domask_chr = ''
1397          DO  WHILE ( domask(mid,av,i) /= ' ' )
1398             domask_chr = TRIM( domask_chr ) // ' ' //  &
1399                          TRIM( domask(mid,av,i) ) // ','
1400             i = i + 1
1401          ENDDO
1402
1403          IF ( domask_chr /= '' )  THEN
1404             IF ( av == 0 )  THEN
1405                WRITE ( io, 346 )  '', mid
1406             ELSE
1407                WRITE ( io, 346 )  ' (time-averaged)', mid
1408             ENDIF
1409
1410             output_format = netcdf_data_format_string
1411!--          Parallel output not implemented for mask data, hence
1412!--          output_format must be adjusted.
1413             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
1414             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
1415             IF ( netcdf_deflate == 0 )  THEN
1416                WRITE ( io, 344 )  output_format
1417             ELSE
1418                WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1419             ENDIF
1420
1421             IF ( av == 0 )  THEN
1422                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
1423             ELSE
1424                WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
1425                                   averaging_interval, dt_averaging_input
1426             ENDIF
1427
1428             IF ( av == 0 )  THEN
1429                IF ( skip_time_domask(mid) /= 0.0_wp )  THEN
1430                   WRITE ( io, 339 )  skip_time_domask(mid)
1431                ENDIF
1432             ELSE
1433                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
1434                   WRITE ( io, 339 )  skip_time_data_output_av
1435                ENDIF
1436             ENDIF
1437!
1438!--          output locations
1439             DO  dim = 1, 3
1440                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
1441                   count = 0
1442                   DO  WHILE ( mask(mid,dim,count+1) >= 0.0_wp )
1443                      count = count + 1
1444                   ENDDO
1445                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
1446                                      mask(mid,dim,:count)
1447                ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
1448                         mask_loop(mid,dim,2) < 0.0_wp .AND.  &
1449                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
1450                   WRITE ( io, 350 )  dir(dim), dir(dim)
1451                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
1452                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1453                                      mask_loop(mid,dim,1:2)
1454                ELSE
1455                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
1456                                      mask_loop(mid,dim,1:3)
1457                ENDIF
1458             ENDDO
1459          ENDIF
1460
1461       ENDDO
1462    ENDDO
1463
1464!
1465!-- Timeseries
1466    IF ( dt_dots /= 9999999.9_wp )  THEN
1467       WRITE ( io, 340 )
1468
1469       output_format = netcdf_data_format_string
1470       IF ( netcdf_deflate == 0 )  THEN
1471          WRITE ( io, 344 )  output_format
1472       ELSE
1473          WRITE ( io, 354 )  TRIM( output_format ), netcdf_deflate
1474       ENDIF
1475       WRITE ( io, 341 )  dt_dots
1476    ENDIF
1477
1478    WRITE ( io, 99 )
1479
1480!
1481!-- Physical quantities
1482    WRITE ( io, 400 )
1483
1484!
1485!-- Geostrophic parameters
1486    WRITE ( io, 410 )  latitude, longitude, rotation_angle, omega, f, fs
1487
1488!
1489!-- Day and time during model start
1490    CALL get_date_time( 0.0_wp, date_time_str=date_time_str )
1491    WRITE ( io, 456 )  TRIM( date_time_str )
1492
1493!
1494!-- Other quantities
1495    WRITE ( io, 411 )  g
1496
1497    WRITE ( io, 412 )  TRIM( reference_state )
1498    IF ( use_single_reference_value )  THEN
1499       IF ( ocean_mode )  THEN
1500          WRITE ( io, 413 )  prho_reference
1501       ELSE
1502          WRITE ( io, 414 )  pt_reference
1503       ENDIF
1504    ENDIF
1505
1506!
1507!-- Cloud physcis parameters / quantities / numerical methods
1508    WRITE ( io, 430 )
1509    IF ( humidity .AND. .NOT. bulk_cloud_model .AND. .NOT. cloud_droplets)  THEN
1510       WRITE ( io, 431 )
1511    ENDIF
1512!
1513!-- LES / turbulence parameters
1514    WRITE ( io, 450 )
1515
1516!--
1517! ... LES-constants used must still be added here
1518!--
1519    IF ( constant_diffusion )  THEN
1520       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
1521                          prandtl_number
1522    ENDIF
1523    IF ( .NOT. constant_diffusion)  THEN
1524       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
1525       IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
1526       IF ( wall_adjustment )  WRITE ( io, 453 )  wall_adjustment_factor
1527    ENDIF
1528    IF ( rans_mode )  THEN
1529       WRITE ( io, 457 )  rans_const_c, rans_const_sigma
1530    ENDIF
1531!
1532!-- Special actions during the run
1533    WRITE ( io, 470 )
1534    IF ( create_disturbances )  THEN
1535       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
1536                          zu(disturbance_level_ind_b), disturbance_level_ind_b,&
1537                          zu(disturbance_level_ind_t), disturbance_level_ind_t
1538       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
1539          WRITE ( io, 472 )  inflow_disturbance_begin, inflow_disturbance_end
1540       ELSE
1541          WRITE ( io, 473 )  disturbance_energy_limit
1542       ENDIF
1543       WRITE ( io, 474 )  TRIM( random_generator )
1544    ENDIF
1545    IF ( pt_surface_initial_change /= 0.0_wp )  THEN
1546       WRITE ( io, 475 )  pt_surface_initial_change
1547    ENDIF
1548    IF ( humidity  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1549       WRITE ( io, 476 )  q_surface_initial_change       
1550    ENDIF
1551    IF ( passive_scalar  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
1552       WRITE ( io, 477 )  q_surface_initial_change       
1553    ENDIF
1554
1555!
1556!-- Parameters of 1D-model
1557    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
1558       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
1559                          mixing_length_1d, dissipation_1d
1560       IF ( damp_level_ind_1d /= nzt+1 )  THEN
1561          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
1562       ENDIF
1563    ENDIF
1564
1565!
1566!-- Header information from other modules
1567    CALL module_interface_header( io )
1568
1569
1570    WRITE ( io, 99 )
1571
1572!
1573!-- Write buffer contents to disc immediately
1574    FLUSH( io )
1575
1576!
1577!-- Here the FORMATs start
1578
1579 99 FORMAT (1X,78('-'))
1580100 FORMAT (/1X,'******************************',4X,44('-')/        &
1581            1X,'* ',A,' *',4X,A/                               &
1582            1X,'******************************',4X,44('-'))
1583101 FORMAT (35X,'coupled run: ',A/ &
1584            35X,42('-'))
1585102 FORMAT (/' Date:               ',A10,4X,'Run:       ',A34/      &
1586            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
1587            ' Run on host:        ',A10)
1588#if defined( __parallel )
1589103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
1590              ')',1X,A)
1591104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
1592              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
1593107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
1594108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
1595109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
1596            35X,42('-'))
1597114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
1598            35X,'independent precursor runs'/             &
1599            35X,42('-'))
1600#endif
1601110 FORMAT (/' Numerical Schemes:'/ &
1602             ' -----------------'/)
1603124 FORMAT (' --> Use the ',A,' turbulence closure (',A,' mode).')
1604121 FORMAT (' --> Use the ',A,' approximation for the model equations.')
1605111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
1606112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
1607            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
1608113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
1609                  ' or Upstream')
1610115 FORMAT ('     FFT and transpositions are overlapping')
1611116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
1612                  ' or Upstream')
1613118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
1614119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
1615            '     translation velocity = ',A/ &
1616            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
1617122 FORMAT (' --> Time differencing scheme: ',A)
1618123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
1619            '     maximum damping coefficient:',F6.3, ' 1/s')
1620129 FORMAT (' --> Additional prognostic equation for the specific humidity')
1621130 FORMAT (' --> Additional prognostic equation for the total water content')
1622131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
1623                  F6.2, ' K assumed')
1624134 FORMAT (' --> Additional prognostic equation for a passive scalar')
1625135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
1626                  A,'-cycle)'/ &
1627            '     number of grid levels:                   ',I2/ &
1628            '     Gauss-Seidel red/black iterations:       ',I2)
1629136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1630                  I3,')')
1631137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
1632            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
1633                  I3,')'/ &
1634            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
1635                  I3,')')
1636139 FORMAT (' --> Loop optimization method: ',A)
1637140 FORMAT ('     maximum residual allowed:                ',E10.3)
1638141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
1639142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
1640                  'step')
1641143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
1642                  'kinetic energy')
1643144 FORMAT ('     masking method is used')
1644150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
1645                  'conserved'/ &
1646            '     using the ',A,' mode')
1647151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
1648152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
1649           /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
1650           /'     starting from dp_level_b =', F8.3, 'm', A /)
1651200 FORMAT (//' Run time and time step information:'/ &
1652             ' ----------------------------------'/)
1653201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
1654             '    CFL-factor:',F5.2)
1655202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
1656203 FORMAT ( ' Start time:        ',F11.3,' s'/ &
1657             ' End time:          ',F11.3,' s')
1658204 FORMAT ( A,F11.3,' s')
1659205 FORMAT ( A,F11.3,' s',5X,'restart every',17X,F11.3,' s')
1660206 FORMAT (/' Time reached:      ',F11.3,' s'/ &
1661             ' CPU-time used:       ',F9.3,' s     per timestep:                 ',F9.3,' s'/ &
1662             '                                      per second of simulated time: ',F9.3,' s')
1663207 FORMAT ( ' Spinup time:       ',F11.3,' s')
1664250 FORMAT (//' Computational grid and domain size:'/ &
1665              ' ----------------------------------'// &
1666              ' Grid length:      dx =    ',F8.3,' m    dy =    ',F8.3, ' m')
1667251 FORMAT (  /' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
1668              ' m  z(u) = ',F10.3,' m'/)
1669253 FORMAT ( '                dz(',I1,') =    ', F8.3, ' m')
1670254 FORMAT (//' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
1671            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
1672260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
1673             ' degrees')
1674270 FORMAT (//' Topography information:'/ &
1675              ' ----------------------'// &
1676              1X,'Topography: ',A)
1677271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
1678              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
1679                ' / ',I4)
1680272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
1681              ' direction' / &
1682              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
1683              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
1684273 FORMAT (  ' Tunnel of infinite length in ',A, &
1685              ' direction' / &
1686              ' Tunnel height: ', F6.2, / &
1687              ' Tunnel-wall depth: ', F6.2      / &
1688              ' Tunnel width: ', F6.2 )
1689274 FORMAT (  ' Tunnel in ', A, ' direction.' / &
1690              ' Tunnel height: ', F6.2, / &   
1691              ' Tunnel-wall depth: ', F6.2      / &
1692              ' Tunnel width: ', F6.2, / &
1693              ' Tunnel length: ', F6.2 )
1694278 FORMAT (' Topography grid definition convention:'/ &
1695            ' cell edge (staggered grid points'/  &
1696            ' (u in x-direction, v in y-direction))' /)
1697279 FORMAT (' Topography grid definition convention:'/ &
1698            ' cell center (scalar grid points)' /)
1699280 FORMAT (' Complex terrain simulation is activated.')
1700281 FORMAT ('    --> Mean inflow profiles are adjusted.' / &
1701            '    --> Elevation of inflow boundary: ', F7.1, ' m' )
1702282 FORMAT ('    --> Initial data from 3D-precursor run is shifted' / &
1703            '        vertically depending on local surface height.')
1704300 FORMAT (//' Boundary conditions:'/ &
1705             ' -------------------'// &
1706             '                     p                    uv             ', &
1707             '                     pt'// &
1708             ' B. bound.: ',A/ &
1709             ' T. bound.: ',A)
1710301 FORMAT (/'                     ',A// &
1711             ' B. bound.: ',A/ &
1712             ' T. bound.: ',A)
1713303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
1714304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
1715305 FORMAT (//'    Constant flux layer between bottom surface and first ',     &
1716              'computational u,v-level:'// &
1717             '       z_mo = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
1718             ' m   kappa =',F5.2/ &
1719             '       Rif value range:   ',F8.2,' <= rif <=',F6.2)
1720306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
1721307 FORMAT ('       Heatflux has a random normal distribution')
1722308 FORMAT ('       Predefined surface temperature')
1723309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
1724310 FORMAT (//'    1D-Model:'// &
1725             '       Rif value range:   ',F6.2,' <= rif <=',F6.2)
1726311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' kg/kg m/s')
1727312 FORMAT ('       Predefined surface humidity')
1728313 FORMAT ('       Predefined constant scalar flux: ',E10.3,' kg/(m**2 s)')
1729314 FORMAT ('       Predefined scalar value at the surface')
1730302 FORMAT ('       Predefined constant scalarflux:   ',F9.6,' kg/(m**2 s)')
1731315 FORMAT ('       Humidity flux at top surface is 0.0')
1732316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
1733                    'atmosphere model')
1734317 FORMAT (//' Lateral boundaries:'/ &
1735            '       left/right:  ',A/    &
1736            '       north/south: ',A)
1737318 FORMAT (/'       use_cmax: ',L1 / &
1738            '       pt damping layer width = ',F8.2,' m, pt ', &
1739                    'damping factor =',F7.4)
1740319 FORMAT ('       turbulence recycling at inflow switched on'/ &
1741            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1742            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
1743320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
1744            '                                          v: ',F9.6,' m**2/s**2')
1745321 FORMAT (//' Initial profiles:'/ &
1746              ' ----------------')
1747322 FORMAT ('       turbulence recycling at inflow switched on'/ &
1748            '       y-shift of the recycled inflow turbulence is',I3,' PE'/ &
1749            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
1750            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
1751323 FORMAT ('       turbulent outflow conditon switched on'/ &
1752            '       position of outflow source plane: ',F7.1,' m   ', &
1753                    'grid index: ', I4)
1754325 FORMAT (//' List output:'/ &
1755             ' -----------'//  &
1756            '    1D-Profiles:'/    &
1757            '       Output every             ',F10.2,' s')
1758326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
1759            '       Averaging input every    ',F8.2,' s')
1760330 FORMAT (//' Data output:'/ &
1761             ' -----------'/)
1762331 FORMAT (/'    1D-Profiles:')
1763332 FORMAT (/'       ',A)
1764333 FORMAT ('       Output every             ',F8.2,' s',/ &
1765            '       Time averaged over       ',F8.2,' s'/ &
1766            '       Averaging input every    ',F8.2,' s')
1767334 FORMAT (/'    2D-Arrays',A,':')
1768335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1769            '       Output every             ',F8.2,' s  ',A/ &
1770            '       Cross sections at ',A1,' = ',A/ &
1771            '       scalar-coordinates:   ',A,' m'/)
1772336 FORMAT (/'    3D-Arrays',A,':')
1773337 FORMAT (/'       Arrays: ',A/ &
1774            '       Output every             ',F8.2,' s  ',A/ &
1775            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1776339 FORMAT ('       No output during initial ',F8.2,' s')
1777340 FORMAT (/'    Time series:')
1778341 FORMAT ('       Output every             ',F8.2,' s'/)
1779342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
1780            '       Output every             ',F8.2,' s  ',A/ &
1781            '       Time averaged over       ',F8.2,' s'/ &
1782            '       Averaging input every    ',F8.2,' s'/ &
1783            '       Cross sections at ',A1,' = ',A/ &
1784            '       scalar-coordinates:   ',A,' m'/)
1785343 FORMAT (/'       Arrays: ',A/ &
1786            '       Output every             ',F8.2,' s  ',A/ &
1787            '       Time averaged over       ',F8.2,' s'/ &
1788            '       Averaging input every    ',F8.2,' s'/ &
1789            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
1790344 FORMAT ('       Output format: ',A/)
1791345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
1792            '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
1793            '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
1794            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
1795346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
1796347 FORMAT ('       Variables: ',A/ &
1797            '       Output every             ',F8.2,' s')
1798348 FORMAT ('       Variables: ',A/ &
1799            '       Output every             ',F8.2,' s'/ &
1800            '       Time averaged over       ',F8.2,' s'/ &
1801            '       Averaging input every    ',F8.2,' s')
1802349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1803            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
1804            13('       ',8(F8.2,',')/) )
1805350 FORMAT (/'       Output locations in ',A,'-direction: ', &
1806            'all gridpoints along ',A,'-direction (default).' )
1807351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
1808            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
1809            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
1810352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
1811353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
1812354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
1813400 FORMAT (//' Physical quantities:'/ &
1814              ' -------------------'/)
1815410 FORMAT ('    Geograph. latitude  :   latitude  = ',F5.1,' degr'/   &
1816            '    Geograph. longitude :   longitude = ',F5.1,' degr'/   &
1817            '    Rotation angle      :   rotation_angle = ',F5.1,' degr'/   &
1818            '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
1819            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
1820            '                            f*     = ',F9.6,' 1/s')
1821411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
1822412 FORMAT (/'    Reference state used in buoyancy terms: ',A)
1823413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
1824414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
1825420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
1826            '       Height:        ',A,'  m'/ &
1827            '       Temperature:   ',A,'  K'/ &
1828            '       Gradient:      ',A,'  K/100m'/ &
1829            '       Gridpoint:     ',A)
1830421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
1831            '       Height:      ',A,'  m'/ &
1832            '       Humidity:    ',A,'  kg/kg'/ &
1833            '       Gradient:    ',A,'  (kg/kg)/100m'/ &
1834            '       Gridpoint:   ',A)
1835422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
1836            '       Height:                  ',A,'  m'/ &
1837            '       Scalar concentration:    ',A,'  kg/m**3'/ &
1838            '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
1839            '       Gridpoint:               ',A)
1840423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
1841            '       Height:      ',A,'  m'/ &
1842            '       ug:          ',A,'  m/s'/ &
1843            '       Gradient:    ',A,'  1/100s'/ &
1844            '       Gridpoint:   ',A)
1845424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
1846            '       Height:      ',A,'  m'/ &
1847            '       vg:          ',A,'  m/s'/ &
1848            '       Gradient:    ',A,'  1/100s'/ &
1849            '       Gridpoint:   ',A)
1850425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
1851            '       Height:     ',A,'  m'/ &
1852            '       Salinity:   ',A,'  psu'/ &
1853            '       Gradient:   ',A,'  psu/100m'/ &
1854            '       Gridpoint:  ',A)
1855426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
1856            '       Height:      ',A,'  m'/ &
1857            '       w_subs:      ',A,'  m/s'/ &
1858            '       Gradient:    ',A,'  (m/s)/100m'/ &
1859            '       Gridpoint:   ',A)
1860427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
1861                  ' profiles')
1862428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
1863             '    NUDGING_DATA')
1864430 FORMAT (//' Cloud physics quantities / methods:'/ &
1865              ' ----------------------------------'/)
1866431 FORMAT ('    Humidity is considered, bu no condensation')
1867450 FORMAT (//' LES / Turbulence quantities:'/ &
1868              ' ---------------------------'/)
1869451 FORMAT ('    Diffusion coefficients are constant:'/ &
1870            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
1871453 FORMAT ('    Mixing length is limited to',F5.2,' * z')
1872454 FORMAT ('    TKE is not allowed to fall below ',E9.2,' (m/s)**2')
1873455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
1874456 FORMAT (/'    Date and time at model start : ',A)
1875457 FORMAT ('    RANS-mode constants: c_0 = ',F9.5/         &
1876            '                         c_1 = ',F9.5/         &
1877            '                         c_2 = ',F9.5/         &
1878            '                         c_3 = ',F9.5/         &
1879            '                         c_4 = ',F9.5/         &
1880            '                         sigma_e    = ',F9.5/  &
1881            '                         sigma_diss = ',F9.5)
1882470 FORMAT (//' Actions during the simulation:'/ &
1883              ' -----------------------------'/)
1884471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
1885            '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
1886            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
1887            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
1888472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
1889                 ' to i/j =',I4)
1890473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
1891                 F6.3, ' m**2/s**2')
1892474 FORMAT ('    Random number generator used    : ',A/)
1893475 FORMAT ('    The surface temperature is increased (or decreased, ', &
1894                 'respectively, if'/ &
1895            '    the value is negative) by ',F5.2,' K at the beginning of the',&
1896                 ' 3D-simulation'/)
1897476 FORMAT ('    The surface humidity is increased (or decreased, ',&
1898                 'respectively, if the'/ &
1899            '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
1900                 ' the 3D-simulation'/)
1901477 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
1902                 'respectively, if the'/ &
1903            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
1904                 ' the 3D-simulation'/)
1905500 FORMAT (//' 1D-Model parameters:'/                           &
1906              ' -------------------'//                           &
1907            '    Simulation time:                   ',F8.1,' s'/ &
1908            '    Run-controll output every:         ',F8.1,' s'/ &
1909            '    Vertical profile output every:     ',F8.1,' s'/ &
1910            '    Mixing length calculation:         ',A/         &
1911            '    Dissipation calculation:           ',A/)
1912502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
1913503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
1914504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
1915512 FORMAT (/' Date:               ',A10,6X,'Run:       ',A34/      &
1916            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
1917            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
1918600 FORMAT (/' Nesting informations:'/ &
1919            ' --------------------'/ &
1920            ' Nesting mode:                     ',A/ &
1921            ' Nesting-datatransfer mode:        ',A// &
1922            ' Nest id  parent  number   lower left coordinates   name'/ &
1923            ' (*=me)     id    of PEs      x (m)     y (m)' )
1924601 FORMAT (2X,A1,1X,I2.2,6X,I2.2,5X,I5,5X,F8.2,2X,F8.2,5X,A)
1925
1926 END SUBROUTINE header
Note: See TracBrowser for help on using the repository browser.