source: palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90 @ 4540

Last change on this file since 4540 was 4535, checked in by raasch, 4 years ago

bugfix for restart data format query

  • Property svn:keywords set to Id
File size: 110.6 KB
Line 
1!> @synthetic_turbulence_generator_mod.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 2017-2020 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: synthetic_turbulence_generator_mod.f90 4535 2020-05-15 12:07:23Z raasch $
27! bugfix for restart data format query
28!
29! 4495 2020-04-13 20:11:20Z raasch
30! restart data handling with MPI-IO added
31!
32! 4481 2020-03-31 18:55:54Z maronga
33! bugfix: cpp-directives for serial mode added, dummy statements to prevent compile errors added
34!
35! 4442 2020-03-04 19:21:13Z suehring
36! Set back turbulent length scale to 8 x grid spacing in the parametrized mode
37! (was accidantly changed).
38!
39! 4441 2020-03-04 19:20:35Z suehring
40! Correct misplaced preprocessor directive
41!
42! 4438 2020-03-03 20:49:28Z suehring
43! Performance optimizations in velocity-seed calculation:
44!  - random number array is only defined and computed locally (except for
45!    normalization to zero mean and unit variance)
46!  - parallel random number generator is applied independent on the 2D random
47!    numbers in other routines
48!  - option to decide wheter velocity seeds are computed locally without any
49!    further communication or are computed by all processes along the
50!    communicator
51!
52! 4346 2019-12-18 11:55:56Z motisi
53! Introduction of wall_flags_total_0, which currently sets bits based on static
54! topography information used in wall_flags_static_0
55!
56! 4335 2019-12-12 16:39:05Z suehring
57! Commentation of last commit
58!
59! 4332 2019-12-10 19:44:12Z suehring
60! Limit initial velocity seeds in restart runs, if not the seed calculation
61! may become unstable. Further, minor bugfix in initial velocity seed
62! calculation.
63!
64! 4329 2019-12-10 15:46:36Z motisi
65! Renamed wall_flags_0 to wall_flags_static_0
66!
67! 4309 2019-11-26 18:49:59Z suehring
68! Computation of velocity seeds optimized. This implies that random numbers
69! are computed now using the parallel random number generator. Random numbers
70! are now only computed and normalized locally, while distributed over all 
71! mpi ranks afterwards, instead of computing random numbers on a global array.
72! Further, the number of calls for the time-consuming velocity-seed generation
73! is reduced - now the left and right, as well as the north and south boundary
74! share the same velocity-seed matrices.
75!
76! 4182 2019-08-22 15:20:23Z scharf
77! Corrected "Former revisions" section
78!
79! 4148 2019-08-08 11:26:00Z suehring
80! Remove unused variable
81!
82! 4144 2019-08-06 09:11:47Z raasch
83! relational operators .EQ., .NE., etc. replaced by ==, /=, etc.
84!
85! 4071 2019-07-03 20:02:00Z suehring
86! Bugfix, initialize mean_inflow_profiles in case turbulence and inflow
87! information is not read from file.
88!
89! 4022 2019-06-12 11:52:39Z suehring
90! Several bugfixes and improvements
91! - revise bias correction of the imposed perturbations (correction via volume
92!   flow can create instabilities in case the mean volume flow is close to zero)
93! - introduce lower limits in calculation of coefficient matrix, else the
94!   calculation may become numerically unstable
95! - impose perturbations every timestep, even though no new set of perturbations
96!   is generated in case dt_stg_call /= dt_3d
97! - Implement a gradual decrease of Reynolds stress and length scales above
98!   ABL height (within 1 length scale above ABL depth to 1/10) rather than a
99!   discontinuous decrease
100! - Bugfix in non-nested case: use ABL height for parametrized turbulence
101!
102! 3987 2019-05-22 09:52:13Z kanani
103! Introduce alternative switch for debug output during timestepping
104!
105! 3938 2019-04-29 16:06:25Z suehring
106! Remove unused variables
107!
108! 3937 2019-04-29 15:09:07Z suehring
109! Minor bugfix in case of a very early restart where mc_factor is sill not
110! present.
111! Some modification and fixing of potential bugs in the calculation of scaling
112! parameters used for synthetic turbulence parametrization.
113!
114! 3909 2019-04-17 09:13:25Z suehring
115! Minor bugfix for last commit
116!
117! 3900 2019-04-16 15:17:43Z suehring
118! Missing re-calculation of perturbation seeds in case of restarts
119!
120! 3891 2019-04-12 17:52:01Z suehring
121! Bugfix in initialization in case of restart runs.
122!
123! 3885 2019-04-11 11:29:34Z kanani
124! Changes related to global restructuring of location messages and introduction
125! of additional debug messages
126!
127!
128! removed unused variables
129!
130! 3719 2019-02-06 13:10:18Z kanani
131! Removed log_point measurement from stg_init, since this part is counted to
132! log_point(2) 'initialisation' already. Moved other log_points to calls of
133! the subroutines in time_integration for better overview.
134!
135! 2259 2017-06-08 09:09:11Z gronemeier
136! Initial revision
137!
138! Authors:
139! --------
140! @author Tobias Gronemeier, Matthias Suehring, Atsushi Inagaki, Micha Gryschka, Christoph Knigge
141!
142!
143! Description:
144! ------------
145!> The module generates turbulence at the inflow boundary based on a method by
146!> Xie and Castro (2008) utilizing a Lund rotation (Lund, 1998) and a mass-flux
147!> correction by Kim et al. (2013).
148!> The turbulence is correlated based on length scales in y- and z-direction and
149!> a time scale for each velocity component. The profiles of length and time
150!> scales, mean u, v, w, e and pt, and all components of the Reynolds stress
151!> tensor can be either read from file STG_PROFILES, or will be parametrized
152!> within the boundary layer.
153!>
154!> @todo test restart
155!>       enable cyclic_fill
156!>       implement turbulence generation for e and pt
157!> @todo Input of height-constant length scales via namelist
158!> @note <Enter notes on the module>
159!> @bug  Height information from input file is not used. Profiles from input
160!>       must match with current PALM grid.
161!>       In case of restart, velocity seeds differ from precursor run if a11,
162!>       a22, or a33 are zero.
163!------------------------------------------------------------------------------!
164 MODULE synthetic_turbulence_generator_mod
165
166
167    USE arrays_3d,                                                             &
168        ONLY:  dzw,                                                            &
169               ddzw,                                                           &
170               drho_air,                                                       &
171               mean_inflow_profiles,                                           &
172               q,                                                              &
173               q_init,                                                         &
174               pt,                                                             &
175               pt_init,                                                        &
176               u,                                                              &
177               u_init,                                                         &
178               v,                                                              &
179               v_init,                                                         &
180               w,                                                              & 
181               zu,                                                             &
182               zw
183
184    USE basic_constants_and_equations_mod,                                     &
185        ONLY:  g,                                                              &
186               kappa,                                                          &
187               pi
188
189    USE control_parameters,                                                    &
190        ONLY:  bc_lr,                                                          &
191               bc_ns,                                                          &
192               child_domain,                                                   &
193               coupling_char,                                                  &
194               debug_output_timestep,                                          &
195               dt_3d,                                                          &
196               e_init,                                                         &
197               humidity,                                                       &
198               initializing_actions,                                           &
199               intermediate_timestep_count,                                    &
200               intermediate_timestep_count_max,                                &
201               length,                                                         &
202               message_string,                                                 &
203               nesting_offline,                                                &
204               neutral,                                                        &
205               num_mean_inflow_profiles,                                       &
206               random_generator,                                               &
207               rans_mode,                                                      &
208               restart_data_format_output,                                     &
209               restart_string,                                                 &
210               syn_turb_gen,                                                   &
211               time_since_reference_point,                                     &
212               turbulent_inflow
213
214    USE cpulog,                                                                &
215        ONLY:  cpu_log,                                                        &
216               log_point_s
217
218    USE grid_variables,                                                        &
219        ONLY:  ddx,                                                            &
220               ddy,                                                            & 
221               dx,                                                             &
222               dy
223
224    USE indices,                                                               &
225        ONLY:  nbgp,                                                           & 
226               nz,                                                             & 
227               nzb,                                                            &
228               nzt,                                                            &
229               nx,                                                             & 
230               nxl,                                                            & 
231               nxlu,                                                           &
232               nxr,                                                            & 
233               ny,                                                             &
234               nys,                                                            &
235               nysv,                                                           &
236               nyn,                                                            &
237               wall_flags_total_0
238
239    USE kinds
240
241#if defined( __parallel )  &&  !defined( __mpifh )
242    USE MPI
243#endif
244
245    USE nesting_offl_mod,                                                      &
246        ONLY:  nesting_offl_calc_zi,                                           &
247               zi_ribulk
248
249    USE pegrid,                                                                &
250        ONLY:  comm1dx,                                                        &
251               comm1dy,                                                        &
252               comm2d,                                                         &
253               ierr,                                                           &
254               myidx,                                                          &
255               myidy,                                                          &
256               pdims
257
258    USE pmc_interface,                                                         &
259        ONLY : rans_mode_parent
260
261    USE random_generator_parallel,                                             &
262        ONLY:  init_parallel_random_generator,                                 &
263               random_dummy,                                                   &
264               random_number_parallel,                                         &
265               random_seed_parallel
266
267    USE restart_data_mpi_io_mod,                                                                   &
268        ONLY:  rrd_mpi_io,                                                                         &
269               wrd_mpi_io
270
271    USE transpose_indices,                                                     &
272        ONLY: nzb_x,                                                           &
273              nzt_x
274
275    USE surface_mod,                                                           &
276        ONLY:  surf_def_h,                                                     &
277               surf_lsm_h,                                                     &
278               surf_usm_h
279
280    IMPLICIT NONE
281
282#if defined( __parallel )  &&  defined( __mpifh )
283    INCLUDE "mpif.h"
284#endif
285
286
287    LOGICAL ::  velocity_seed_initialized = .FALSE.     !< true after first call of stg_main
288    LOGICAL ::  parametrize_inflow_turbulence = .FALSE. !< flag indicating that inflow turbulence is either read from file (.FALSE.) or if it parametrized
289    LOGICAL ::  use_syn_turb_gen = .FALSE.              !< switch to use synthetic turbulence generator
290    LOGICAL ::  compute_velocity_seeds_local = .TRUE.   !< switch to decide whether velocity seeds are computed locally or if computation
291                                                        !< is distributed over several processes
292
293    INTEGER(iwp) ::  id_stg_left        !< left lateral boundary core id in case of turbulence generator
294    INTEGER(iwp) ::  id_stg_north       !< north lateral boundary core id in case of turbulence generator
295    INTEGER(iwp) ::  id_stg_right       !< right lateral boundary core id in case of turbulence generator
296    INTEGER(iwp) ::  id_stg_south       !< south lateral boundary core id in case of turbulence generator
297    INTEGER(iwp) ::  mergp              !< maximum length scale (in gp)
298    INTEGER(iwp) ::  nzb_x_stg          !< lower bound of z coordinate (required for transposing z on PEs along x)
299    INTEGER(iwp) ::  nzt_x_stg          !< upper bound of z coordinate (required for transposing z on PEs along x)
300    INTEGER(iwp) ::  nzb_y_stg          !< lower bound of z coordinate (required for transposing z on PEs along y)
301    INTEGER(iwp) ::  nzt_y_stg          !< upper bound of z coordinate (required for transposing z on PEs along y)
302#if defined( __parallel )
303    INTEGER(iwp) ::  stg_type_xz        !< MPI type for full z range
304    INTEGER(iwp) ::  stg_type_xz_small  !< MPI type for small z range
305    INTEGER(iwp) ::  stg_type_yz        !< MPI type for full z range
306    INTEGER(iwp) ::  stg_type_yz_small  !< MPI type for small z range
307#endif
308
309    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_xz = 0 !< number of non-topography grid points at xz cross-sections,
310                                                      !< required for bias correction of imposed perturbations
311    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_yz = 0 !< number of non-topography grid points at yz cross-sections,
312                                                      !< required for bias correction of imposed perturbations
313   
314#if defined( __parallel )
315    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displs_xz      !< displacement for MPI_GATHERV
316    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  recv_count_xz  !< receive count for MPI_GATHERV
317    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  displs_yz      !< displacement for MPI_GATHERV
318    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  recv_count_yz  !< receive count for MPI_GATHERV
319#endif
320    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nux            !< length scale of u in x direction (in gp)
321    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nuy            !< length scale of u in y direction (in gp)
322    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nuz            !< length scale of u in z direction (in gp)
323    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nvx            !< length scale of v in x direction (in gp)
324    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nvy            !< length scale of v in y direction (in gp)
325    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nvz            !< length scale of v in z direction (in gp)
326    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nwx            !< length scale of w in x direction (in gp)
327    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nwy            !< length scale of w in y direction (in gp)
328    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nwz            !< length scale of w in z direction (in gp)
329
330    INTEGER(isp), DIMENSION(:), ALLOCATABLE   ::  id_rand_xz     !< initial random IDs at xz inflow boundary
331    INTEGER(isp), DIMENSION(:), ALLOCATABLE   ::  id_rand_yz     !< initial random IDs at yz inflow boundary
332    INTEGER(isp), DIMENSION(:,:), ALLOCATABLE ::  seq_rand_xz    !< initial random seeds at xz inflow boundary
333    INTEGER(isp), DIMENSION(:,:), ALLOCATABLE ::  seq_rand_yz    !< initial random seeds at yz inflow boundary
334
335    REAL(wp) ::  blend                    !< value to create gradually and smooth blending of Reynolds stress and length
336                                          !< scales above the boundary layer
337    REAL(wp) ::  blend_coeff = -2.3_wp    !< coefficient used to ensure that blending functions decreases to 1/10 after
338                                          !< one length scale above ABL top
339    REAL(wp) ::  d_l                      !< blend_coeff/length_scale
340    REAL(wp) ::  length_scale             !< length scale, default is 8 x minimum grid spacing
341    REAL(wp) ::  dt_stg_adjust = 300.0_wp !< time interval for adjusting turbulence statistics
342    REAL(wp) ::  dt_stg_call = 0.0_wp     !< time interval for calling synthetic turbulence generator
343    REAL(wp) ::  scale_l                  !< scaling parameter used for turbulence parametrization - Obukhov length
344    REAL(wp) ::  scale_us                 !< scaling parameter used for turbulence parametrization - friction velocity
345    REAL(wp) ::  scale_wm                 !< scaling parameter used for turbulence parametrization - momentum scale 
346    REAL(wp) ::  time_stg_adjust = 0.0_wp !< time counter for adjusting turbulence information   
347    REAL(wp) ::  time_stg_call = 0.0_wp   !< time counter for calling generator   
348   
349    REAL(wp), DIMENSION(3) ::  mc_factor = 1.0_wp !< correction factor for the u,v,w-components to maintain original mass flux
350   
351   
352    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r11              !< Reynolds parameter
353    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r21              !< Reynolds parameter
354    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r22              !< Reynolds parameter
355    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r31              !< Reynolds parameter
356    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r32              !< Reynolds parameter
357    REAL(wp),DIMENSION(:), ALLOCATABLE ::  r33              !< Reynolds parameter
358   
359    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a11             !< coefficient for Lund rotation
360    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a21             !< coefficient for Lund rotation
361    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a22             !< coefficient for Lund rotation
362    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a31             !< coefficient for Lund rotation
363    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a32             !< coefficient for Lund rotation
364    REAL(wp), DIMENSION(:), ALLOCATABLE ::  a33             !< coefficient for Lund rotation
365    REAL(wp), DIMENSION(:), ALLOCATABLE ::  tu              !< Lagrangian time scale of u
366    REAL(wp), DIMENSION(:), ALLOCATABLE ::  tv              !< Lagrangian time scale of v
367    REAL(wp), DIMENSION(:), ALLOCATABLE ::  tw              !< Lagrangian time scale of w
368
369    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bux           !< filter function for u in x direction
370    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  buy           !< filter function for u in y direction
371    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  buz           !< filter function for u in z direction
372    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bvx           !< filter function for v in x direction
373    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bvy           !< filter function for v in y direction
374    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bvz           !< filter function for v in z direction
375    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bwx           !< filter function for w in y direction
376    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bwy           !< filter function for w in y direction
377    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  bwz           !< filter function for w in z direction
378    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fu_xz         !< velocity seed for u at xz plane
379    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fuo_xz        !< velocity seed for u at xz plane with new random number
380    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fu_yz         !< velocity seed for u at yz plane
381    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fuo_yz        !< velocity seed for u at yz plane with new random number
382    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fv_xz         !< velocity seed for v at xz plane
383    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fvo_xz        !< velocity seed for v at xz plane with new random number
384    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fv_yz         !< velocity seed for v at yz plane
385    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fvo_yz        !< velocity seed for v at yz plane with new random number
386    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fw_xz         !< velocity seed for w at xz plane
387    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fwo_xz        !< velocity seed for w at xz plane with new random number
388    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fw_yz         !< velocity seed for w at yz plane
389    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  fwo_yz        !< velocity seed for w at yz plane with new random number
390   
391    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dist_xz     !< imposed disturbances at north/south boundary
392    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  dist_yz     !< imposed disturbances at north/south boundary
393
394!
395!-- PALM interfaces:
396!-- Adjust time and lenght scales, Reynolds stress, and filter functions
397    INTERFACE stg_adjust
398       MODULE PROCEDURE stg_adjust
399    END INTERFACE stg_adjust
400!
401!-- Input parameter checks to be done in check_parameters
402    INTERFACE stg_check_parameters
403       MODULE PROCEDURE stg_check_parameters
404    END INTERFACE stg_check_parameters
405
406!
407!-- Calculate filter functions
408    INTERFACE stg_filter_func
409       MODULE PROCEDURE stg_filter_func
410    END INTERFACE stg_filter_func
411
412!
413!-- Generate velocity seeds at south and north domain boundary
414    INTERFACE stg_generate_seed_xz
415       MODULE PROCEDURE stg_generate_seed_xz
416    END INTERFACE stg_generate_seed_xz
417!
418!-- Generate velocity seeds at left and/or right domain boundary
419    INTERFACE stg_generate_seed_yz
420       MODULE PROCEDURE stg_generate_seed_yz
421    END INTERFACE stg_generate_seed_yz
422
423!
424!-- Output of information to the header file
425    INTERFACE stg_header
426       MODULE PROCEDURE stg_header
427    END INTERFACE stg_header
428
429!
430!-- Initialization actions
431    INTERFACE stg_init
432       MODULE PROCEDURE stg_init
433    END INTERFACE stg_init
434
435!
436!-- Main procedure of synth. turb. gen.
437    INTERFACE stg_main
438       MODULE PROCEDURE stg_main
439    END INTERFACE stg_main
440
441!
442!-- Reading of NAMELIST parameters
443    INTERFACE stg_parin
444       MODULE PROCEDURE stg_parin
445    END INTERFACE stg_parin
446
447!
448!-- Reading of parameters for restart runs
449    INTERFACE stg_rrd_global
450       MODULE PROCEDURE stg_rrd_global_ftn
451       MODULE PROCEDURE stg_rrd_global_mpi
452    END INTERFACE stg_rrd_global
453
454!
455!-- Writing of binary output for restart runs
456    INTERFACE stg_wrd_global
457       MODULE PROCEDURE stg_wrd_global
458    END INTERFACE stg_wrd_global
459
460    SAVE
461
462    PRIVATE
463
464!
465!-- Public interfaces
466    PUBLIC  stg_adjust, stg_check_parameters, stg_header, stg_init, stg_main,  &
467            stg_parin, stg_rrd_global, stg_wrd_global
468
469!
470!-- Public variables
471    PUBLIC  dt_stg_call, dt_stg_adjust, id_stg_left, id_stg_north,             &
472            id_stg_right, id_stg_south, parametrize_inflow_turbulence,         &
473            time_stg_adjust, time_stg_call, use_syn_turb_gen
474
475
476 CONTAINS
477
478
479!------------------------------------------------------------------------------!
480! Description:
481! ------------
482!> Check parameters routine for synthetic turbulence generator
483!------------------------------------------------------------------------------!
484 SUBROUTINE stg_check_parameters
485
486    IF ( .NOT. use_syn_turb_gen  .AND.  .NOT. rans_mode  .AND.                 &
487          nesting_offline )  THEN
488       message_string = 'Synthetic turbulence generator is required ' //       &
489                        'if offline nesting is applied and PALM operates ' //  &
490                        'in LES mode.'
491       CALL message( 'stg_check_parameters', 'PA0520', 0, 0, 0, 6, 0 )
492    ENDIF
493
494    IF ( .NOT. use_syn_turb_gen  .AND.  child_domain                           &
495         .AND. rans_mode_parent  .AND.  .NOT. rans_mode )  THEN
496       message_string = 'Synthetic turbulence generator is required ' //       &
497                        'when nesting is applied and parent operates in '  //  &
498                        'RANS-mode but current child in LES mode.'
499       CALL message( 'stg_check_parameters', 'PA0524', 1, 2, 0, 6, 0 )
500    ENDIF
501
502    IF ( use_syn_turb_gen )  THEN
503
504       IF ( child_domain  .AND.  .NOT. rans_mode  .AND.                        &
505                                 .NOT. rans_mode_parent )  THEN
506          message_string = 'Using synthetic turbulence generator ' //          &
507                           'is not allowed in LES-LES nesting.'
508          CALL message( 'stg_check_parameters', 'PA0620', 1, 2, 0, 6, 0 )
509       
510       ENDIF
511       
512       IF ( child_domain  .AND.  rans_mode  .AND.                              &
513                                 rans_mode_parent )  THEN
514          message_string = 'Using synthetic turbulence generator ' //          &
515                           'is not allowed in RANS-RANS nesting.'
516          CALL message( 'stg_check_parameters', 'PA0621', 1, 2, 0, 6, 0 )
517       
518       ENDIF
519   
520       IF ( .NOT. nesting_offline  .AND.  .NOT. child_domain )  THEN
521       
522          IF ( INDEX( initializing_actions, 'set_constant_profiles' ) == 0     &
523        .AND.  INDEX( initializing_actions, 'read_restart_data' ) == 0 )  THEN
524             message_string = 'Using synthetic turbulence generator ' //       &
525                            'requires %initializing_actions = '         //     &
526                            '"set_constant_profiles" or "read_restart_data"' //&
527                            ', if not offline nesting is applied.'
528             CALL message( 'stg_check_parameters', 'PA0015', 1, 2, 0, 6, 0 )
529          ENDIF
530
531          IF ( bc_lr /= 'dirichlet/radiation' )  THEN
532             message_string = 'Using synthetic turbulence generator ' //       &
533                              'requires &bc_lr = "dirichlet/radiation", ' //   &
534                              'if not offline nesting is applied.'
535             CALL message( 'stg_check_parameters', 'PA0035', 1, 2, 0, 6, 0 )
536          ENDIF
537          IF ( bc_ns /= 'cyclic' )  THEN
538             message_string = 'Using synthetic turbulence generator ' //       &
539                              'requires &bc_ns = "cyclic", ' //                &
540                              'if not offline nesting is applied.'
541             CALL message( 'stg_check_parameters', 'PA0037', 1, 2, 0, 6, 0 )
542          ENDIF
543
544       ENDIF
545
546       IF ( turbulent_inflow )  THEN
547          message_string = 'Using synthetic turbulence generator ' //          &
548                           'in combination &with turbulent_inflow = .T. '//    &
549                              'is not allowed'
550          CALL message( 'stg_check_parameters', 'PA0039', 1, 2, 0, 6, 0 )
551       ENDIF
552!
553!--    Synthetic turbulence generator requires the parallel random generator
554       IF ( random_generator /= 'random-parallel' )  THEN
555          message_string = 'Using synthetic turbulence generator ' //          &
556                           'requires random_generator = random-parallel.'
557          CALL message( 'stg_check_parameters', 'PA0421', 1, 2, 0, 6, 0 )
558       ENDIF
559
560    ENDIF
561
562 END SUBROUTINE stg_check_parameters
563
564
565!------------------------------------------------------------------------------!
566! Description:
567! ------------
568!> Header output for synthetic turbulence generator
569!------------------------------------------------------------------------------!
570 SUBROUTINE stg_header ( io )
571
572    INTEGER(iwp), INTENT(IN) ::  io   !< Unit of the output file
573
574!
575!-- Write synthetic turbulence generator Header
576    WRITE( io, 1 )
577    IF ( use_syn_turb_gen )  THEN
578       WRITE( io, 2 )
579    ELSE
580       WRITE( io, 3 )
581    ENDIF
582   
583    IF ( parametrize_inflow_turbulence )  THEN
584       WRITE( io, 4 ) dt_stg_adjust
585    ELSE
586       WRITE( io, 5 )
587    ENDIF
588
5891   FORMAT (//' Synthetic turbulence generator information:'/                  &
590              ' ------------------------------------------'/)
5912   FORMAT ('    synthetic turbulence generator is switched on')
5923   FORMAT ('    synthetic turbulence generator is switched off')
5934   FORMAT ('    imposed turbulence statistics are parametrized and ajdusted to boundary-layer development each ', F8.2, ' s' )
5945   FORMAT ('    imposed turbulence is read from file' )
595
596 END SUBROUTINE stg_header
597
598
599!------------------------------------------------------------------------------!
600! Description:
601! ------------
602!> Initialization of the synthetic turbulence generator
603!------------------------------------------------------------------------------!
604 SUBROUTINE stg_init
605
606    LOGICAL ::  file_stg_exist = .FALSE. !< flag indicating whether parameter file for Reynolds stress and length scales exist
607
608#if defined( __parallel )
609    INTEGER(KIND=MPI_ADDRESS_KIND) :: extent !< extent of new MPI type
610    INTEGER(KIND=MPI_ADDRESS_KIND) :: tob=0  !< dummy variable
611#endif
612
613    INTEGER(iwp) :: i                        !> grid index in x-direction
614    INTEGER(iwp) :: j                        !> loop index
615    INTEGER(iwp) :: k                        !< index
616#if defined( __parallel )
617    INTEGER(iwp) :: newtype                  !< dummy MPI type
618    INTEGER(iwp) :: realsize                 !< size of REAL variables
619#endif
620
621    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_xz_l = 0 !< number of non-topography grid points at xz-cross-section on subdomain
622    INTEGER(iwp), DIMENSION(3) ::  nr_non_topo_yz_l = 0 !< number of non-topography grid points at yz-cross-section on subdomain
623!
624!-- Dummy variables used for reading profiles
625    REAL(wp) :: d1      !< u profile
626    REAL(wp) :: d2      !< v profile
627    REAL(wp) :: d3      !< w profile
628    REAL(wp) :: d5      !< e profile
629    REAL(wp) :: luy     !< length scale for u in y direction
630    REAL(wp) :: luz     !< length scale for u in z direction
631    REAL(wp) :: lvy     !< length scale for v in y direction
632    REAL(wp) :: lvz     !< length scale for v in z direction
633    REAL(wp) :: lwy     !< length scale for w in y direction
634    REAL(wp) :: lwz     !< length scale for w in z direction
635#if defined( __parallel )
636    REAL(wp) :: nnz     !< increment used to determine processor decomposition of z-axis along x and y direction
637#endif
638    REAL(wp) :: zz      !< height
639
640
641#if defined( __parallel )
642    CALL MPI_BARRIER( comm2d, ierr )
643#endif
644!
645!-- Create mpi-datatypes for exchange in case of non-local but distributed
646!-- computation of the velocity seeds. This option is useful in
647!-- case large turbulent length scales are present, where the computational
648!-- effort becomes large and need to be parallelized. For parameterized
649!-- turbulence the length scales are small and computing the velocity seeds
650!-- locally is faster (no overhead by communication).
651    IF ( .NOT. compute_velocity_seeds_local )  THEN
652#if defined( __parallel )
653!     
654!--    Determine processor decomposition of z-axis along x- and y-direction
655       nnz = nz / pdims(1)
656       nzb_x_stg = 1 + myidx * INT( nnz )
657       nzt_x_stg = ( myidx + 1 ) * INT( nnz )
658       
659       IF ( MOD( nz , pdims(1) ) /= 0  .AND.  myidx == id_stg_right )          &
660          nzt_x_stg = nzt_x_stg + myidx * ( nnz - INT( nnz ) )
661       
662       IF ( nesting_offline   .OR.  ( child_domain  .AND.  rans_mode_parent    &
663                               .AND.  .NOT.  rans_mode ) )  THEN
664          nnz = nz / pdims(2)
665          nzb_y_stg = 1 + myidy * INT( nnz )
666          nzt_y_stg = ( myidy + 1 ) * INT( nnz )
667       
668          IF ( MOD( nz , pdims(2) ) /= 0  .AND.  myidy == id_stg_north )       &
669             nzt_y_stg = nzt_y_stg + myidy * ( nnz - INT( nnz ) )
670       ENDIF
671       
672!     
673!--    Define MPI type used in stg_generate_seed_yz to gather vertical splitted
674!--    velocity seeds
675       CALL MPI_TYPE_SIZE( MPI_REAL, realsize, ierr )
676       extent = 1 * realsize
677!     
678!--    Set-up MPI datatyp to involve all cores for turbulence generation at yz
679!--    layer
680!--    stg_type_yz: yz-slice with vertical bounds nzb:nzt+1
681       CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nyn-nys+1],                &
682               [1,nyn-nys+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr )
683       CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_yz, ierr )
684       CALL MPI_TYPE_COMMIT( stg_type_yz, ierr )
685       CALL MPI_TYPE_FREE( newtype, ierr )
686       
687       ! stg_type_yz_small: yz-slice with vertical bounds nzb_x_stg:nzt_x_stg+1
688       CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_x_stg-nzb_x_stg+2,nyn-nys+1],    &
689               [1,nyn-nys+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr )
690       CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_yz_small, ierr )
691       CALL MPI_TYPE_COMMIT( stg_type_yz_small, ierr )
692       CALL MPI_TYPE_FREE( newtype, ierr )
693       
694       ! receive count and displacement for MPI_GATHERV in stg_generate_seed_yz
695       ALLOCATE( recv_count_yz(pdims(1)), displs_yz(pdims(1)) )
696       
697       recv_count_yz           = nzt_x_stg-nzb_x_stg + 1
698       recv_count_yz(pdims(1)) = recv_count_yz(pdims(1)) + 1
699       
700       DO  j = 1, pdims(1)
701          displs_yz(j) = 0 + (nzt_x_stg-nzb_x_stg+1) * (j-1)
702       ENDDO
703!     
704!--    Set-up MPI datatyp to involve all cores for turbulence generation at xz
705!--    layer
706!--    stg_type_xz: xz-slice with vertical bounds nzb:nzt+1
707       IF ( nesting_offline  .OR.  ( child_domain .AND.  rans_mode_parent      &
708                              .AND.  .NOT.  rans_mode ) )  THEN
709          CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nxr-nxl+1],             &
710                  [1,nxr-nxl+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr )
711          CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_xz, ierr )
712          CALL MPI_TYPE_COMMIT( stg_type_xz, ierr )
713          CALL MPI_TYPE_FREE( newtype, ierr )
714       
715          ! stg_type_yz_small: xz-slice with vertical bounds nzb_x_stg:nzt_x_stg+1
716          CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_y_stg-nzb_y_stg+2,nxr-nxl+1], &
717                  [1,nxr-nxl+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr )
718          CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_xz_small, ierr )
719          CALL MPI_TYPE_COMMIT( stg_type_xz_small, ierr )
720          CALL MPI_TYPE_FREE( newtype, ierr )
721       
722          ! receive count and displacement for MPI_GATHERV in stg_generate_seed_yz
723          ALLOCATE( recv_count_xz(pdims(2)), displs_xz(pdims(2)) )
724       
725          recv_count_xz           = nzt_y_stg-nzb_y_stg + 1
726          recv_count_xz(pdims(2)) = recv_count_xz(pdims(2)) + 1
727       
728          DO  j = 1, pdims(2)
729             displs_xz(j) = 0 + (nzt_y_stg-nzb_y_stg+1) * (j-1)
730          ENDDO
731       
732       ENDIF
733#endif
734    ENDIF
735!
736!-- Allocate required arrays.
737!-- In case no offline nesting or self nesting is used, the arrary
738!-- mean_inflow profiles is required. Check if it is already allocated, else
739!-- allocate and initialize it appropriately. Note, in case turbulence and
740!-- inflow information is read from file, mean_inflow_profiles is already
741!-- allocated and initialized appropriately.
742    IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )  THEN
743       IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
744          ALLOCATE( mean_inflow_profiles(nzb:nzt+1,1:num_mean_inflow_profiles) )
745          mean_inflow_profiles = 0.0_wp
746          mean_inflow_profiles(:,1) = u_init
747          mean_inflow_profiles(:,2) = v_init
748!
749!--       Even though potential temperature and humidity are not perturbed,
750!--       they need to be initialized appropriately.
751          IF ( .NOT. neutral )                                                 &
752             mean_inflow_profiles(:,4) = pt_init
753          IF ( humidity )                                                      &
754             mean_inflow_profiles(:,6) = q_init       
755       ENDIF   
756    ENDIF
757
758    ALLOCATE ( a11(nzb:nzt+1), a21(nzb:nzt+1), a22(nzb:nzt+1),                 &
759               a31(nzb:nzt+1), a32(nzb:nzt+1), a33(nzb:nzt+1),                 &
760               nux(nzb:nzt+1), nuy(nzb:nzt+1), nuz(nzb:nzt+1),                 &
761               nvx(nzb:nzt+1), nvy(nzb:nzt+1), nvz(nzb:nzt+1),                 &
762               nwx(nzb:nzt+1), nwy(nzb:nzt+1), nwz(nzb:nzt+1),                 &
763               r11(nzb:nzt+1), r21(nzb:nzt+1), r22(nzb:nzt+1),                 &
764               r31(nzb:nzt+1), r32(nzb:nzt+1), r33(nzb:nzt+1),                 &
765               tu(nzb:nzt+1),  tv(nzb:nzt+1),  tw(nzb:nzt+1)   )
766               
767    ALLOCATE ( dist_xz(nzb:nzt+1,nxl:nxr,3) )
768    ALLOCATE ( dist_yz(nzb:nzt+1,nys:nyn,3) )
769    dist_xz = 0.0_wp
770    dist_yz = 0.0_wp
771!
772!-- Read inflow profile
773!-- Height levels of profiles in input profile is as follows:
774!-- zu: luy, luz, tu, lvy, lvz, tv, r11, r21, r22, d1, d2, d5
775!-- zw: lwy, lwz, tw, r31, r32, r33, d3
776!-- WARNING: zz is not used at the moment
777    INQUIRE( FILE = 'STG_PROFILES' // TRIM( coupling_char ),                   &
778             EXIST = file_stg_exist  )
779
780    IF ( file_stg_exist )  THEN
781
782       OPEN( 90, FILE='STG_PROFILES'//TRIM( coupling_char ), STATUS='OLD',     &
783                      FORM='FORMATTED')
784!
785!--    Skip header
786       READ( 90, * )
787
788       DO  k = nzb+1, nzt+1
789          READ( 90, * ) zz, luy, luz, tu(k), lvy, lvz, tv(k), lwy, lwz, tw(k), &
790                        r11(k), r21(k), r22(k), r31(k), r32(k), r33(k),        &
791                        d1, d2, d3, d5
792
793!
794!--       Convert length scales from meter to number of grid points.
795          nuy(k) = INT( luy * ddy )
796          nuz(k) = INT( luz * ddzw(k) )
797          nvy(k) = INT( lvy * ddy )
798          nvz(k) = INT( lvz * ddzw(k) )
799          nwy(k) = INT( lwy * ddy )
800          nwz(k) = INT( lwz * ddzw(k) )
801!
802!--       Workaround, assume isotropic turbulence
803          nwx(k) = nwy(k)
804          nvx(k) = nvy(k)
805          nux(k) = nuy(k)
806!
807!--       Save Mean inflow profiles
808          IF ( TRIM( initializing_actions ) /= 'read_restart_data' ) THEN
809             mean_inflow_profiles(k,1) = d1
810             mean_inflow_profiles(k,2) = d2
811            !  mean_inflow_profiles(k,4) = d4
812             mean_inflow_profiles(k,5) = d5
813          ENDIF
814       ENDDO
815!
816!--    Set lenght scales at surface grid point
817       nuy(nzb) = nuy(nzb+1) 
818       nuz(nzb) = nuz(nzb+1)
819       nvy(nzb) = nvy(nzb+1)
820       nvz(nzb) = nvz(nzb+1)
821       nwy(nzb) = nwy(nzb+1)
822       nwz(nzb) = nwz(nzb+1)
823       
824       CLOSE( 90 )
825!
826!--    Calculate coefficient matrix from Reynolds stress tensor 
827!--    (Lund rotation)
828       CALL calc_coeff_matrix
829!
830!-- No information about turbulence and its length scales are available.
831!-- Instead, parametrize turbulence which is imposed at the boundaries.
832!-- Set flag which indicates that turbulence is parametrized, which is done
833!-- later when energy-balance models are already initialized. This is
834!-- because the STG needs information about surface properties such as
835!-- roughness to build 'realistic' turbulence profiles.
836    ELSE
837!
838!--    Define length scale for the imposed turbulence, which is defined as
839!--    8 times the minimum grid spacing
840       length_scale = 8.0_wp * MIN( dx, dy, MINVAL( dzw ) )
841!
842!--    Define constant to gradually decrease length scales and Reynolds stress
843!--    above ABL top. Assure that no zero length scales are used.
844       d_l = blend_coeff / MAX( length_scale, dx, dy, MINVAL( dzw ) )
845!
846!--    Set flag indicating that turbulence is parametrized
847       parametrize_inflow_turbulence = .TRUE.
848!
849!--    In case of dirichlet inflow boundary conditions only at one lateral
850!--    boundary, i.e. in the case no offline or self nesting is applied but
851!--    synthetic turbulence shall be parametrized nevertheless, the
852!--    boundary-layer depth need to determined first.
853       IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )                &
854          CALL nesting_offl_calc_zi
855!
856!--    Determine boundary-layer depth, which is used to initialize lenght
857!--    scales
858       CALL calc_scaling_variables
859!
860!--    Initialize lenght and time scales, which in turn are used
861!--    to initialize the filter functions.
862       CALL calc_length_and_time_scale
863!
864!--    Parametrize Reynolds-stress tensor, diagonal elements as well
865!--    as r21 (v'u'), r31 (w'u'), r32 (w'v'). Parametrization follows
866!--    Rotach et al. (1996) and is based on boundary-layer depth,
867!--    friction velocity and velocity scale.
868       CALL parametrize_reynolds_stress
869!     
870!--    Calculate coefficient matrix from Reynolds stress tensor 
871!--    (Lund rotation)
872       CALL calc_coeff_matrix
873           
874    ENDIF
875
876!
877!-- Assign initial profiles. Note, this is only required if turbulent
878!-- inflow from the left is desired, not in case of any of the
879!-- nesting (offline or self nesting) approaches.
880    IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )  THEN
881       u_init = mean_inflow_profiles(:,1)
882       v_init = mean_inflow_profiles(:,2)
883      !pt_init = mean_inflow_profiles(:,4)
884       e_init = MAXVAL( mean_inflow_profiles(:,5) )
885    ENDIF
886   
887!
888!-- Define the size of the filter functions and allocate them.
889    mergp = 0
890
891    ! arrays must be large enough to cover the largest length scale
892    DO  k = nzb, nzt+1
893       j = MAX( ABS(nux(k)), ABS(nuy(k)), ABS(nuz(k)), &
894                ABS(nvx(k)), ABS(nvy(k)), ABS(nvz(k)), &
895                ABS(nwx(k)), ABS(nwy(k)), ABS(nwz(k))  )
896       IF ( j > mergp )  mergp = j
897    ENDDO
898
899!     mergp  = 2 * mergp
900!     mergp = mergp
901
902    ALLOCATE ( bux(-mergp:mergp,nzb:nzt+1),                                      &
903               buy(-mergp:mergp,nzb:nzt+1),                                      &
904               buz(-mergp:mergp,nzb:nzt+1),                                      &
905               bvx(-mergp:mergp,nzb:nzt+1),                                      &
906               bvy(-mergp:mergp,nzb:nzt+1),                                      &
907               bvz(-mergp:mergp,nzb:nzt+1),                                      &
908               bwx(-mergp:mergp,nzb:nzt+1),                                      &
909               bwy(-mergp:mergp,nzb:nzt+1),                                      &
910               bwz(-mergp:mergp,nzb:nzt+1)  )
911
912!
913!-- Allocate velocity seeds for turbulence at xz-layer
914    ALLOCATE ( fu_xz( nzb:nzt+1,nxl:nxr), fuo_xz(nzb:nzt+1,nxl:nxr),       &
915               fv_xz( nzb:nzt+1,nxl:nxr), fvo_xz(nzb:nzt+1,nxl:nxr),       &
916               fw_xz( nzb:nzt+1,nxl:nxr), fwo_xz(nzb:nzt+1,nxl:nxr)  )
917
918!
919!-- Allocate velocity seeds for turbulence at yz-layer
920    ALLOCATE ( fu_yz( nzb:nzt+1,nys:nyn), fuo_yz(nzb:nzt+1,nys:nyn),       &
921               fv_yz( nzb:nzt+1,nys:nyn), fvo_yz(nzb:nzt+1,nys:nyn),       &
922               fw_yz( nzb:nzt+1,nys:nyn), fwo_yz(nzb:nzt+1,nys:nyn)  )
923
924    fu_xz  = 0.0_wp
925    fuo_xz = 0.0_wp
926    fv_xz  = 0.0_wp
927    fvo_xz = 0.0_wp
928    fw_xz  = 0.0_wp
929    fwo_xz = 0.0_wp
930
931    fu_yz  = 0.0_wp
932    fuo_yz = 0.0_wp
933    fv_yz  = 0.0_wp
934    fvo_yz = 0.0_wp
935    fw_yz  = 0.0_wp
936    fwo_yz = 0.0_wp
937
938!
939!-- Create filter functions
940    CALL stg_filter_func( nux, bux ) !filter ux
941    CALL stg_filter_func( nuy, buy ) !filter uy
942    CALL stg_filter_func( nuz, buz ) !filter uz
943    CALL stg_filter_func( nvx, bvx ) !filter vx
944    CALL stg_filter_func( nvy, bvy ) !filter vy
945    CALL stg_filter_func( nvz, bvz ) !filter vz
946    CALL stg_filter_func( nwx, bwx ) !filter wx
947    CALL stg_filter_func( nwy, bwy ) !filter wy
948    CALL stg_filter_func( nwz, bwz ) !filter wz
949
950#if defined( __parallel )
951    CALL MPI_BARRIER( comm2d, ierr )
952#endif
953
954!
955!-- In case of restart, calculate velocity seeds fu, fv, fw from former
956!   time step.
957!   Bug: fu, fv, fw are different in those heights where a11, a22, a33
958!        are 0 compared to the prerun. This is mostly for k=nzt+1.
959    IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
960       IF ( myidx == id_stg_left  .OR.  myidx == id_stg_right )  THEN
961
962          IF ( myidx == id_stg_left  )  i = -1
963          IF ( myidx == id_stg_right )  i = nxr+1
964
965          DO  j = nys, nyn
966             DO  k = nzb, nzt+1
967                IF  ( a11(k) > 10E-8_wp )  THEN
968                   fu_yz(k,j) = ( u(k,j,i) - u_init(k) ) / a11(k)
969                ELSE
970                   fu_yz(k,j) = 10E-8_wp
971                ENDIF
972
973                IF  ( a22(k) > 10E-8_wp )  THEN
974                   fv_yz(k,j) = ( v(k,j,i) -                                  &
975                                  a21(k) * fu_yz(k,j) - v_init(k) ) / a22(k)
976                ELSE
977                   fv_yz(k,j) = 10E-8_wp
978                ENDIF
979
980                IF  ( a33(k) > 10E-8_wp )  THEN
981                   fw_yz(k,j) = ( w(k,j,i) -                                   &
982                                  a31(k) * fu_yz(k,j) - a32(k) *               &
983                                  fv_yz(k,j) ) / a33(k)
984                ELSE
985                   fw_yz(k,j) = 10E-8_wp
986                ENDIF
987             ENDDO
988          ENDDO
989       ENDIF
990       
991       IF ( myidy == id_stg_south  .OR.  myidy == id_stg_north )  THEN
992
993          IF ( myidy == id_stg_south )  j = -1
994          IF ( myidy == id_stg_north )  j = nyn+1
995
996          DO  i = nxl, nxr
997             DO  k = nzb, nzt+1
998!
999!--             In case the correlation coefficients are very small, the
1000!--             velocity seeds may become very large finally creating
1001!--             numerical instabilities in the synthetic turbulence generator.
1002!--             Empirically, a value of 10E-8 seems to be sufficient.
1003                IF  ( a11(k) > 10E-8_wp )  THEN
1004                   fu_xz(k,i) = ( u(k,j,i) - u_init(k) ) / a11(k)
1005                ELSE
1006                   fu_xz(k,i) = 10E-8_wp
1007                ENDIF
1008
1009                IF  ( a22(k) > 10E-8_wp )  THEN
1010                   fv_xz(k,i) = ( v(k,j,i) -                                   &
1011                                  a21(k) * fu_xz(k,i) - v_init(k) ) / a22(k)
1012                ELSE
1013                   fv_xz(k,i) = 10E-8_wp
1014                ENDIF
1015
1016                IF  ( a33(k) > 10E-8_wp )  THEN
1017                   fw_xz(k,i) = ( w(k,j,i) -                                   &
1018                                  a31(k) * fu_xz(k,i) -                        &
1019                                  a32(k) * fv_xz(k,i) ) / a33(k)
1020                ELSE
1021                   fw_xz(k,i) = 10E-8_wp
1022                ENDIF
1023
1024             ENDDO
1025          ENDDO
1026       ENDIF
1027    ENDIF
1028!
1029!-- Count the number of non-topography grid points at the boundaries where
1030!-- perturbations are imposed. This number is later used for bias corrections
1031!-- of the perturbations, i.e. to force that their mean is zero. Please note,
1032!-- due to the asymetry of u and v along x and y direction, respectively,
1033!-- different cases must be distinguished.
1034    IF ( myidx == id_stg_left  .OR.  myidx == id_stg_right )  THEN
1035!
1036!--    Number of grid points where perturbations are imposed on u
1037       IF ( myidx == id_stg_left  )  i = nxl
1038       IF ( myidx == id_stg_right )  i = nxr+1
1039       
1040       nr_non_topo_yz_l(1) = SUM(                                              &
1041                          MERGE( 1, 0,                                         &
1042                          BTEST( wall_flags_total_0(nzb:nzt,nys:nyn,i), 1 ) ) )
1043!
1044!--    Number of grid points where perturbations are imposed on v and w                                   
1045       IF ( myidx == id_stg_left  )  i = nxl-1
1046       IF ( myidx == id_stg_right )  i = nxr+1
1047       
1048       nr_non_topo_yz_l(2) = SUM(                                              &
1049                          MERGE( 1, 0,                                         &
1050                          BTEST( wall_flags_total_0(nzb:nzt,nysv:nyn,i), 2 ) ) )
1051       nr_non_topo_yz_l(3) = SUM(                                              &
1052                          MERGE( 1, 0,                                         &
1053                          BTEST( wall_flags_total_0(nzb:nzt,nys:nyn,i), 3 ) ) )
1054                                   
1055#if defined( __parallel )
1056       CALL MPI_ALLREDUCE( nr_non_topo_yz_l, nr_non_topo_yz, 3, MPI_INTEGER,   &
1057                           MPI_SUM, comm1dy, ierr )
1058#else
1059       nr_non_topo_yz = nr_non_topo_yz_l
1060#endif 
1061    ENDIF
1062   
1063    IF ( myidy == id_stg_south  .OR.  myidy == id_stg_north )  THEN
1064!
1065!--    Number of grid points where perturbations are imposed on v
1066       IF ( myidy == id_stg_south )  j = nys
1067       IF ( myidy == id_stg_north )  j = nyn+1
1068       
1069       nr_non_topo_xz_l(2) = SUM(                                              &
1070                          MERGE( 1, 0,                                         &
1071                          BTEST( wall_flags_total_0(nzb:nzt,j,nxl:nxr), 2 ) ) )
1072!
1073!--    Number of grid points where perturbations are imposed on u and w
1074       IF ( myidy == id_stg_south )  j = nys-1
1075       IF ( myidy == id_stg_north )  j = nyn+1
1076       
1077       nr_non_topo_xz_l(1) = SUM(                                              &
1078                          MERGE( 1, 0,                                         &
1079                          BTEST( wall_flags_total_0(nzb:nzt,j,nxlu:nxr), 1 ) ) )
1080       nr_non_topo_xz_l(3) = SUM(                                              &
1081                          MERGE( 1, 0,                                         &
1082                          BTEST( wall_flags_total_0(nzb:nzt,j,nxl:nxr), 3 ) ) )
1083                                   
1084#if defined( __parallel )
1085       CALL MPI_ALLREDUCE( nr_non_topo_xz_l, nr_non_topo_xz, 3, MPI_INTEGER,   &
1086                           MPI_SUM, comm1dx, ierr )
1087#else
1088       nr_non_topo_xz = nr_non_topo_xz_l
1089#endif 
1090    ENDIF
1091!
1092!-- Initialize random number generator at xz- and yz-layers. Random numbers
1093!-- are initialized at each core. In case there is only inflow from the left,
1094!-- it is sufficient to generate only random numbers for the yz-layer, else
1095!-- random numbers for the xz-layer are also required.
1096    ALLOCATE ( id_rand_yz(-mergp+nys:nyn+mergp) )
1097    ALLOCATE ( seq_rand_yz(5,-mergp+nys:nyn+mergp) )
1098    id_rand_yz  = 0
1099    seq_rand_yz = 0
1100
1101    CALL init_parallel_random_generator( ny, -mergp+nys, nyn+mergp,            &
1102                                         id_rand_yz, seq_rand_yz )
1103
1104    IF ( nesting_offline  .OR.  ( child_domain .AND.  rans_mode_parent         &
1105                           .AND.  .NOT.  rans_mode ) )  THEN
1106       ALLOCATE ( id_rand_xz(-mergp+nxl:nxr+mergp) )
1107       ALLOCATE ( seq_rand_xz(5,-mergp+nxl:nxr+mergp) )
1108       id_rand_xz  = 0
1109       seq_rand_xz = 0
1110
1111       CALL init_parallel_random_generator( nx, -mergp+nxl, nxr+mergp,         &
1112                                            id_rand_xz, seq_rand_xz )
1113    ENDIF
1114
1115
1116
1117 END SUBROUTINE stg_init
1118
1119
1120!------------------------------------------------------------------------------!
1121! Description:
1122! ------------
1123!> Calculate filter function bxx from length scale nxx following Eg.9 and 10
1124!> (Xie and Castro, 2008)
1125!------------------------------------------------------------------------------!
1126 SUBROUTINE stg_filter_func( nxx, bxx )
1127
1128    INTEGER(iwp) :: k         !< loop index
1129    INTEGER(iwp) :: n_k       !< length scale nXX in height k
1130    INTEGER(iwp) :: nf        !< index for length scales
1131
1132    REAL(wp) :: bdenom        !< denominator for filter functions bXX
1133    REAL(wp) :: qsi = 1.0_wp  !< minimization factor
1134
1135    INTEGER(iwp), DIMENSION(nzb:nzt+1) ::  nxx         !< length scale (in gp)
1136
1137    REAL(wp), DIMENSION(-mergp:mergp,nzb:nzt+1) ::  bxx  !< filter function
1138
1139
1140    bxx = 0.0_wp
1141
1142    DO  k = nzb, nzt+1
1143       bdenom = 0.0_wp
1144       n_k    = nxx(k)
1145       IF ( n_k /= 0 )  THEN
1146
1147!
1148!--       ( Eq.10 )^2
1149          DO  nf = -n_k, n_k
1150             bdenom = bdenom + EXP( -qsi * pi * ABS(nf) / n_k )**2
1151          ENDDO
1152
1153!
1154!--       ( Eq.9 )
1155          bdenom = SQRT( bdenom )
1156          DO  nf = -n_k, n_k
1157             bxx(nf,k) = EXP( -qsi * pi * ABS(nf) / n_k ) / bdenom
1158          ENDDO
1159       ENDIF
1160    ENDDO
1161
1162 END SUBROUTINE stg_filter_func
1163
1164
1165!------------------------------------------------------------------------------!
1166! Description:
1167! ------------
1168!> Parin for &stg_par for synthetic turbulence generator
1169!------------------------------------------------------------------------------!
1170 SUBROUTINE stg_parin
1171
1172    CHARACTER (LEN=80) ::  line   !< dummy string that contains the current line of the parameter file
1173
1174
1175    NAMELIST /stg_par/  dt_stg_adjust,                                         &
1176                        dt_stg_call,                                           &
1177                        use_syn_turb_gen,                                      &
1178                        compute_velocity_seeds_local
1179
1180    line = ' '
1181!
1182!-- Try to find stg package
1183    REWIND ( 11 )
1184    line = ' '
1185    DO WHILE ( INDEX( line, '&stg_par' ) == 0 )
1186       READ ( 11, '(A)', END=20 )  line
1187    ENDDO
1188    BACKSPACE ( 11 )
1189
1190!
1191!-- Read namelist
1192    READ ( 11, stg_par, ERR = 10, END = 20 )
1193
1194!
1195!-- Set flag that indicates that the synthetic turbulence generator is switched
1196!-- on
1197    syn_turb_gen = .TRUE.
1198    GOTO 20
1199
1200 10 BACKSPACE( 11 )
1201    READ( 11 , '(A)') line
1202    CALL parin_fail_message( 'stg_par', line )
1203
1204 20 CONTINUE
1205
1206 END SUBROUTINE stg_parin
1207
1208
1209!------------------------------------------------------------------------------!
1210! Description:
1211! ------------
1212!> Read module-specific global restart data (Fortran binary format).
1213!------------------------------------------------------------------------------!
1214 SUBROUTINE stg_rrd_global_ftn( found )
1215
1216    LOGICAL, INTENT(OUT)  ::  found !< flag indicating if variable was found
1217
1218    found = .TRUE.
1219
1220
1221    SELECT CASE ( restart_string(1:length) )
1222         
1223       CASE ( 'time_stg_adjust' )
1224          READ ( 13 )  time_stg_adjust
1225         
1226       CASE ( 'time_stg_call' )
1227          READ ( 13 )  time_stg_call
1228         
1229       CASE ( 'use_syn_turb_gen' )
1230          READ ( 13 )  use_syn_turb_gen
1231
1232       CASE DEFAULT
1233
1234          found = .FALSE.
1235
1236    END SELECT
1237
1238
1239 END SUBROUTINE stg_rrd_global_ftn
1240
1241
1242!------------------------------------------------------------------------------!
1243! Description:
1244! ------------
1245!> Read module-specific global restart data (MPI-IO).
1246!------------------------------------------------------------------------------!
1247 SUBROUTINE stg_rrd_global_mpi
1248
1249    CALL rrd_mpi_io( 'time_stg_adjust', time_stg_adjust )
1250    CALL rrd_mpi_io( 'time_stg_call', time_stg_call )
1251    CALL rrd_mpi_io( 'use_syn_turb_gen', use_syn_turb_gen )
1252
1253 END SUBROUTINE stg_rrd_global_mpi
1254
1255
1256!------------------------------------------------------------------------------!
1257! Description:
1258! ------------
1259!> This routine writes the respective restart data.
1260!------------------------------------------------------------------------------!
1261 SUBROUTINE stg_wrd_global
1262
1263    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
1264
1265      CALL wrd_write_string( 'time_stg_adjust' )
1266       WRITE ( 14 )  time_stg_adjust
1267   
1268       CALL wrd_write_string( 'time_stg_call' )
1269       WRITE ( 14 )  time_stg_call
1270
1271       CALL wrd_write_string( 'use_syn_turb_gen' )
1272       WRITE ( 14 )  use_syn_turb_gen
1273
1274    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
1275
1276       CALL wrd_mpi_io( 'time_stg_adjust', time_stg_adjust )
1277       CALL wrd_mpi_io( 'time_stg_call', time_stg_call )
1278       CALL wrd_mpi_io( 'use_syn_turb_gen', use_syn_turb_gen )
1279
1280    ENDIF
1281
1282 END SUBROUTINE stg_wrd_global
1283
1284
1285!------------------------------------------------------------------------------!
1286! Description:
1287! ------------
1288!> Create turbulent inflow fields for u, v, w with prescribed length scales and
1289!> Reynolds stress tensor after a method of Xie and Castro (2008), modified
1290!> following suggestions of Kim et al. (2013), and using a Lund rotation
1291!> (Lund, 1998).
1292!------------------------------------------------------------------------------!
1293 SUBROUTINE stg_main
1294
1295    USE exchange_horiz_mod,                                                    &
1296        ONLY:  exchange_horiz
1297
1298    INTEGER(iwp) :: i           !< grid index in x-direction
1299    INTEGER(iwp) :: j           !< loop index in y-direction
1300    INTEGER(iwp) :: k           !< loop index in z-direction
1301   
1302    LOGICAL  :: stg_call = .FALSE. !< control flag indicating whether turbulence was updated or only restored from last call
1303
1304    REAL(wp) :: dt_stg          !< wheighted subtimestep
1305   
1306    REAL(wp), DIMENSION(3) :: mc_factor_l   !< local mass flux correction factor
1307
1308    IF ( debug_output_timestep )  CALL debug_message( 'stg_main', 'start' )
1309!
1310!-- Calculate time step which is needed for filter functions
1311    dt_stg = MAX( dt_3d, dt_stg_call )
1312!
1313!-- Check if synthetic turbulence generator needs to be called and new
1314!-- perturbations need to be created or if old disturbances can be imposed
1315!-- again.
1316    IF ( time_stg_call >= dt_stg_call  .AND.                                  &
1317         intermediate_timestep_count == intermediate_timestep_count_max  )  THEN
1318       stg_call = .TRUE.
1319    ELSE
1320       stg_call = .FALSE.
1321    ENDIF
1322!
1323!-- Initial value of fu, fv, fw
1324    IF ( time_since_reference_point == 0.0_wp .AND. .NOT. velocity_seed_initialized )  THEN
1325!
1326!--    Generate turbulence at the left and right boundary. Random numbers
1327!--    for the yz-planes at the left/right boundary are generated by the
1328!--    left-sided mpi ranks only. After random numbers are calculated, they
1329!--    are distributed to all other mpi ranks in the model, so that the
1330!--    velocity seed matrices are available on all mpi ranks (i.e. also on the
1331!--    right-sided boundary mpi ranks). In case of offline nesting, this implies,
1332!--    that the left- and the right-sided lateral boundary have the same initial
1333!--    seeds.
1334!--    Note, in case of inflow from the right only, only turbulence at the left
1335!--    boundary is required.
1336       IF ( .NOT. ( nesting_offline  .OR.                                      &
1337                  ( child_domain .AND.  rans_mode_parent                       &
1338                                 .AND.  .NOT.  rans_mode ) ) )  THEN
1339          CALL stg_generate_seed_yz( nuy, nuz, buy, buz, fu_yz, id_stg_left )
1340          CALL stg_generate_seed_yz( nvy, nvz, bvy, bvz, fv_yz, id_stg_left )
1341          CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fw_yz, id_stg_left )
1342       ELSE
1343          CALL stg_generate_seed_yz( nuy, nuz, buy, buz, fu_yz,               &
1344                                     id_stg_left, id_stg_right )
1345          CALL stg_generate_seed_yz( nvy, nvz, bvy, bvz, fv_yz,               &
1346                                     id_stg_left, id_stg_right )
1347          CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fw_yz,               &
1348                                     id_stg_left, id_stg_right )
1349!
1350!--       Generate turbulence at the south and north boundary. Random numbers
1351!--       for the xz-planes at the south/north boundary are generated by the
1352!--       south-sided mpi ranks only. Please see also comment above.
1353          CALL stg_generate_seed_xz( nux, nuz, bux, buz, fu_xz,               &
1354                                     id_stg_south, id_stg_north )
1355          CALL stg_generate_seed_xz( nvx, nvz, bvx, bvz, fv_xz,               &
1356                                     id_stg_south, id_stg_north )
1357          CALL stg_generate_seed_xz( nwx, nwz, bwx, bwz, fw_xz,               &
1358                                     id_stg_south, id_stg_north )
1359       ENDIF
1360       velocity_seed_initialized = .TRUE.
1361    ENDIF
1362!
1363!-- New set of fu, fv, fw. Note, for inflow from the left side only, velocity
1364!-- seeds are only required at the left boundary, while in case of offline
1365!-- nesting or RANS-LES nesting velocity seeds are required also at the
1366!-- right, south and north boundaries.
1367    IF ( stg_call )  THEN
1368       IF ( .NOT. ( nesting_offline  .OR.                                      &
1369                  ( child_domain .AND.  rans_mode_parent                       &
1370                                 .AND.  .NOT.  rans_mode ) ) )  THEN
1371          CALL stg_generate_seed_yz( nuy, nuz, buy, buz, fuo_yz, id_stg_left )
1372          CALL stg_generate_seed_yz( nvy, nvz, bvy, bvz, fvo_yz, id_stg_left )
1373          CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fwo_yz, id_stg_left )
1374
1375       ELSE
1376          CALL stg_generate_seed_yz( nuy, nuz, buy, buz, fuo_yz,               &
1377                                     id_stg_left, id_stg_right )
1378          CALL stg_generate_seed_yz( nvy, nvz, bvy, bvz, fvo_yz,               &
1379                                     id_stg_left, id_stg_right )
1380          CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fwo_yz,               &
1381                                     id_stg_left, id_stg_right )
1382
1383          CALL stg_generate_seed_xz( nux, nuz, bux, buz, fuo_xz,               &
1384                                     id_stg_south, id_stg_north )
1385          CALL stg_generate_seed_xz( nvx, nvz, bvx, bvz, fvo_xz,               &
1386                                     id_stg_south, id_stg_north )
1387          CALL stg_generate_seed_xz( nwx, nwz, bwx, bwz, fwo_xz,               &
1388                                     id_stg_south, id_stg_north )
1389       ENDIF
1390    ENDIF
1391   
1392!
1393!-- Turbulence generation at left and/or right boundary
1394    IF ( myidx == id_stg_left  .OR.  myidx == id_stg_right )  THEN
1395!
1396!--    Calculate new set of perturbations. Do this only at last RK3-substep and
1397!--    when dt_stg_call is exceeded. Else the old set of perturbations is
1398!--    imposed
1399       IF ( stg_call )  THEN
1400       
1401          DO  j = nys, nyn
1402             DO  k = nzb, nzt + 1
1403!     
1404!--             Update fu, fv, fw following Eq. 14 of Xie and Castro (2008)
1405                IF ( tu(k) == 0.0_wp )  THEN
1406                   fu_yz(k,j) = fuo_yz(k,j)
1407                ELSE
1408                   fu_yz(k,j) = fu_yz(k,j) * EXP( -pi * dt_stg * 0.5_wp / tu(k) ) + &
1409                            fuo_yz(k,j) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tu(k) ) )
1410                ENDIF
1411       
1412                IF ( tv(k) == 0.0_wp )  THEN
1413                   fv_yz(k,j) = fvo_yz(k,j)
1414                ELSE
1415                   fv_yz(k,j) = fv_yz(k,j) * EXP( -pi * dt_stg * 0.5_wp / tv(k) ) + &
1416                            fvo_yz(k,j) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tv(k) ) )
1417                ENDIF
1418       
1419                IF ( tw(k) == 0.0_wp )  THEN
1420                   fw_yz(k,j) = fwo_yz(k,j)
1421                ELSE
1422                   fw_yz(k,j) = fw_yz(k,j) * EXP( -pi * dt_stg * 0.5_wp / tw(k) ) + &
1423                            fwo_yz(k,j) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tw(k) ) )
1424                ENDIF
1425             ENDDO
1426          ENDDO
1427         
1428          dist_yz(nzb,:,1) = 0.0_wp
1429          dist_yz(nzb,:,2) = 0.0_wp
1430          dist_yz(nzb,:,3) = 0.0_wp
1431         
1432          IF ( myidx == id_stg_left  )  i = nxl
1433          IF ( myidx == id_stg_right )  i = nxr+1       
1434          DO  j = nys, nyn
1435             DO  k = nzb+1, nzt + 1
1436!     
1437!--             Lund rotation following Eq. 17 in Xie and Castro (2008).
1438!--             Additional factors are added to improve the variance of v and w
1439                dist_yz(k,j,1) = MIN( a11(k) * fu_yz(k,j), 3.0_wp ) *          &
1440                                    MERGE( 1.0_wp, 0.0_wp,                     &
1441                                    BTEST( wall_flags_total_0(k,j,i), 1 ) )
1442             ENDDO
1443          ENDDO
1444
1445          IF ( myidx == id_stg_left  )  i = nxl-1
1446          IF ( myidx == id_stg_right )  i = nxr+1
1447          DO  j = nys, nyn
1448             DO  k = nzb+1, nzt + 1
1449!     
1450!--             Lund rotation following Eq. 17 in Xie and Castro (2008).
1451!--             Additional factors are added to improve the variance of v and w
1452!--             experimental test of 1.2                                       
1453                dist_yz(k,j,2) = MIN( ( SQRT( a22(k) / MAXVAL(a22) )           &
1454                                      * 1.2_wp )                               &
1455                                     * (   a21(k) * fu_yz(k,j)                 &
1456                                         + a22(k) * fv_yz(k,j) ), 3.0_wp ) *   &
1457                                    MERGE( 1.0_wp, 0.0_wp,                     &
1458                                        BTEST( wall_flags_total_0(k,j,i), 2 ) )   
1459                dist_yz(k,j,3) = MIN( ( SQRT(a33(k) / MAXVAL(a33) )            &
1460                                      * 1.3_wp )                               &
1461                                    * (   a31(k) * fu_yz(k,j)                  &
1462                                        + a32(k) * fv_yz(k,j)                  &
1463                                        + a33(k) * fw_yz(k,j) ), 3.0_wp )  *   &
1464                                    MERGE( 1.0_wp, 0.0_wp,                     &
1465                                        BTEST( wall_flags_total_0(k,j,i), 3 ) )
1466             ENDDO
1467          ENDDO
1468       ENDIF
1469!
1470!--    Mass flux correction following Kim et al. (2013)
1471!--    This correction factor insures that the mass flux is preserved at the
1472!--    inflow boundary. First, calculate mean value of the imposed
1473!--    perturbations at yz boundary.
1474!--    Note, this needs to be done only after the last RK3-substep, else
1475!--    the boundary values won't be accessed.
1476       IF ( intermediate_timestep_count == intermediate_timestep_count_max )  THEN
1477          mc_factor_l   = 0.0_wp
1478          mc_factor     = 0.0_wp
1479!       
1480!--       Sum up the original volume flows (with and without perturbations).
1481!--       Note, for non-normal components (here v and w) it is actually no
1482!--       volume flow.
1483          IF ( myidx == id_stg_left  )  i = nxl
1484          IF ( myidx == id_stg_right )  i = nxr+1
1485         
1486          mc_factor_l(1) = SUM( dist_yz(nzb:nzt,nys:nyn,1)                     &
1487                         * MERGE( 1.0_wp, 0.0_wp,                              &
1488                           BTEST( wall_flags_total_0(nzb:nzt,nys:nyn,i), 1 ) ) )
1489       
1490          IF ( myidx == id_stg_left  )  i = nxl-1
1491          IF ( myidx == id_stg_right )  i = nxr+1
1492         
1493          mc_factor_l(2) = SUM( dist_yz(nzb:nzt,nysv:nyn,2)                    &
1494                          * MERGE( 1.0_wp, 0.0_wp,                             &
1495                            BTEST( wall_flags_total_0(nzb:nzt,nysv:nyn,i), 2 ) ) )
1496          mc_factor_l(3) = SUM( dist_yz(nzb:nzt,nys:nyn,3)                     &
1497                          * MERGE( 1.0_wp, 0.0_wp,                             &
1498                            BTEST( wall_flags_total_0(nzb:nzt,nys:nyn,i), 3 ) ) )
1499         
1500#if defined( __parallel )
1501          CALL MPI_ALLREDUCE( mc_factor_l, mc_factor,                          &
1502                              3, MPI_REAL, MPI_SUM, comm1dy, ierr )           
1503#else                                                                         
1504          mc_factor   = mc_factor_l                                           
1505#endif
1506!     
1507!--       Calculate correction factor and force zero mean perturbations.
1508          mc_factor = mc_factor / REAL( nr_non_topo_yz, KIND = wp )           
1509                                                                               
1510          IF ( myidx == id_stg_left  )  i = nxl                               
1511          IF ( myidx == id_stg_right )  i = nxr+1                             
1512                                                                               
1513          dist_yz(:,nys:nyn,1) = ( dist_yz(:,nys:nyn,1) - mc_factor(1) )                   &
1514                        * MERGE( 1.0_wp, 0.0_wp,                               &
1515                          BTEST( wall_flags_total_0(:,nys:nyn,i), 1 ) )             
1516                                                                               
1517                                                                               
1518          IF ( myidx == id_stg_left  )  i = nxl-1                             
1519          IF ( myidx == id_stg_right )  i = nxr+1                             
1520                                                                               
1521          dist_yz(:,nys:nyn,2) = ( dist_yz(:,nys:nyn,2) - mc_factor(2) )                   &
1522                        * MERGE( 1.0_wp, 0.0_wp,                               &
1523                          BTEST( wall_flags_total_0(:,nys:nyn,i), 2 ) )             
1524                                                                               
1525          dist_yz(:,nys:nyn,3) = ( dist_yz(:,nys:nyn,3) - mc_factor(3) )                   &
1526                        * MERGE( 1.0_wp, 0.0_wp,                               &
1527                          BTEST( wall_flags_total_0(:,nys:nyn,i), 3 ) )
1528!     
1529!--       Add disturbances
1530          IF ( myidx == id_stg_left  )  THEN
1531!     
1532!--          For the left boundary distinguish between mesoscale offline / self
1533!--          nesting and turbulent inflow at the left boundary only. In the latter
1534!--          case turbulence is imposed on the mean inflow profiles.
1535             IF ( .NOT. nesting_offline  .AND.  .NOT. child_domain )  THEN 
1536!           
1537!--             Add disturbance at the inflow
1538                DO  j = nys, nyn
1539                   DO  k = nzb, nzt+1
1540                      u(k,j,-nbgp+1:0) = ( mean_inflow_profiles(k,1) +         &
1541                                           dist_yz(k,j,1)             )        &
1542                                   * MERGE( 1.0_wp, 0.0_wp,                    &
1543                                     BTEST( wall_flags_total_0(k,j,0), 1 ) ) 
1544                      v(k,j,-nbgp:-1)  = ( mean_inflow_profiles(k,2) +         &
1545                                           dist_yz(k,j,2)             )        &
1546                                   * MERGE( 1.0_wp, 0.0_wp,                    &
1547                                     BTEST( wall_flags_total_0(k,j,-1), 2 ) ) 
1548                      w(k,j,-nbgp:-1)  =   dist_yz(k,j,3)                      &
1549                                   * MERGE( 1.0_wp, 0.0_wp,                    &
1550                                     BTEST( wall_flags_total_0(k,j,-1), 3 ) )
1551                   ENDDO
1552                ENDDO
1553             ELSE
1554             
1555                DO  j = nys, nyn
1556                   DO  k = nzb+1, nzt
1557                      u(k,j,0)   = ( u(k,j,0) + dist_yz(k,j,1) )               &
1558                                 * MERGE( 1.0_wp, 0.0_wp,                      &
1559                                   BTEST( wall_flags_total_0(k,j,0), 1 ) )
1560                      u(k,j,-1)  = u(k,j,0)
1561                      v(k,j,-1)  = ( v(k,j,-1)  + dist_yz(k,j,2)  )            &
1562                                 * MERGE( 1.0_wp, 0.0_wp,                      &
1563                                   BTEST( wall_flags_total_0(k,j,-1), 2 ) )
1564                      w(k,j,-1)  = ( w(k,j,-1)  + dist_yz(k,j,3) )             &
1565                                 * MERGE( 1.0_wp, 0.0_wp,                      &
1566                                   BTEST( wall_flags_total_0(k,j,-1), 3 ) )
1567                   ENDDO
1568                ENDDO
1569             ENDIF
1570          ENDIF
1571          IF ( myidx == id_stg_right  )  THEN
1572             DO  j = nys, nyn
1573                DO  k = nzb+1, nzt
1574                   u(k,j,nxr+1) = ( u(k,j,nxr+1) + dist_yz(k,j,1) )            &
1575                                  * MERGE( 1.0_wp, 0.0_wp,                     &
1576                                    BTEST( wall_flags_total_0(k,j,nxr+1), 1 ) ) 
1577                   v(k,j,nxr+1) = ( v(k,j,nxr+1) + dist_yz(k,j,2) )            &
1578                                  * MERGE( 1.0_wp, 0.0_wp,                     &
1579                                    BTEST( wall_flags_total_0(k,j,nxr+1), 2 ) )
1580                   w(k,j,nxr+1) = ( w(k,j,nxr+1) + dist_yz(k,j,3) )            &
1581                                  * MERGE( 1.0_wp, 0.0_wp,                     &
1582                                    BTEST( wall_flags_total_0(k,j,nxr+1), 3 ) )
1583                ENDDO
1584             ENDDO
1585          ENDIF
1586       ENDIF
1587    ENDIF
1588!
1589!-- Turbulence generation at north and south boundary
1590    IF ( myidy == id_stg_north  .OR.  myidy == id_stg_south )  THEN
1591!
1592!--    Calculate new set of perturbations. Do this only at last RK3-substep and
1593!--    when dt_stg_call is exceeded. Else the old set of perturbations is
1594!--    imposed
1595       IF ( stg_call )  THEN
1596          DO  i = nxl, nxr
1597             DO  k = nzb, nzt + 1
1598!         
1599!--             Update fu, fv, fw following Eq. 14 of Xie and Castro (2008)
1600                IF ( tu(k) == 0.0_wp )  THEN
1601                   fu_xz(k,i) = fuo_xz(k,i)
1602                ELSE
1603                   fu_xz(k,i) = fu_xz(k,i) * EXP( -pi * dt_stg * 0.5_wp / tu(k) ) +     &
1604                            fuo_xz(k,i) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tu(k) ) )
1605                ENDIF
1606         
1607                IF ( tv(k) == 0.0_wp )  THEN
1608                   fv_xz(k,i) = fvo_xz(k,i)
1609                ELSE
1610                   fv_xz(k,i) = fv_xz(k,i) * EXP( -pi * dt_stg * 0.5_wp / tv(k) ) +     &
1611                         fvo_xz(k,i) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tv(k) ) )
1612                ENDIF
1613               
1614                IF ( tw(k) == 0.0_wp )  THEN
1615                   fw_xz(k,i) = fwo_xz(k,i)
1616                ELSE
1617                   fw_xz(k,i) = fw_xz(k,i) * EXP( -pi * dt_stg * 0.5_wp / tw(k) ) +     &
1618                         fwo_xz(k,i) * SQRT( 1.0_wp - EXP( -pi * dt_stg / tw(k) ) )
1619                ENDIF
1620             ENDDO
1621          ENDDO
1622         
1623         
1624          dist_xz(nzb,:,1) = 0.0_wp
1625          dist_xz(nzb,:,2) = 0.0_wp
1626          dist_xz(nzb,:,3) = 0.0_wp
1627         
1628          IF ( myidy == id_stg_south  ) j = nys
1629          IF ( myidy == id_stg_north )  j = nyn+1
1630          DO  i = nxl, nxr
1631             DO  k = nzb+1, nzt + 1
1632!         
1633!--             Lund rotation following Eq. 17 in Xie and Castro (2008).
1634!--             Additional factors are added to improve the variance of v and w
1635                !experimental test of 1.2                                         
1636                dist_xz(k,i,2) = MIN( ( SQRT( a22(k) / MAXVAL(a22) )           &
1637                                      * 1.2_wp )                               &
1638                                     * (   a21(k) * fu_xz(k,i)                 &
1639                                         + a22(k) * fv_xz(k,i) ), 3.0_wp ) *   &
1640                                    MERGE( 1.0_wp, 0.0_wp,                     &
1641                                    BTEST( wall_flags_total_0(k,j,i), 2 ) )
1642             ENDDO
1643          ENDDO
1644         
1645          IF ( myidy == id_stg_south  ) j = nys-1
1646          IF ( myidy == id_stg_north )  j = nyn+1
1647          DO  i = nxl, nxr
1648             DO  k = nzb+1, nzt + 1
1649!         
1650!--             Lund rotation following Eq. 17 in Xie and Castro (2008).
1651!--             Additional factors are added to improve the variance of v and w
1652                dist_xz(k,i,1) = MIN( a11(k) * fu_xz(k,i), 3.0_wp ) *          &
1653                                    MERGE( 1.0_wp, 0.0_wp,                     &
1654                                    BTEST( wall_flags_total_0(k,j,i), 1 ) )   
1655         
1656                dist_xz(k,i,3) = MIN( ( SQRT(a33(k) / MAXVAL(a33) )            &
1657                                      * 1.3_wp )                               &
1658                                    * (   a31(k) * fu_xz(k,i)                  &
1659                                        + a32(k) * fv_xz(k,i)                  &
1660                                        + a33(k) * fw_xz(k,i) ), 3.0_wp )  *   &
1661                                    MERGE( 1.0_wp, 0.0_wp,                     &
1662                                    BTEST( wall_flags_total_0(k,j,i), 3 ) ) 
1663             ENDDO
1664          ENDDO
1665       ENDIF
1666
1667!
1668!--    Mass flux correction following Kim et al. (2013)
1669!--    This correction factor insures that the mass flux is preserved at the
1670!--    inflow boundary. First, calculate mean value of the imposed
1671!--    perturbations at yz boundary.
1672!--    Note, this needs to be done only after the last RK3-substep, else
1673!--    the boundary values won't be accessed.
1674       IF ( intermediate_timestep_count == intermediate_timestep_count_max )  THEN
1675          mc_factor_l   = 0.0_wp
1676          mc_factor     = 0.0_wp
1677         
1678          IF ( myidy == id_stg_south  ) j = nys
1679          IF ( myidy == id_stg_north )  j = nyn+1
1680         
1681          mc_factor_l(2) = SUM( dist_xz(nzb:nzt,nxl:nxr,2)                     &
1682                         * MERGE( 1.0_wp, 0.0_wp,                              &
1683                           BTEST( wall_flags_total_0(nzb:nzt,j,nxl:nxr), 2 ) ) )
1684         
1685          IF ( myidy == id_stg_south  ) j = nys-1
1686          IF ( myidy == id_stg_north )  j = nyn+1
1687         
1688          mc_factor_l(1) = SUM( dist_xz(nzb:nzt,nxlu:nxr,1)                    &
1689                         * MERGE( 1.0_wp, 0.0_wp,                              &
1690                           BTEST( wall_flags_total_0(nzb:nzt,j,nxlu:nxr), 1 ) ) )
1691          mc_factor_l(3) = SUM( dist_xz(nzb:nzt,nxl:nxr,3)                     &
1692                         * MERGE( 1.0_wp, 0.0_wp,                              &
1693                           BTEST( wall_flags_total_0(nzb:nzt,j,nxl:nxr), 3 ) ) )
1694         
1695#if defined( __parallel )
1696          CALL MPI_ALLREDUCE( mc_factor_l, mc_factor,                          &
1697                              3, MPI_REAL, MPI_SUM, comm1dx, ierr )
1698#else     
1699          mc_factor   = mc_factor_l
1700#endif
1701         
1702          mc_factor = mc_factor / REAL( nr_non_topo_xz, KIND = wp )
1703         
1704          IF ( myidy == id_stg_south  ) j = nys
1705          IF ( myidy == id_stg_north )  j = nyn+1
1706         
1707          dist_xz(:,nxl:nxr,2)   = ( dist_xz(:,nxl:nxr,2) - mc_factor(2) )                 &
1708                           * MERGE( 1.0_wp, 0.0_wp,                            &
1709                             BTEST( wall_flags_total_0(:,j,nxl:nxr), 2 ) )         
1710                                                                               
1711                                                                               
1712          IF ( myidy == id_stg_south  ) j = nys-1                             
1713          IF ( myidy == id_stg_north )  j = nyn+1                             
1714                                                                               
1715          dist_xz(:,nxl:nxr,1)   = ( dist_xz(:,nxl:nxr,1) - mc_factor(1) )                 &
1716                           * MERGE( 1.0_wp, 0.0_wp,                            &
1717                             BTEST( wall_flags_total_0(:,j,nxl:nxr), 1 ) )         
1718                                                                               
1719          dist_xz(:,nxl:nxr,3)   = ( dist_xz(:,nxl:nxr,3) - mc_factor(3) )                 &
1720                           * MERGE( 1.0_wp, 0.0_wp,                            &
1721                             BTEST( wall_flags_total_0(:,j,nxl:nxr), 3 ) )     
1722!         
1723!--       Add disturbances
1724          IF ( myidy == id_stg_south  )  THEN
1725             DO  i = nxl, nxr
1726                DO  k = nzb+1, nzt
1727                   u(k,-1,i) = ( u(k,-1,i) + dist_xz(k,i,1) )                  &
1728                                        * MERGE( 1.0_wp, 0.0_wp,               &
1729                                          BTEST( wall_flags_total_0(k,-1,i), 1 ) )
1730                   v(k,0,i)  = ( v(k,0,i)  + dist_xz(k,i,2)  )                 &
1731                                        * MERGE( 1.0_wp, 0.0_wp,               &
1732                                          BTEST( wall_flags_total_0(k,0,i), 2 ) )
1733                   v(k,-1,i) = v(k,0,i)
1734                   w(k,-1,i) = ( w(k,-1,i) + dist_xz(k,i,3)  )                 &
1735                                        * MERGE( 1.0_wp, 0.0_wp,               &
1736                                          BTEST( wall_flags_total_0(k,-1,i), 3 ) )
1737                ENDDO
1738             ENDDO
1739          ENDIF
1740          IF ( myidy == id_stg_north  )  THEN
1741         
1742             DO  i = nxl, nxr
1743                DO  k = nzb+1, nzt
1744                   u(k,nyn+1,i) = ( u(k,nyn+1,i) + dist_xz(k,i,1) )            &
1745                                     * MERGE( 1.0_wp, 0.0_wp,                  &
1746                                       BTEST( wall_flags_total_0(k,nyn+1,i), 1 ) )
1747                   v(k,nyn+1,i) = ( v(k,nyn+1,i) + dist_xz(k,i,2) )            &
1748                                     * MERGE( 1.0_wp, 0.0_wp,                  &
1749                                       BTEST( wall_flags_total_0(k,nyn+1,i), 2 ) )
1750                   w(k,nyn+1,i) = ( w(k,nyn+1,i) + dist_xz(k,i,3) )            &
1751                                     * MERGE( 1.0_wp, 0.0_wp,                  &
1752                                       BTEST( wall_flags_total_0(k,nyn+1,i), 3 ) )
1753                ENDDO
1754             ENDDO
1755          ENDIF
1756       ENDIF
1757    ENDIF
1758!
1759!-- Exchange ghost points.
1760    CALL exchange_horiz( u, nbgp )
1761    CALL exchange_horiz( v, nbgp )
1762    CALL exchange_horiz( w, nbgp )
1763!
1764!-- Finally, set time counter for calling STG to zero
1765    IF ( stg_call )  time_stg_call = 0.0_wp
1766
1767    IF ( debug_output_timestep )  CALL debug_message( 'stg_main', 'end' )
1768
1769 END SUBROUTINE stg_main
1770
1771!------------------------------------------------------------------------------!
1772! Description:
1773! ------------
1774!> Generate a set of random number rand_it wich is equal on each PE
1775!> and calculate the velocity seed f_n.
1776!> f_n is splitted in vertical direction by the number of PEs in x-direction and
1777!> and each PE calculates a vertical subsection of f_n. At the the end, all
1778!> parts are collected to form the full array.
1779!------------------------------------------------------------------------------!
1780 SUBROUTINE stg_generate_seed_yz( n_y, n_z, b_y, b_z, f_n, id_left, id_right )
1781
1782    INTEGER(iwp)           :: id_left     !< core ids at respective boundaries
1783    INTEGER(iwp), OPTIONAL :: id_right    !< core ids at respective boundaries
1784    INTEGER(iwp)           :: j           !< loop index in y-direction
1785    INTEGER(iwp)           :: jj          !< loop index in y-direction
1786    INTEGER(iwp)           :: k           !< loop index in z-direction
1787    INTEGER(iwp)           :: kk          !< loop index in z-direction
1788    INTEGER(iwp)           :: send_count  !< send count for MPI_GATHERV
1789
1790    INTEGER(iwp), DIMENSION(nzb:nzt+1) :: n_y    !< length scale in y-direction
1791    INTEGER(iwp), DIMENSION(nzb:nzt+1) :: n_z    !< length scale in z-direction
1792
1793    REAL(wp) :: nyz_inv         !< inverse of number of grid points in yz-slice
1794    REAL(wp) :: rand_av         !< average of random number
1795    REAL(wp) :: rand_sigma_inv  !< inverse of stdev of random number
1796
1797    REAL(wp), DIMENSION(-mergp:mergp,nzb:nzt+1)    :: b_y     !< filter function in y-direction
1798    REAL(wp), DIMENSION(-mergp:mergp,nzb:nzt+1)    :: b_z     !< filter function in z-direction
1799   
1800    REAL(wp), DIMENSION(nzb_x_stg:nzt_x_stg+1,nys:nyn) :: f_n_l   !<  local velocity seed
1801    REAL(wp), DIMENSION(nzb:nzt+1,nys:nyn)             :: f_n     !<  velocity seed
1802   
1803    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rand_it   !< global array of random numbers
1804!
1805!-- Generate random numbers using the parallel random generator.
1806!-- The set of random numbers are modified to have an average of 0 and
1807!-- unit variance. Note, at the end the random number array must be defined
1808!-- globally in order to compute the correlation matrices. However,
1809!-- the calculation and normalization of random numbers is done locally,
1810!-- while the result is later distributed to all processes. Further,
1811!-- please note, a set of random numbers is only calculated for the
1812!-- left boundary, while the right boundary uses the same random numbers
1813!-- and thus also computes the same correlation matrix.
1814    ALLOCATE( rand_it(nzb-mergp:nzt+1+mergp,-mergp+nys:nyn+mergp) )
1815    rand_it = 0.0_wp
1816
1817    rand_av        = 0.0_wp
1818    rand_sigma_inv = 0.0_wp
1819    nyz_inv        = 1.0_wp / REAL( ( nzt + 1 + mergp - ( nzb - mergp ) + 1 )  &
1820                                  * ( ny + mergp - ( 0 - mergp ) + 1 ),        &
1821                                    KIND=wp )
1822!
1823!-- Compute and normalize random numbers.
1824    DO  j = nys - mergp, nyn + mergp
1825!
1826!--    Put the random seeds at grid point j
1827       CALL random_seed_parallel( put=seq_rand_yz(:,j) )
1828       DO  k = nzb - mergp, nzt + 1 + mergp
1829          CALL random_number_parallel( random_dummy )
1830          rand_it(k,j) = random_dummy
1831       ENDDO
1832!
1833!--    Get the new random seeds from last call at grid point j
1834       CALL random_seed_parallel( get=seq_rand_yz(:,j) )
1835    ENDDO
1836!
1837!-- For normalization to zero mean, sum-up the global random numers.
1838!-- To normalize the global set of random numbers,
1839!-- the inner ghost layers mergp must not be summed-up, else
1840!-- the random numbers on the ghost layers will be stronger weighted as they
1841!-- also occur on the inner subdomains.
1842    DO  j = MERGE( nys, nys - mergp, nys /= 0 ),                              &
1843            MERGE( nyn, nyn + mergp, nyn /= ny )
1844       DO  k = nzb - mergp, nzt + 1 + mergp
1845          rand_av = rand_av + rand_it(k,j)
1846       ENDDO
1847    ENDDO
1848   
1849#if defined( __parallel )
1850!
1851!-- Sum-up the local averages of the random numbers
1852    CALL MPI_ALLREDUCE( MPI_IN_PLACE, rand_av, 1, MPI_REAL,                    &
1853                        MPI_SUM, comm1dy, ierr )
1854#endif
1855    rand_av = rand_av * nyz_inv
1856!
1857!-- Obtain zero mean
1858    rand_it= rand_it - rand_av
1859!
1860!-- Now, compute the variance
1861    DO  j = MERGE( nys, nys - mergp, nys /= 0 ),                               &
1862            MERGE( nyn, nyn + mergp, nyn /= ny )
1863       DO  k = nzb - mergp, nzt + 1 + mergp
1864          rand_sigma_inv = rand_sigma_inv + rand_it(k,j)**2
1865       ENDDO
1866    ENDDO
1867
1868#if defined( __parallel )
1869!
1870!-- Sum-up the local quadratic averages of the random numbers
1871    CALL MPI_ALLREDUCE( MPI_IN_PLACE, rand_sigma_inv, 1, MPI_REAL,          &
1872                        MPI_SUM, comm1dy, ierr )
1873#endif
1874!
1875!-- Compute standard deviation
1876    IF ( rand_sigma_inv /= 0.0_wp )  THEN
1877       rand_sigma_inv = 1.0_wp / SQRT( rand_sigma_inv * nyz_inv )
1878    ELSE
1879       rand_sigma_inv = 1.0_wp
1880    ENDIF
1881!
1882!-- Normalize with standard deviation to obtain unit variance
1883    rand_it = rand_it * rand_sigma_inv
1884
1885    CALL cpu_log( log_point_s(31), 'STG f_n factors', 'start' )
1886!
1887!-- Generate velocity seed following Eq.6 of Xie and Castro (2008). There
1888!-- are two options. In the first one, the computation of the seeds is
1889!-- distributed to all processes along the communicator comm1dy and
1890!-- gathered on the leftmost and, if necessary, on the rightmost process.
1891!-- For huge length scales the computational effort can become quite huge
1892!-- (it scales with the turbulent length scales), so that gain by parallelization
1893!-- exceeds the costs by the subsequent communication.
1894!-- In the second option, which performs better when the turbulent length scales
1895!-- are parametrized and thus the loops are smaller, the seeds are computed
1896!-- locally and no communication is necessary.
1897    IF ( compute_velocity_seeds_local )  THEN
1898
1899       f_n  = 0.0_wp
1900       DO  j = nys, nyn
1901          DO  k = nzb, nzt+1
1902             DO  jj = -n_y(k), n_y(k)
1903                DO  kk = -n_z(k), n_z(k)
1904                   f_n(k,j) = f_n(k,j) + b_y(jj,k) * b_z(kk,k) * rand_it(k+kk,j+jj)
1905                ENDDO
1906             ENDDO
1907          ENDDO
1908       ENDDO
1909
1910    ELSE
1911
1912       f_n_l  = 0.0_wp
1913       DO  j = nys, nyn
1914          DO  k = nzb_x_stg, nzt_x_stg+1
1915             DO  jj = -n_y(k), n_y(k)
1916                DO  kk = -n_z(k), n_z(k)
1917                   f_n_l(k,j) = f_n_l(k,j) + b_y(jj,k) * b_z(kk,k) * rand_it(k+kk,j+jj)
1918                ENDDO
1919             ENDDO
1920          ENDDO
1921       ENDDO
1922!
1923!--    Gather velocity seeds of full subdomain
1924       send_count = nzt_x_stg - nzb_x_stg + 1
1925       IF ( nzt_x_stg == nzt )  send_count = send_count + 1
1926
1927#if defined( __parallel )
1928!
1929!--    Gather the velocity seed matrix on left boundary mpi ranks.
1930       CALL MPI_GATHERV( f_n_l(nzb_x_stg,nys), send_count, stg_type_yz_small,  &
1931                         f_n(nzb+1,nys), recv_count_yz, displs_yz, stg_type_yz,&
1932                         id_left, comm1dx, ierr )
1933!
1934!--    If required, gather the same velocity seed matrix on right boundary
1935!--    mpi ranks (in offline nesting for example).
1936       IF ( PRESENT( id_right ) )  THEN
1937          CALL MPI_GATHERV( f_n_l(nzb_x_stg,nys), send_count, stg_type_yz_small,  &
1938                            f_n(nzb+1,nys), recv_count_yz, displs_yz, stg_type_yz,&
1939                            id_right, comm1dx, ierr )
1940       ENDIF
1941#else
1942       f_n(nzb+1:nzt+1,nys:nyn) = f_n_l(nzb_x_stg:nzt_x_stg+1,nys:nyn)
1943!
1944!--    Next line required to avoid compile errors because of unused dummy arguments
1945       IF ( id_left == 0 )  id_right = 0
1946#endif
1947
1948    ENDIF
1949
1950    DEALLOCATE( rand_it )
1951
1952    CALL cpu_log( log_point_s(31), 'STG f_n factors', 'stop' )
1953
1954 END SUBROUTINE stg_generate_seed_yz
1955
1956
1957!------------------------------------------------------------------------------!
1958! Description:
1959! ------------
1960!> Generate a set of random number rand_it wich is equal on each PE
1961!> and calculate the velocity seed f_n.
1962!> f_n is splitted in vertical direction by the number of PEs in y-direction and
1963!> and each PE calculates a vertical subsection of f_n. At the the end, all
1964!> parts are collected to form the full array.
1965!------------------------------------------------------------------------------!
1966 SUBROUTINE stg_generate_seed_xz( n_x, n_z, b_x, b_z, f_n, id_south, id_north )
1967
1968    INTEGER(iwp) :: i           !< loop index in x-direction
1969    INTEGER(iwp) :: id_north    !< core ids at respective boundaries
1970    INTEGER(iwp) :: id_south    !< core ids at respective boundaries
1971    INTEGER(iwp) :: ii          !< loop index in x-direction
1972    INTEGER(iwp) :: k           !< loop index in z-direction
1973    INTEGER(iwp) :: kk          !< loop index in z-direction
1974    INTEGER(iwp) :: send_count  !< send count for MPI_GATHERV
1975
1976    INTEGER(iwp), DIMENSION(nzb:nzt+1) :: n_x    !< length scale in x-direction
1977    INTEGER(iwp), DIMENSION(nzb:nzt+1) :: n_z    !< length scale in z-direction
1978
1979    REAL(wp) :: nxz_inv         !< inverse of number of grid points in xz-slice
1980    REAL(wp) :: rand_av         !< average of random number
1981    REAL(wp) :: rand_sigma_inv  !< inverse of stdev of random number
1982
1983    REAL(wp), DIMENSION(-mergp:mergp,nzb:nzt+1)    :: b_x     !< filter function in x-direction
1984    REAL(wp), DIMENSION(-mergp:mergp,nzb:nzt+1)    :: b_z     !< filter function in z-direction
1985   
1986    REAL(wp), DIMENSION(nzb_y_stg:nzt_y_stg+1,nxl:nxr) :: f_n_l   !<  local velocity seed
1987    REAL(wp), DIMENSION(nzb:nzt+1,nxl:nxr)             :: f_n     !<  velocity seed
1988
1989    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rand_it   !< global array of random numbers
1990
1991!
1992!-- Generate random numbers using the parallel random generator.
1993!-- The set of random numbers are modified to have an average of 0 and
1994!-- unit variance. Note, at the end the random number array must be defined
1995!-- globally in order to compute the correlation matrices. However,
1996!-- the calculation and normalization of random numbers is done locally,
1997!-- while the result is later distributed to all processes. Further,
1998!-- please note, a set of random numbers is only calculated for the
1999!-- left boundary, while the right boundary uses the same random numbers
2000!-- and thus also computes the same correlation matrix.
2001    ALLOCATE( rand_it(nzb-mergp:nzt+1+mergp,-mergp+nxl:nxr+mergp) )
2002    rand_it = 0.0_wp
2003
2004    rand_av        = 0.0_wp
2005    rand_sigma_inv = 0.0_wp
2006    nxz_inv        = 1.0_wp / REAL( ( nzt + 1 + mergp - ( nzb - mergp ) + 1 )  &
2007                                  * ( nx + mergp - ( 0 - mergp ) +1 ),         &
2008                                    KIND=wp )
2009!
2010!-- Compute and normalize random numbers.
2011    DO  i = nxl - mergp, nxr + mergp
2012!
2013!--    Put the random seeds at grid point ii
2014       CALL random_seed_parallel( put=seq_rand_xz(:,i) )
2015       DO  k = nzb - mergp, nzt + 1 + mergp
2016          CALL random_number_parallel( random_dummy )
2017          rand_it(k,i) = random_dummy
2018       ENDDO
2019!
2020!--    Get the new random seeds from last call at grid point ii
2021       CALL random_seed_parallel( get=seq_rand_xz(:,i) )
2022    ENDDO
2023!
2024!-- For normalization to zero mean, sum-up the global random numers.
2025!-- To normalize the global set of random numbers,
2026!-- the inner ghost layers mergp must not be summed-up, else
2027!-- the random numbers on the ghost layers will be stronger weighted as they
2028!-- also occur on the inner subdomains.
2029    DO  i = MERGE( nxl, nxl - mergp, nxl /= 0 ),                              &
2030            MERGE( nxr, nxr + mergp, nxr /= nx )
2031       DO  k = nzb - mergp, nzt + 1 + mergp
2032          rand_av = rand_av + rand_it(k,i)
2033       ENDDO
2034    ENDDO
2035   
2036#if defined( __parallel )
2037!
2038!-- Sum-up the local averages of the random numbers
2039    CALL MPI_ALLREDUCE( MPI_IN_PLACE, rand_av, 1, MPI_REAL,                    &
2040                        MPI_SUM, comm1dx, ierr )
2041#endif
2042    rand_av = rand_av * nxz_inv
2043!
2044!-- Obtain zero mean
2045    rand_it= rand_it - rand_av
2046!
2047!-- Now, compute the variance
2048    DO  i = MERGE( nxl, nxl - mergp, nxl /= 0 ),                               &
2049            MERGE( nxr, nxr + mergp, nxr /= nx )
2050       DO  k = nzb - mergp, nzt + 1 + mergp
2051          rand_sigma_inv = rand_sigma_inv + rand_it(k,i)**2
2052       ENDDO
2053    ENDDO
2054
2055#if defined( __parallel )
2056!
2057!-- Sum-up the local quadratic averages of the random numbers
2058    CALL MPI_ALLREDUCE( MPI_IN_PLACE, rand_sigma_inv, 1, MPI_REAL,          &
2059                        MPI_SUM, comm1dx, ierr )
2060#endif
2061!
2062!-- Compute standard deviation
2063    IF ( rand_sigma_inv /= 0.0_wp )  THEN
2064       rand_sigma_inv = 1.0_wp / SQRT( rand_sigma_inv * nxz_inv )
2065    ELSE
2066       rand_sigma_inv = 1.0_wp
2067    ENDIF
2068!
2069!-- Normalize with standard deviation to obtain unit variance
2070    rand_it = rand_it * rand_sigma_inv
2071
2072    CALL cpu_log( log_point_s(31), 'STG f_n factors', 'start' )
2073!
2074!-- Generate velocity seed following Eq.6 of Xie and Castro (2008). There
2075!-- are two options. In the first one, the computation of the seeds is
2076!-- distributed to all processes along the communicator comm1dx and
2077!-- gathered on the southmost and, if necessary, on the northmost process.
2078!-- For huge length scales the computational effort can become quite huge
2079!-- (it scales with the turbulent length scales), so that gain by parallelization
2080!-- exceeds the costs by the subsequent communication.
2081!-- In the second option, which performs better when the turbulent length scales
2082!-- are parametrized and thus the loops are smaller, the seeds are computed
2083!-- locally and no communication is necessary.
2084    IF ( compute_velocity_seeds_local )  THEN
2085
2086       f_n  = 0.0_wp
2087       DO  i = nxl, nxr
2088          DO  k = nzb, nzt+1
2089             DO  ii = -n_x(k), n_x(k)
2090                DO  kk = -n_z(k), n_z(k)
2091                   f_n(k,i) = f_n(k,i) + b_x(ii,k) * b_z(kk,k) * rand_it(k+kk,i+ii)
2092                ENDDO
2093             ENDDO
2094          ENDDO
2095       ENDDO
2096
2097    ELSE
2098
2099       f_n_l  = 0.0_wp
2100       DO  i = nxl, nxr
2101          DO  k = nzb_y_stg, nzt_y_stg+1
2102             DO  ii = -n_x(k), n_x(k)
2103                DO  kk = -n_z(k), n_z(k)
2104                   f_n_l(k,i) = f_n_l(k,i) + b_x(ii,k) * b_z(kk,k) * rand_it(k+kk,i+ii)
2105                ENDDO
2106             ENDDO
2107          ENDDO
2108       ENDDO
2109!
2110!--    Gather velocity seeds of full subdomain
2111       send_count = nzt_y_stg - nzb_y_stg + 1
2112       IF ( nzt_y_stg == nzt )  send_count = send_count + 1
2113
2114#if defined( __parallel )
2115!
2116!--    Gather the processed velocity seed on south boundary mpi ranks.
2117       CALL MPI_GATHERV( f_n_l(nzb_y_stg,nxl), send_count, stg_type_xz_small,   &
2118                         f_n(nzb+1,nxl), recv_count_xz, displs_xz, stg_type_xz, &
2119                         id_south, comm1dy, ierr )
2120!
2121!--    Gather the processed velocity seed on north boundary mpi ranks.
2122       CALL MPI_GATHERV( f_n_l(nzb_y_stg,nxl), send_count, stg_type_xz_small,   &
2123                         f_n(nzb+1,nxl), recv_count_xz, displs_xz, stg_type_xz, &
2124                         id_north, comm1dy, ierr )
2125#else
2126       f_n(nzb+1:nzt+1,nxl:nxr) = f_n_l(nzb_y_stg:nzt_y_stg+1,nxl:nxr)
2127!
2128!--    Next line required to avoid compile errors because of unused dummy arguments
2129       IF ( id_north == 0 )  id_south = 0
2130#endif
2131
2132    ENDIF
2133
2134    DEALLOCATE( rand_it )
2135
2136    CALL cpu_log( log_point_s(31), 'STG f_n factors', 'stop' )
2137
2138 END SUBROUTINE stg_generate_seed_xz
2139
2140!------------------------------------------------------------------------------!
2141! Description:
2142! ------------
2143!> Parametrization of the Reynolds stress tensor, following the parametrization
2144!> described in Rotach et al. (1996), which is applied in state-of-the-art
2145!> dispserion modelling. Please note, the parametrization does not distinguish
2146!> between along-wind and cross-wind turbulence.
2147!------------------------------------------------------------------------------!
2148 SUBROUTINE parametrize_reynolds_stress
2149
2150    INTEGER(iwp) :: k            !< loop index in z-direction
2151   
2152    REAL(wp)     ::  zzi         !< ratio of z/zi
2153   
2154    DO  k = nzb+1, nzt+1
2155!
2156!--    Calculate function to gradually decrease Reynolds stress above ABL top.
2157!--    The function decreases to 1/10 after one length scale above the
2158!--    ABL top.
2159       blend = MIN( 1.0_wp, EXP( d_l * zu(k) - d_l * zi_ribulk ) )
2160!
2161!--    Determine normalized height coordinate
2162       zzi = zu(k) / zi_ribulk
2163!
2164!--    u'u' and v'v'. Assume isotropy. Note, add a small negative number
2165!--    to the denominator, else the mergpe-function can crash if scale_l is
2166!--    zero.
2167       r11(k) = scale_us**2 * (                                                &
2168                   MERGE( 0.35_wp * ABS(                                       &
2169                        - zi_ribulk / ( kappa * scale_l - 10E-4_wp )           &
2170                                       )**( 2.0_wp / 3.0_wp ),                 &
2171                          0.0_wp,                                              &
2172                          scale_l < 0.0_wp )                                   &
2173                 + 5.0_wp - 4.0_wp * zzi                                       &
2174                              ) * blend                                       
2175                                                                               
2176       r22(k) = r11(k)                                                         
2177!                                                                             
2178!--    w'w'                                                                   
2179       r33(k) = scale_wm**2 * (                                                &
2180                   1.5_wp * zzi**( 2.0_wp / 3.0_wp ) * EXP( -2.0_wp * zzi )    &
2181                 + ( 1.7_wp - zzi ) * ( scale_us / scale_wm )**2               &                     
2182                              )  * blend                                       
2183!                                                                             
2184!--    u'w' and v'w'. Assume isotropy.                                         
2185       r31(k) = - scale_us**2 * ( 1.01_wp - MIN( zzi, 1.0_wp ) ) * blend
2186       r32(k) = r31(k)
2187!
2188!--    For u'v' no parametrization exist so far - ?. For simplicity assume
2189!--    a similar profile as for u'w'.
2190       r21(k) = r31(k)
2191    ENDDO
2192
2193!
2194!-- Set bottom boundary condition   
2195    r11(nzb) = r11(nzb+1)
2196    r22(nzb) = r22(nzb+1)
2197    r33(nzb) = r33(nzb+1)
2198
2199    r21(nzb) = r11(nzb+1)
2200    r31(nzb) = r31(nzb+1)
2201    r32(nzb) = r32(nzb+1)
2202   
2203
2204 END SUBROUTINE parametrize_reynolds_stress 
2205 
2206!------------------------------------------------------------------------------!
2207! Description:
2208! ------------
2209!> Calculate the coefficient matrix from the Lund rotation.
2210!------------------------------------------------------------------------------!
2211 SUBROUTINE calc_coeff_matrix
2212
2213    INTEGER(iwp) :: k   !< loop index in z-direction
2214   
2215!
2216!-- Calculate coefficient matrix. Split loops to allow for loop vectorization.
2217    DO  k = nzb+1, nzt+1
2218       IF ( r11(k) > 10E-6_wp )  THEN
2219          a11(k) = SQRT( r11(k) ) 
2220          a21(k) = r21(k) / a11(k)
2221          a31(k) = r31(k) / a11(k)
2222       ELSE
2223          a11(k) = 10E-8_wp
2224          a21(k) = 10E-8_wp
2225          a31(k) = 10E-8_wp
2226       ENDIF
2227    ENDDO
2228    DO  k = nzb+1, nzt+1
2229       a22(k) = r22(k) - a21(k)**2 
2230       IF ( a22(k) > 10E-6_wp )  THEN
2231          a22(k) = SQRT( a22(k) )
2232          a32(k) = r32(k) - a21(k) * a31(k) / a22(k)
2233       ELSE
2234          a22(k) = 10E-8_wp
2235          a32(k) = 10E-8_wp
2236       ENDIF
2237    ENDDO
2238    DO  k = nzb+1, nzt+1
2239       a33(k) = r33(k) - a31(k)**2 - a32(k)**2
2240       IF ( a33(k) > 10E-6_wp )  THEN
2241          a33(k) =  SQRT( a33(k) )
2242       ELSE
2243          a33(k) = 10E-8_wp
2244       ENDIF
2245    ENDDO   
2246!
2247!-- Set bottom boundary condition
2248    a11(nzb) = a11(nzb+1)
2249    a22(nzb) = a22(nzb+1)
2250    a21(nzb) = a21(nzb+1)
2251    a33(nzb) = a33(nzb+1)   
2252    a31(nzb) = a31(nzb+1)
2253    a32(nzb) = a32(nzb+1)   
2254
2255 END SUBROUTINE calc_coeff_matrix
2256 
2257!------------------------------------------------------------------------------!
2258! Description:
2259! ------------
2260!> This routine controls the re-adjustment of the turbulence statistics used
2261!> for generating turbulence at the lateral boundaries. 
2262!------------------------------------------------------------------------------!
2263 SUBROUTINE stg_adjust
2264
2265    IF ( debug_output_timestep )  CALL debug_message( 'stg_adjust', 'start' )
2266!
2267!-- In case of dirichlet inflow boundary conditions only at one lateral
2268!-- boundary, i.e. in the case no offline or self nesting is applied but
2269!-- synthetic turbulence shall be parametrized nevertheless, the
2270!-- boundary-layer depth need to determined first.
2271    IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )                   &
2272       CALL nesting_offl_calc_zi   
2273!
2274!-- Compute scaling parameters (domain-averaged), such as friction velocity
2275!-- are calculated.
2276    CALL calc_scaling_variables
2277!
2278!-- Set length and time scales depending on boundary-layer height
2279    CALL calc_length_and_time_scale
2280!
2281!-- Parametrize Reynolds-stress tensor, diagonal elements as well
2282!-- as r21 (v'u'), r31 (w'u'), r32 (w'v'). Parametrization follows
2283!-- Rotach et al. (1996) and is based on boundary-layer depth,
2284!-- friction velocity and velocity scale.
2285    CALL parametrize_reynolds_stress
2286!
2287!-- Calculate coefficient matrix from Reynolds stress tensor 
2288!-- (Lund rotation)
2289    CALL calc_coeff_matrix
2290!
2291!-- Determine filter functions on basis of updated length scales
2292    CALL stg_filter_func( nux, bux ) !filter ux
2293    CALL stg_filter_func( nuy, buy ) !filter uy
2294    CALL stg_filter_func( nuz, buz ) !filter uz
2295    CALL stg_filter_func( nvx, bvx ) !filter vx
2296    CALL stg_filter_func( nvy, bvy ) !filter vy
2297    CALL stg_filter_func( nvz, bvz ) !filter vz
2298    CALL stg_filter_func( nwx, bwx ) !filter wx
2299    CALL stg_filter_func( nwy, bwy ) !filter wy
2300    CALL stg_filter_func( nwz, bwz ) !filter wz
2301!
2302!-- Reset time counter for controlling next adjustment to zero
2303    time_stg_adjust = 0.0_wp
2304
2305    IF ( debug_output_timestep )  CALL debug_message( 'stg_adjust', 'end' )
2306   
2307 END SUBROUTINE stg_adjust 
2308 
2309 
2310!------------------------------------------------------------------------------!
2311! Description:
2312! ------------
2313!> Calculates turbuluent length and time scales if these are not available
2314!> from measurements.
2315!------------------------------------------------------------------------------!
2316 SUBROUTINE calc_length_and_time_scale
2317
2318    INTEGER(iwp) ::  k !< loop index in z-direction
2319   
2320    REAL(wp) ::  length_scale_dum     !< effectively used length scale
2321   
2322!
2323!-- In initial call the boundary-layer depth can be zero. This case, set
2324!-- minimum value for boundary-layer depth, to setup length scales correctly.
2325    zi_ribulk = MAX( zi_ribulk, zw(nzb+2) )
2326!
2327!-- Set-up default turbulent length scales. From the numerical point of
2328!-- view the imposed perturbations should not be immediately dissipated
2329!-- by the numerics. The numerical dissipation, however, acts on scales
2330!-- up to 8 x the grid spacing. For this reason, set the turbulence
2331!-- length scale to 8 time the grid spacing. Further, above the boundary
2332!-- layer height, set turbulence lenght scales to zero (equivalent to not
2333!-- imposing any perturbations) in order to save computational costs.
2334!-- Typical time scales are derived by assuming Taylors's hypothesis,
2335!-- using the length scales and the mean profiles of u- and v-component.
2336    DO  k = nzb+1, nzt+1
2337!
2338!--    Determine blending parameter. Within the boundary layer length scales
2339!--    are constant, while above lengths scales approach gradully zero,
2340!--    i.e. imposed turbulence is not correlated in space and time,
2341!--    just white noise, which saves computations power as the loops for the
2342!--    computation of the filter functions depend on the length scales.
2343!--    The value decreases to 1/10 after one length scale above the
2344!--    ABL top.
2345       blend = MIN( 1.0_wp, EXP( d_l * zu(k) - d_l * zi_ribulk ) )
2346!
2347!--    Assume isotropic turbulence length scales
2348       nux(k) = MAX( INT( length_scale * ddx     ), 1 ) * blend
2349       nuy(k) = MAX( INT( length_scale * ddy     ), 1 ) * blend
2350       nvx(k) = MAX( INT( length_scale * ddx     ), 1 ) * blend
2351       nvy(k) = MAX( INT( length_scale * ddy     ), 1 ) * blend
2352       nwx(k) = MAX( INT( length_scale * ddx     ), 1 ) * blend
2353       nwy(k) = MAX( INT( length_scale * ddy     ), 1 ) * blend
2354!
2355!--    Along the vertical direction limit the length scale further by the
2356!--    boundary-layer depth to assure that no length scales larger than
2357!--    the boundary-layer depth are used
2358       length_scale_dum = MIN( length_scale, zi_ribulk )
2359       
2360       nuz(k) = MAX( INT( length_scale_dum * ddzw(k) ), 1 ) * blend
2361       nvz(k) = MAX( INT( length_scale_dum * ddzw(k) ), 1 ) * blend
2362       nwz(k) = MAX( INT( length_scale_dum * ddzw(k) ), 1 ) * blend
2363!
2364!--    Limit time scales, else they become very larger for low wind speed,
2365!--    imposing long-living inflow perturbations which in turn propagate
2366!--    further into the model domain. Use u_init and v_init to calculate
2367!--    the time scales, which will be equal to the inflow profiles, both,
2368!--    in offline nesting mode or in dirichlet/radiation mode.
2369       tu(k)  = MIN( dt_stg_adjust, length_scale /                          &
2370                               ( ABS( u_init(k) ) + 0.1_wp ) ) * blend 
2371       tv(k)  = MIN( dt_stg_adjust, length_scale /                          &
2372                               ( ABS( v_init(k) ) + 0.1_wp ) ) * blend
2373!
2374!--    Time scale of w-component is a mixture from u- and v-component.
2375       tw(k)  = SQRT( tu(k)**2 + tv(k)**2 ) * blend
2376     
2377    ENDDO
2378!
2379!-- Set bottom boundary condition for the length and time scales
2380    nux(nzb) = nux(nzb+1)
2381    nuy(nzb) = nuy(nzb+1)
2382    nuz(nzb) = nuz(nzb+1)
2383    nvx(nzb) = nvx(nzb+1)
2384    nvy(nzb) = nvy(nzb+1)
2385    nvz(nzb) = nvz(nzb+1)
2386    nwx(nzb) = nwx(nzb+1)
2387    nwy(nzb) = nwy(nzb+1)
2388    nwz(nzb) = nwz(nzb+1)
2389
2390    tu(nzb)  = tu(nzb+1)
2391    tv(nzb)  = tv(nzb+1)
2392    tw(nzb)  = tw(nzb+1)
2393
2394
2395 END SUBROUTINE calc_length_and_time_scale 
2396
2397!------------------------------------------------------------------------------!
2398! Description:
2399! ------------
2400!> Calculate scaling variables which are used for turbulence parametrization
2401!> according to Rotach et al. (1996). Scaling variables are: friction velocity,
2402!> boundary-layer depth, momentum velocity scale, and Obukhov length.
2403!------------------------------------------------------------------------------!
2404 SUBROUTINE calc_scaling_variables
2405
2406    INTEGER(iwp) :: i            !< loop index in x-direction
2407    INTEGER(iwp) :: j            !< loop index in y-direction
2408    INTEGER(iwp) :: k            !< loop index in z-direction
2409    INTEGER(iwp) :: m            !< surface element index
2410
2411    REAL(wp) ::  friction_vel_l         !< mean friction veloctiy on subdomain
2412    REAL(wp) ::  pt_surf_mean           !< mean near surface temperature (at 1st grid point)
2413    REAL(wp) ::  pt_surf_mean_l         !< mean near surface temperature (at 1st grid point) on subdomain
2414    REAL(wp) ::  scale_l_l              !< mean Obukhov lenght on subdomain
2415    REAL(wp) ::  shf_mean               !< mean surface sensible heat flux
2416    REAL(wp) ::  shf_mean_l             !< mean surface sensible heat flux on subdomain
2417    REAL(wp) ::  w_convective           !< convective velocity scale
2418   
2419!
2420!-- Calculate mean friction velocity, velocity scale, heat flux and
2421!-- near-surface temperature in the model domain. 
2422    pt_surf_mean_l = 0.0_wp
2423    shf_mean_l     = 0.0_wp
2424    scale_l_l      = 0.0_wp
2425    friction_vel_l = 0.0_wp
2426    DO  m = 1, surf_def_h(0)%ns
2427       i = surf_def_h(0)%i(m)
2428       j = surf_def_h(0)%j(m)
2429       k = surf_def_h(0)%k(m)
2430       friction_vel_l = friction_vel_l  + surf_def_h(0)%us(m)
2431       shf_mean_l     = shf_mean_l      + surf_def_h(0)%shf(m) * drho_air(k)
2432       scale_l_l      = scale_l_l       + surf_def_h(0)%ol(m)
2433       pt_surf_mean_l = pt_surf_mean_l  + pt(k,j,i)
2434    ENDDO   
2435    DO  m = 1, surf_lsm_h%ns
2436       i = surf_lsm_h%i(m)
2437       j = surf_lsm_h%j(m)
2438       k = surf_lsm_h%k(m)
2439       friction_vel_l = friction_vel_l  + surf_lsm_h%us(m)
2440       shf_mean_l     = shf_mean_l      + surf_lsm_h%shf(m) * drho_air(k)
2441       scale_l_l      = scale_l_l       + surf_lsm_h%ol(m)
2442       pt_surf_mean_l = pt_surf_mean_l  + pt(k,j,i)
2443    ENDDO
2444    DO  m = 1, surf_usm_h%ns
2445       i = surf_usm_h%i(m)
2446       j = surf_usm_h%j(m)
2447       k = surf_usm_h%k(m)
2448       friction_vel_l = friction_vel_l  + surf_usm_h%us(m)
2449       shf_mean_l     = shf_mean_l      + surf_usm_h%shf(m) * drho_air(k)
2450       scale_l_l      = scale_l_l       + surf_usm_h%ol(m)
2451       pt_surf_mean_l = pt_surf_mean_l  + pt(k,j,i)
2452    ENDDO
2453   
2454#if defined( __parallel )
2455    CALL MPI_ALLREDUCE( friction_vel_l, scale_us,     1, MPI_REAL, MPI_SUM,    &
2456                        comm2d, ierr )
2457    CALL MPI_ALLREDUCE( shf_mean_l, shf_mean,         1, MPI_REAL, MPI_SUM,    &
2458                        comm2d, ierr )
2459    CALL MPI_ALLREDUCE( scale_l_l, scale_l,           1, MPI_REAL, MPI_SUM,    &
2460                        comm2d, ierr )
2461    CALL MPI_ALLREDUCE( pt_surf_mean_l, pt_surf_mean, 1, MPI_REAL, MPI_SUM,    &
2462                        comm2d, ierr )
2463#else
2464    scale_us     = friction_vel_l
2465    shf_mean     = shf_mean_l
2466    scale_l      = scale_l_l
2467    pt_surf_mean = pt_surf_mean_l
2468#endif
2469
2470    scale_us     = scale_us     / REAL( ( nx + 1 ) * ( ny + 1 ), KIND = wp )
2471    shf_mean     = shf_mean     / REAL( ( nx + 1 ) * ( ny + 1 ), KIND = wp )
2472    scale_l      = scale_l      / REAL( ( nx + 1 ) * ( ny + 1 ), KIND = wp )
2473    pt_surf_mean = pt_surf_mean / REAL( ( nx + 1 ) * ( ny + 1 ), KIND = wp )   
2474!
2475!-- Compute mean convective velocity scale. Note, in case the mean heat flux
2476!-- is negative, set convective velocity scale to zero.
2477    IF ( shf_mean > 0.0_wp )  THEN
2478       w_convective = ( g * shf_mean * zi_ribulk / pt_surf_mean )**( 1.0_wp / 3.0_wp )
2479    ELSE
2480       w_convective = 0.0_wp
2481    ENDIF
2482!
2483!-- Finally, in order to consider also neutral or stable stratification,
2484!-- compute momentum velocity scale from u* and convective velocity scale,
2485!-- according to Rotach et al. (1996).
2486    scale_wm = ( scale_us**3 + 0.6_wp * w_convective**3 )**( 1.0_wp / 3.0_wp )
2487   
2488 END SUBROUTINE calc_scaling_variables
2489
2490 END MODULE synthetic_turbulence_generator_mod
Note: See TracBrowser for help on using the repository browser.