Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 6 additions & 0 deletions src/common/m_derived_types.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -443,4 +443,10 @@ module m_derived_types

end type bubbles_lagrange_parameters

!> Max and min number of cells in a direction of each combination of x-,y-, and z-
type cell_num_bounds
integer :: mn_max, np_max, mp_max, mnp_max
integer :: mn_min, np_min, mp_min, mnp_min
end type cell_num_bounds

end module m_derived_types
23 changes: 22 additions & 1 deletion src/common/m_helper_basic.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@ module m_helper_basic
f_is_default, &
f_all_default, &
f_is_integer, &
s_configure_coordinate_bounds
s_configure_coordinate_bounds, &
s_update_cell_bounds

contains

Expand Down Expand Up @@ -146,4 +147,24 @@ contains

end subroutine s_configure_coordinate_bounds

!> Updates the min and max number of cells in each set of axes
!! @param bounds Min ans max values to update
!! @param m Number of cells in x-axis
!! @param n Number of cells in y-axis
!! @param p Number of cells in z-axis
pure elemental subroutine s_update_cell_bounds(bounds, m, n, p)
type(cell_num_bounds), intent(out) :: bounds
integer, intent(in) :: m, n, p

bounds%mn_max = max(m, n)
bounds%np_max = max(n, p)
bounds%mp_max = max(m, p)
bounds%mnp_max = max(m, n, p)
bounds%mn_min = min(m, n)
bounds%np_min = min(n, p)
bounds%mp_min = min(m, p)
bounds%mnp_min = min(m, n, p)

end subroutine s_update_cell_bounds

end module m_helper_basic
6 changes: 4 additions & 2 deletions src/common/m_mpi_common.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -67,10 +67,10 @@ contains
& (m + 2*buff_size + 1)* &
& (n + 2*buff_size + 1)* &
& (p + 2*buff_size + 1)/ &
& (min(m, n, p) + 2*buff_size + 1))
& (cells_bounds%mnp_min + 2*buff_size + 1))
else
halo_size = -1 + buff_size*(v_size)* &
& (max(m, n) + 2*buff_size + 1)
& (cells_bounds%mn_max + 2*buff_size + 1)
end if
else
halo_size = -1 + buff_size*(v_size)
Expand Down Expand Up @@ -1446,6 +1446,8 @@ contains
end if
end do

call s_update_cell_bounds(cells_bounds, m, n, p)

! Boundary condition at the beginning
if (proc_coords(1) > 0 .or. (bc_x%beg == BC_PERIODIC .and. num_procs_x > 1)) then
proc_coords(1) = proc_coords(1) - 1
Expand Down
2 changes: 1 addition & 1 deletion src/common/m_variables_conversion.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -637,7 +637,7 @@
#ifdef MFC_SIMULATION

if (viscous) then
@:ALLOCATE(Res(1:2, 1:maxval(Re_size)))
@:ALLOCATE(Res(1:2, 1:Re_size_max))

Check warning on line 640 in src/common/m_variables_conversion.fpp

View check run for this annotation

Codecov / codecov/patch

src/common/m_variables_conversion.fpp#L640

Added line #L640 was not covered by tests
do i = 1, 2
do j = 1, Re_size(i)
Res(i, j) = fluid_pp(Re_idx(i, j))%Re(i)
Expand Down
5 changes: 5 additions & 0 deletions src/post_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,9 @@ module m_global_parameters
integer :: p
!> @}

!> @name Max and min number of cells in a direction of each combination of x-,y-, and z-
type(cell_num_bounds) :: cells_bounds

integer(8) :: nGlobal ! Total number of cells in global domain

!> @name Cylindrical coordinates (either axisymmetric or full 3D)
Expand Down Expand Up @@ -336,6 +339,8 @@ contains

! Computational domain parameters
m = dflt_int; n = 0; p = 0
call s_update_cell_bounds(cells_bounds, m, n, p)

m_root = dflt_int
cyl_coord = .false.

Expand Down
3 changes: 3 additions & 0 deletions src/post_process/m_start_up.f90
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,9 @@ impure subroutine s_read_input_file
end if

close (1)

call s_update_cell_bounds(cells_bounds, m, n, p)

! Store m,n,p into global m,n,p
m_glb = m
n_glb = n
Expand Down
5 changes: 5 additions & 0 deletions src/pre_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,9 @@ module m_global_parameters
integer :: n
integer :: p

!> @name Max and min number of cells in a direction of each combination of x-,y-, and z-
type(cell_num_bounds) :: cells_bounds

integer(8) :: nGlobal !< Global number of cells in the domain

integer :: m_glb, n_glb, p_glb !< Global number of cells in each direction
Expand Down Expand Up @@ -306,6 +309,8 @@ contains
! Computational domain parameters
m = dflt_int; n = 0; p = 0

call s_update_cell_bounds(cells_bounds, m, n, p)

cyl_coord = .false.

x_domain%beg = dflt_real
Expand Down
3 changes: 3 additions & 0 deletions src/pre_process/m_start_up.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -169,6 +169,9 @@ contains
'likely due to a datatype mismatch. Exiting.')
end if
close (1)

call s_update_cell_bounds(cells_bounds, m, n, p)

! Store m,n,p into global m,n,p
m_glb = m
n_glb = n
Expand Down
16 changes: 11 additions & 5 deletions src/simulation/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@
integer :: m, n, p
!> @}

!> @name Max and min number of cells in a direction of each combination of x-,y-, and z-
type(cell_num_bounds) :: cells_bounds

