Skip to content

Commit

Permalink
coordinate bounds updates
Browse files Browse the repository at this point in the history
  • Loading branch information
wilfonba committed Mar 8, 2025
1 parent 2e42cc7 commit 637c765
Show file tree
Hide file tree
Showing 4 changed files with 54 additions and 98 deletions.
40 changes: 39 additions & 1 deletion src/common/m_helper_basic.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ module m_helper_basic
public :: f_approx_equal, &
f_is_default, &
f_all_default, &
f_is_integer
f_is_integer, &
s_configure_coordinate_bounds

contains

Expand Down Expand Up @@ -74,4 +75,41 @@ logical function f_is_integer(var) result(res)
res = f_approx_equal(var, real(nint(var), wp))
end function f_is_integer

subroutine s_configure_coordinate_bounds(weno_polyn, buff_size, idwint, idwbuff, &
viscous, bubbles_lagrange, m, n, p, num_dims)

integer, intent(in) :: weno_polyn, m, n, p, num_dims
integer, intent(inout) :: buff_size
type(int_bounds_info), dimension(3), intent(inout) :: idwint, idwbuff
logical, intent(in) :: viscous, bubbles_lagrange

! Determining the number of cells that are needed in order to store
! sufficient boundary conditions data as to iterate the solution in
! the physical computational domain from one time-step iteration to
! the next one
if (viscous) then
buff_size = 2*weno_polyn + 2
else
buff_size = weno_polyn + 2
end if

! Correction for smearing function in the lagrangian subgrid bubble model
if (bubbles_lagrange) then
buff_size = max(buff_size, 6)
end if

! Configuring Coordinate Direction Indexes
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p

idwbuff(1)%beg = -buff_size
if (num_dims > 1) then; idwbuff(2)%beg = -buff_size; else; idwbuff(2)%beg = 0; end if
if (num_dims > 2) then; idwbuff(3)%beg = -buff_size; else; idwbuff(3)%beg = 0; end if

idwbuff(1)%end = idwint(1)%end - idwbuff(1)%beg
idwbuff(2)%end = idwint(2)%end - idwbuff(2)%beg
idwbuff(3)%end = idwint(3)%end - idwbuff(3)%beg

end subroutine s_configure_coordinate_bounds

end module m_helper_basic
52 changes: 7 additions & 45 deletions src/post_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -194,15 +194,6 @@ module m_global_parameters
type(bounds_info) :: x_output, y_output, z_output !< Portion of domain to output for post-processing
type(int_bounds_info) :: x_output_idx, y_output_idx, z_output_idx !< Indices of domain to output for post-processing

!> @name Size of the ghost zone layer in the x-, y- and z-coordinate directions.
!! The definition of the ghost zone layers is only necessary when using the
!! Silo database file format in multidimensions. These zones provide VisIt
!! with the subdomain connectivity information that it requires in order to
!! produce smooth plots.
!> @{
type(int_bounds_info) :: offset_x, offset_y, offset_z
!> @}

!> @name The list of all possible flow variables that may be written to a database
!! file. It includes partial densities, density, momentum, velocity, energy,
!! pressure, volume fraction(s), specific heat ratio function, specific heat
Expand Down Expand Up @@ -719,7 +710,6 @@ contains
chemxe = species_idx%end

#ifdef MFC_MPI

if (bubbles_lagrange) then
allocate (MPI_IO_DATA%view(1:sys_size + 1))
allocate (MPI_IO_DATA%var(1:sys_size + 1))
Expand All @@ -739,35 +729,7 @@ contains
if (ib) allocate (MPI_IO_IB_DATA%var%sf(0:m, 0:n, 0:p))
#endif

! Size of the ghost zone layer is non-zero only when post-processing
! the raw simulation data of a parallel multidimensional computation
! in the Silo-HDF5 format. If this is the case, one must also verify
! whether the raw simulation data is 2D or 3D. In the 2D case, size
! of the z-coordinate direction ghost zone layer must be zeroed out.
if (num_procs == 1 .or. format /= 1 .or. n == 0) then

offset_x%beg = 0
offset_x%end = 0
offset_y%beg = 0
offset_y%end = 0
offset_z%beg = 0
offset_z%end = 0

elseif (p == 0) then

offset_z%beg = 0
offset_z%end = 0

end if

! Determining the finite-difference number and the buffer size. Note
! that the size of the buffer is unrelated to the order of the WENO
! scheme. Rather, it is directly dependent on maximum size of ghost
! zone layers and possibly the order of the finite difference scheme
! used for the computation of vorticity and/or numerical Schlieren
! function.
buff_size = max(offset_x%beg, offset_x%end, offset_y%beg, &
offset_y%end, offset_z%beg, offset_z%end)
buff_size = 0

