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

Last change on this file since 4642 was 4640, checked in by suehring, 4 years ago

synthetic turbulence generator: to avoid that the correction term in r11/r22 computation becomes unrealistically high, limit Obukhov length (term is not valid for near neutral conditions); to avoid unrealistically large perturbations, change computation of r21 so that this resembles the vertical transport of horizontal momentum

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