Merge branch 'master' into gem-reconnection-challenge

This commit is contained in:
Grzegorz Kowal 2022-11-25 18:22:45 -03:00
commit 0cd26a7683
2 changed files with 55 additions and 125 deletions

View File

@ -1135,12 +1135,6 @@ module evolution
end if ! toplev > 1
#ifdef DEBUG
! check variables for NaNs
!
call check_variables()
#endif /* DEBUG */
! error entry point
!
100 continue
@ -4319,73 +4313,6 @@ module evolution
!-------------------------------------------------------------------------------
!
end subroutine update_errors_max
#ifdef DEBUG
!
!===============================================================================
!
! subroutine CHECK_VARIABLES:
! --------------------------
!
! Subroutine iterates over all data blocks and converts the conservative
! variables to their primitive representation.
!
!
!===============================================================================
!
subroutine check_variables()
use coordinates , only : nn => bcells
use equations , only : nv, pvars, cvars
use ieee_arithmetic, only : ieee_is_nan
use blocks , only : block_meta
use blocks , only : block_data, list_data
implicit none
integer :: i, j, k, p
type(block_meta), pointer :: pmeta
type(block_data), pointer :: pdata
!-------------------------------------------------------------------------------
!
#if NDIMS == 2
k = 1
#endif /* NDIMS == 2 */
pdata => list_data
do while (associated(pdata))
pmeta => pdata%meta
#if NDIMS == 3
do k = 1, nn
#endif /* NDIMS == 3 */
do j = 1, nn
do i = 1, nn
do p = 1, nv
if (ieee_is_nan(pdata%u(p,i,j,k))) then
print *, 'U NaN:', cvars(p), pdata%meta%id, i, j, k
end if
if (ieee_is_nan(pdata%q(p,i,j,k))) then
print *, 'Q NaN:', pvars(p), pdata%meta%id, i, j, k
end if
end do ! p = 1, nv
end do ! i = 1, nn
end do ! j = 1, nn
#if NDIMS == 3
end do ! k = 1, nn
#endif /* NDIMS == 3 */
pdata => pdata%next
end do
!-------------------------------------------------------------------------------
!
end subroutine check_variables
#endif /* DEBUG */
!===============================================================================
!

View File

@ -1212,33 +1212,28 @@ module forcing
!
subroutine inject_eddy(xp, ap)
use blocks, only : block_data, list_data
use blocks, only : block_data, data_blocks, get_dblocks
implicit none
real(kind=8), dimension(3), intent(in) :: xp, ap
integer :: m, n
type(block_data), pointer :: pdata
!-------------------------------------------------------------------------------
!
! assign pdata with the first block on the data block list
!
pdata => list_data
n = get_dblocks()
! iterate over all data blocks
!
do while (associated(pdata))
!$omp parallel do default(shared) private(pdata)
do m = 1, n
pdata => data_blocks(m)%ptr
! inject eddy into the current block
!
call inject_eddy_block(pdata, xp(:), ap(:))
! assign pdata to the next block
!
pdata => pdata%next
end do ! over data blocks
end do
!$omp end parallel do
!-------------------------------------------------------------------------------
!
@ -1420,33 +1415,28 @@ module forcing
!
subroutine inject_fmodes(dt)
use blocks, only : block_data, list_data
use blocks, only : block_data, data_blocks, get_dblocks
implicit none
real(kind=8), intent(in) :: dt
integer :: m, n
type(block_data), pointer :: pdata
!-------------------------------------------------------------------------------
!
! assign pdata with the first block on the data block list
!
pdata => list_data
n = get_dblocks()
! iterate over all data blocks
!
do while (associated(pdata))
!$omp parallel do default(shared) private(pdata)
do m = 1, n
pdata => data_blocks(m)%ptr
! inject eddy into the current block
!
call inject_fmodes_block(pdata, dt)
! assign pdata to the next block
!
pdata => pdata%next
end do ! over data blocks
end do
!$omp end parallel do
!-------------------------------------------------------------------------------
!
@ -1699,42 +1689,53 @@ module forcing
!
subroutine get_vcoefs()
use blocks , only : block_data, list_data
use blocks , only : block_data, data_blocks, get_dblocks
use helpers , only : print_message
#ifdef MPI
use mpitools, only : reduce_sum
#endif /* MPI */
implicit none
integer :: m, n, status
type(block_data), pointer :: pdata
complex(kind=8), dimension(:,:,:), allocatable :: vc
character(len=*), parameter :: loc = 'FORCING:get_vcoefs()'
!-------------------------------------------------------------------------------
!
! reset vcoefs
!
vcoefs(:,:) = cmplx(0.0d+00, 0.0d+00, kind=8)
n = get_dblocks()
! assign pdata with the first block on the data block list
!
pdata => list_data
allocate(vc(nmodes, NDIMS, n), stat=status)
if (status /= 0) then
call print_message(loc, &
"Could not allocate memory for the Fourier coefficients!")
go to 100
end if
! iterate over all data blocks
!
do while (associated(pdata))
vc(:,:,:) = cmplx(0.0d+00, 0.0d+00, kind=8)
! get contribution of velocity coefficients from the current block
!
call get_vcoefs_block(pdata)
!$omp parallel do default(shared) private(pdata)
do m = 1, n
pdata => data_blocks(m)%ptr
! assign pdata to the next block
!
pdata => pdata%next
call get_vcoefs_block(pdata, vc(:,:,m))
end do
!$omp end parallel do
end do ! over data blocks
vcoefs = sum(vc, 3)
deallocate(vc, stat=status)
if (status /= 0) &
call print_message(loc, &
"Could not release memory of the Fourier coefficients!")
100 continue
#ifdef MPI
! reduce velocity coefficients over all processes
!
call reduce_sum(vcoefs)
#endif /* MPI */
@ -1752,10 +1753,11 @@ module forcing
! Arguments:
!
! 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 constants , only : pi2
@ -1771,7 +1773,8 @@ module forcing
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
real(kind=8) :: cs, sn, dvol
@ -1837,10 +1840,10 @@ module forcing
cf = cmplx(cs, sn, kind=8) * dvol
vcoefs(l,1) = vcoefs(l,1) + pdata%q(ivx,i,j,k) * cf
vcoefs(l,2) = vcoefs(l,2) + pdata%q(ivy,i,j,k) * cf
vc(l,1) = vc(l,1) + pdata%q(ivx,i,j,k) * cf
vc(l,2) = vc(l,2) + pdata%q(ivy,i,j,k) * cf
#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 */
end do