!> @name Global number of cells in each direction
!> @{
integer :: m_glb, n_glb, p_glb
Expand Down Expand Up @@ -273,10 +276,11 @@
!! numbers, will be non-negligible.
!> @{
integer, dimension(2) :: Re_size
integer :: Re_size_max
integer, allocatable, dimension(:, :) :: Re_idx
!> @}

$:GPU_DECLARE(create='[Re_size,Re_idx]')
$:GPU_DECLARE(create='[Re_size,Re_size_max,Re_idx]')

! The WENO average (WA) flag regulates whether the calculation of any cell-
! average spatial derivatives is carried out in each cell by utilizing the
Expand Down Expand Up @@ -525,6 +529,7 @@

! Computational domain parameters
m = dflt_int; n = 0; p = 0
call s_update_cell_bounds(cells_bounds, m, n, p)

cyl_coord = .false.

Expand Down Expand Up @@ -809,6 +814,7 @@
! of fluids for which the physical and geometric curvatures of the
! interfaces will be computed
Re_size = 0
Re_size_max = 0

! Gamma/Pi_inf Model
if (model_eqns == 1) then
Expand Down Expand Up @@ -1036,13 +1042,15 @@
if (Re_size(1) > 0._wp) shear_stress = .true.
if (Re_size(2) > 0._wp) bulk_stress = .true.

$:GPU_UPDATE(device='[Re_size,viscous,shear_stress,bulk_stress]')
Re_size_max = maxval(Re_size)

$:GPU_UPDATE(device='[Re_size,Re_size_max,viscous,shear_stress,bulk_stress]')

! Bookkeeping the indexes of any viscous fluids and any pairs of
! fluids whose interface will support effects of surface tension
if (viscous) then

@:ALLOCATE(Re_idx(1:2, 1:maxval(Re_size)))
@:ALLOCATE(Re_idx(1:2, 1:Re_size_max))

Check warning on line 1053 in src/simulation/m_global_parameters.fpp

View check run for this annotation

Codecov / codecov/patch

src/simulation/m_global_parameters.fpp#L1053

Added line #L1053 was not covered by tests

k = 0
do i = 1, num_fluids
Expand Down Expand Up @@ -1169,8 +1177,6 @@
if (ib) allocate (MPI_IO_IB_DATA%var%sf(0:m, 0:n, 0:p))
Np = 0

$:GPU_UPDATE(device='[Re_size]')

if (elasticity) then
fd_number = max(1, fd_order/2)
end if
Expand Down
4 changes: 2 additions & 2 deletions src/simulation/m_mpi_proxy.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -62,10 +62,10 @@ contains
& (m + 2*gp_layers + 1)* &
& (n + 2*gp_layers + 1)* &
& (p + 2*gp_layers + 1)/ &
& (min(m, n, p) + 2*gp_layers + 1)
& (cells_bounds%mnp_min + 2*gp_layers + 1)
else
i_halo_size = -1 + gp_layers* &
& (max(m, n) + 2*gp_layers + 1)
& (cells_bounds%mn_max + 2*gp_layers + 1)
end if
else
i_halo_size = -1 + gp_layers
Expand Down
2 changes: 1 addition & 1 deletion src/simulation/m_pressure_relaxation.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@
$:GPU_UPDATE(device='[gamma_min, pres_inf]')

if (viscous) then
@:ALLOCATE(Res(1:2, 1:maxval(Re_size)))
@:ALLOCATE(Res(1:2, 1:Re_size_max))

Check warning on line 45 in src/simulation/m_pressure_relaxation.fpp

View check run for this annotation

Codecov / codecov/patch

src/simulation/m_pressure_relaxation.fpp#L45

Added line #L45 was not covered by tests
do i = 1, 2
do j = 1, Re_size(i)
Res(i, j) = fluid_pp(Re_idx(i, j))%Re(i)
Expand Down
2 changes: 1 addition & 1 deletion src/simulation/m_riemann_solvers.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -3169,7 +3169,7 @@
$:GPU_UPDATE(device='[Gs]')

if (viscous) then
@:ALLOCATE(Res(1:2, 1:maxval(Re_size)))
@:ALLOCATE(Res(1:2, 1:Re_size_max))

Check warning on line 3172 in src/simulation/m_riemann_solvers.fpp

View check run for this annotation

Codecov / codecov/patch

src/simulation/m_riemann_solvers.fpp#L3172

Added line #L3172 was not covered by tests
end if

if (viscous) then
Expand Down
2 changes: 2 additions & 0 deletions src/simulation/m_start_up.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -210,6 +210,8 @@ contains
n_glb = n
p_glb = p

call s_update_cell_bounds(cells_bounds, m, n, p)

if (cfl_adap_dt .or. cfl_const_dt) cfl_dt = .true.

if (any((/bc_x%beg, bc_x%end, bc_y%beg, bc_y%end, bc_z%beg, bc_z%end/) == -17) .or. &
Expand Down
2 changes: 1 addition & 1 deletion src/simulation/m_viscous.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@

integer :: i, j !< generic loop iterators

@:ALLOCATE(Res_viscous(1:2, 1:maxval(Re_size)))
@:ALLOCATE(Res_viscous(1:2, 1:Re_size_max))

Check warning on line 38 in src/simulation/m_viscous.fpp

View check run for this annotation

Codecov / codecov/patch

src/simulation/m_viscous.fpp#L38

Added line #L38 was not covered by tests

do i = 1, 2
do j = 1, Re_size(i)
Expand Down
Loading