Merge branch 'master' into reconnection

This commit is contained in:
Grzegorz Kowal 2022-11-25 16:09:58 -03:00
commit 11bfa4f6ef

View File

@ -1420,33 +1420,28 @@ module forcing
! !
subroutine inject_fmodes(dt) subroutine inject_fmodes(dt)
use blocks, only : block_data, list_data use blocks, only : block_data, data_blocks, get_dblocks
implicit none implicit none
real(kind=8), intent(in) :: dt real(kind=8), intent(in) :: dt
integer :: m, n
type(block_data), pointer :: pdata type(block_data), pointer :: pdata
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
! assign pdata with the first block on the data block list n = get_dblocks()
!
pdata => list_data
! iterate over all data blocks !$omp parallel do default(shared) private(pdata)
! do m = 1, n
do while (associated(pdata)) pdata => data_blocks(m)%ptr
! inject eddy into the current block
!
call inject_fmodes_block(pdata, dt) call inject_fmodes_block(pdata, dt)
! assign pdata to the next block end do
! !$omp end parallel do
pdata => pdata%next
end do ! over data blocks
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
@ -1699,42 +1694,48 @@ module forcing
! !
subroutine get_vcoefs() subroutine get_vcoefs()
use blocks , only : block_data, list_data use blocks , only : block_data, data_blocks, get_dblocks
#ifdef MPI #ifdef MPI
use mpitools, only : reduce_sum use mpitools, only : reduce_sum
#endif /* MPI */ #endif /* MPI */
implicit none implicit none
integer :: m, n, nt
type(block_data), pointer :: pdata type(block_data), pointer :: pdata
complex(kind=8), dimension(:,:,:), allocatable :: vc
!$ integer :: omp_get_num_threads, omp_get_thread_num
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
! reset vcoefs nt = 0
! !$omp parallel
vcoefs(:,:) = cmplx(0.0d+00, 0.0d+00, kind=8) !$ nt = omp_get_num_threads() - 1
!$omp end parallel
allocate(vc(nmodes, NDIMS, 0:nt))
! assign pdata with the first block on the data block list vc(:,:,:) = cmplx(0.0d+00, 0.0d+00, kind=8)
!
pdata => list_data
! iterate over all data blocks n = get_dblocks()
! !$omp parallel default(shared) private(pdata,nt)
do while (associated(pdata)) !$ nt = omp_get_thread_num()
!$omp do
do m = 1, n
pdata => data_blocks(m)%ptr
! get contribution of velocity coefficients from the current block call get_vcoefs_block(pdata, vc(:,:,nt))
! end do
call get_vcoefs_block(pdata) !$omp end do
!$omp end parallel
! assign pdata to the next block vcoefs = sum(vc, 3)
!
pdata => pdata%next
end do ! over data blocks deallocate(vc)
#ifdef MPI #ifdef MPI
! reduce velocity coefficients over all processes
!
call reduce_sum(vcoefs) call reduce_sum(vcoefs)
#endif /* MPI */ #endif /* MPI */
@ -1752,10 +1753,11 @@ module forcing
! Arguments: ! Arguments:
! !
! pdata - a pointer to the data block; ! pdata - a pointer to the data block;
! vc - an array for the velocity Fourier coefficients;
! !
!=============================================================================== !===============================================================================
! !
subroutine get_vcoefs_block(pdata) subroutine get_vcoefs_block(pdata, vc)
use blocks , only : block_data use blocks , only : block_data
use constants , only : pi2 use constants , only : pi2
@ -1771,7 +1773,8 @@ module forcing
implicit none implicit none
type(block_data), pointer, intent(inout) :: pdata type(block_data), pointer , intent(inout) :: pdata
complex(kind=8), dimension(:,:), intent(inout) :: vc
integer :: i, j, k, l integer :: i, j, k, l
real(kind=8) :: cs, sn, dvol real(kind=8) :: cs, sn, dvol
@ -1837,10 +1840,10 @@ module forcing
cf = cmplx(cs, sn, kind=8) * dvol cf = cmplx(cs, sn, kind=8) * dvol
vcoefs(l,1) = vcoefs(l,1) + pdata%q(ivx,i,j,k) * cf vc(l,1) = vc(l,1) + pdata%q(ivx,i,j,k) * cf
vcoefs(l,2) = vcoefs(l,2) + pdata%q(ivy,i,j,k) * cf vc(l,2) = vc(l,2) + pdata%q(ivy,i,j,k) * cf
#if NDIMS == 3 #if NDIMS == 3
vcoefs(l,3) = vcoefs(l,3) + pdata%q(ivz,i,j,k) * cf vc(l,3) = vc(l,3) + pdata%q(ivz,i,j,k) * cf
#endif /* NDIMS == 3 */ #endif /* NDIMS == 3 */
end do end do