SUBROUTINE inflow_turbulence !--------------------------------------------------------------------------------! ! This file is part of PALM. ! ! PALM is free software: you can redistribute it and/or modify it under the terms ! of the GNU General Public License as published by the Free Software Foundation, ! either version 3 of the License, or (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2014 Leibniz Universitaet Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: inflow_turbulence.f90 1354 2014-04-08 15:22:57Z raasch $ ! ! 1353 2014-04-08 15:21:23Z heinze ! REAL constants provided with KIND-attribute ! ! 1346 2014-03-27 13:18:20Z heinze ! Bugfix: REAL constants provided with KIND-attribute especially in call of ! intrinsic function like MAX, MIN, SIGN ! ! 1320 2014-03-20 08:40:49Z raasch ! ONLY-attribute added to USE-statements, ! kind-parameters added to all INTEGER and REAL declaration statements, ! kinds are defined in new module kinds, ! revision history before 2012 removed, ! comment fields (!:) to be used for variable explanations added to ! all variable declaration statements ! ! 1092 2013-02-02 11:24:22Z raasch ! unused variables removed ! ! 1036 2012-10-22 13:43:42Z raasch ! code put under GPL (PALM 3.9) ! ! Initial version (2008/03/07) ! ! Description: ! ------------ ! Imposing turbulence at the respective inflow using the turbulence ! recycling method of Kataoka and Mizuno (2002). !------------------------------------------------------------------------------! USE arrays_3d, & ONLY: e, inflow_damping_factor, mean_inflow_profiles, pt, u, v, w USE control_parameters, & ONLY: recycling_plane USE cpulog, & ONLY: cpu_log, log_point USE grid_variables, & ONLY: USE indices, & ONLY: nbgp, nxl, ny, nyn, nys, nyng, nysg, nzb, nzt USE kinds USE pegrid IMPLICIT NONE INTEGER(iwp) :: i !: INTEGER(iwp) :: j !: INTEGER(iwp) :: k !: INTEGER(iwp) :: l !: INTEGER(iwp) :: ngp_ifd !: INTEGER(iwp) :: ngp_pr !: REAL(wp), DIMENSION(nzb:nzt+1,5,nbgp) :: & avpr, avpr_l !: REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,5,nbgp) :: & inflow_dist !: CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' ) ! !-- Carry out spanwise averaging in the recycling plane avpr_l = 0.0_wp ngp_pr = ( nzt - nzb + 2 ) * 5 * nbgp ngp_ifd = ngp_pr * ( nyn - nys + 1 + 2 * nbgp ) ! !-- First, local averaging within the recycling domain i = recycling_plane #if defined( __parallel ) IF ( myidx == id_recycling ) THEN DO l = 1, nbgp DO j = nys, nyn DO k = nzb, nzt + 1 avpr_l(k,1,l) = avpr_l(k,1,l) + u(k,j,i) avpr_l(k,2,l) = avpr_l(k,2,l) + v(k,j,i) avpr_l(k,3,l) = avpr_l(k,3,l) + w(k,j,i) avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i) avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i) ENDDO ENDDO i = i + 1 ENDDO ENDIF ! !-- Now, averaging over all PEs IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr ) CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL, & MPI_SUM, comm2d, ierr ) #else DO l = 1, nbgp DO j = nys, nyn DO k = nzb, nzt + 1 avpr_l(k,1,l) = avpr_l(k,1,l) + u(k,j,i) avpr_l(k,2,l) = avpr_l(k,2,l) + v(k,j,i) avpr_l(k,3,l) = avpr_l(k,3,l) + w(k,j,i) avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i) avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i) ENDDO ENDDO i = i + 1 ENDDO avpr = avpr_l #endif avpr = avpr / ( ny + 1 ) ! !-- Calculate the disturbances at the recycling plane i = recycling_plane #if defined( __parallel ) IF ( myidx == id_recycling ) THEN DO l = 1, nbgp DO j = nysg, nyng DO k = nzb, nzt + 1 inflow_dist(k,j,1,l) = u(k,j,i+1) - avpr(k,1,l) inflow_dist(k,j,2,l) = v(k,j,i) - avpr(k,2,l) inflow_dist(k,j,3,l) = w(k,j,i) - avpr(k,3,l) inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l) inflow_dist(k,j,5,l) = e(k,j,i) - avpr(k,5,l) ENDDO ENDDO i = i + 1 ENDDO ENDIF #else DO l = 1, nbgp DO j = nysg, nyng DO k = nzb, nzt+1 inflow_dist(k,j,1,l) = u(k,j,i+1) - avpr(k,1,l) inflow_dist(k,j,2,l) = v(k,j,i) - avpr(k,2,l) inflow_dist(k,j,3,l) = w(k,j,i) - avpr(k,3,l) inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l) inflow_dist(k,j,5,l) = e(k,j,i) - avpr(k,5,l) ENDDO ENDDO i = i + 1 ENDDO #endif ! !-- For parallel runs, send the disturbances to the respective inflow PE #if defined( __parallel ) IF ( myidx == id_recycling .AND. myidx /= id_inflow ) THEN CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, & id_inflow, 1, comm1dx, ierr ) ELSEIF ( myidx /= id_recycling .AND. myidx == id_inflow ) THEN inflow_dist = 0.0_wp CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, & id_recycling, 1, comm1dx, status, ierr ) ENDIF #endif ! !-- Add the disturbance at the inflow IF ( nxl == 0 ) THEN DO j = nysg, nyng DO k = nzb, nzt + 1 u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) + & inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k) v(k,j,-nbgp:-1) = mean_inflow_profiles(k,2) + & inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k) w(k,j,-nbgp:-1) = & inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k) pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) + & inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k) e(k,j,-nbgp:-1) = mean_inflow_profiles(k,5) + & inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k) e(k,j,-nbgp:-1) = MAX( e(k,j,-nbgp:-1), 0.0_wp ) ENDDO ENDDO ENDIF CALL cpu_log( log_point(40), 'inflow_turbulence', 'stop' ) END SUBROUTINE inflow_turbulence