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

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

files re-formatted to follow the PALM coding standard

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