if (any(omega_wrt) .or. schlieren_wrt .or. qm_wrt) then
fd_number = max(1, fd_order/2)
Expand All @@ -788,31 +750,31 @@ contains

! Allocating single precision grid variables if needed
if (precision == 1) then
allocate (x_cb_s(-1 - offset_x%beg:m + offset_x%end))
allocate (x_cb_s(-1:m))
if (n > 0) then
allocate (y_cb_s(-1 - offset_x%beg:n + offset_x%end))
allocate (y_cb_s(-1:n))
if (p > 0) then
allocate (z_cb_s(-1 - offset_x%beg:m + offset_x%end))
allocate (z_cb_s(-1:m))
end if
end if
else
allocate (x_cc_s(-buff_size:m + buff_size))
end if

! Allocating the grid variables in the x-coordinate direction
allocate (x_cb(-1 - offset_x%beg:m + offset_x%end))
allocate (x_cb(-1:m))
allocate (x_cc(-buff_size:m + buff_size))
allocate (dx(-buff_size:m + buff_size))

! Allocating grid variables in the y- and z-coordinate directions
if (n > 0) then

allocate (y_cb(-1 - offset_y%beg:n + offset_y%end))
allocate (y_cb(-1:n))
allocate (y_cc(-buff_size:n + buff_size))
allocate (dy(-buff_size:n + buff_size))

if (p > 0) then
allocate (z_cb(-1 - offset_z%beg:p + offset_z%end))
allocate (z_cb(-1:p))
allocate (z_cc(-buff_size:p + buff_size))
allocate (dz(-buff_size:p + buff_size))
end if
Expand Down
30 changes: 4 additions & 26 deletions src/pre_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -797,32 +797,10 @@ contains
chemxb = species_idx%beg
chemxe = species_idx%end

! Determining the number of cells that are needed in order to store
! sufficient boundary conditions data as to iterate the solution in
! the physical computational domain from one time-step iteration to
! the next one
if (viscous) then
buff_size = 2*weno_polyn + 2
else
buff_size = weno_polyn + 2
end if

! Correction for smearing function in the lagrangian subgrid bubble model
if (bubbles_lagrange) then
buff_size = max(buff_size, 6)
end if

! Configuring Coordinate Direction Indexes
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p

idwbuff(1)%beg = -buff_size
if (num_dims > 1) then; idwbuff(2)%beg = -buff_size; else; idwbuff(2)%beg = 0; end if
if (num_dims > 2) then; idwbuff(3)%beg = -buff_size; else; idwbuff(3)%beg = 0; end if

idwbuff(1)%end = idwint(1)%end - idwbuff(1)%beg
idwbuff(2)%end = idwint(2)%end - idwbuff(2)%beg
idwbuff(3)%end = idwint(3)%end - idwbuff(3)%beg
call s_configure_coordinate_bounds(weno_polyn, buff_size, &
idwint, idwbuff, viscous, &
bubbles_lagrange, m, n, p, &
num_dims)

#ifdef MFC_MPI

Expand Down
30 changes: 4 additions & 26 deletions src/simulation/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1093,41 +1093,19 @@ contains
Np = 0
!$acc update device(Re_size)
! Determining the number of cells that are needed in order to store
! sufficient boundary conditions data as to iterate the solution in
! the physical computational domain from one time-step iteration to
! the next one
if (viscous) then
buff_size = 2*weno_polyn + 2
else
buff_size = weno_polyn + 2
end if
if (elasticity) then
fd_number = max(1, fd_order/2)
!buff_size = buff_size + fd_number
end if
if (probe_wrt) then
fd_number = max(1, fd_order/2)
end if
! Correction for smearing function in the lagrangian subgrid bubble model
if (bubbles_lagrange) then
buff_size = max(buff_size, 6)
end if
! Configuring Coordinate Direction Indexes
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p
idwbuff(1)%beg = -buff_size
if (num_dims > 1) then; idwbuff(2)%beg = -buff_size; else; idwbuff(2)%beg = 0; end if
if (num_dims > 2) then; idwbuff(3)%beg = -buff_size; else; idwbuff(3)%beg = 0; end if
idwbuff(1)%end = idwint(1)%end - idwbuff(1)%beg
idwbuff(2)%end = idwint(2)%end - idwbuff(2)%beg
idwbuff(3)%end = idwint(3)%end - idwbuff(3)%beg
call s_configure_coordinate_bounds(weno_polyn, buff_size, &
idwint, idwbuff, viscous, &
bubbles_lagrange, m, n, p, &
num_dims)
!$acc update device(idwint, idwbuff)
! Configuring Coordinate Direction Indexes
Expand Down

0 comments on commit 637c765

Please sign in to comment.