Skip to content

Commit

Permalink
Simulation, Added Intent, and Formatting (#487)
Browse files Browse the repository at this point in the history
  • Loading branch information
okBrian authored Jun 24, 2024
1 parent fc85a76 commit 2a2d3d1
Show file tree
Hide file tree
Showing 22 changed files with 471 additions and 467 deletions.
24 changes: 14 additions & 10 deletions src/simulation/m_body_forces.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,10 @@ module m_body_forces

implicit none

private; public :: s_compute_body_forces_rhs, &
s_initialize_body_forces_module, &
s_finalize_body_forces_module
private;
public :: s_compute_body_forces_rhs, &
s_initialize_body_forces_module, &
s_finalize_body_forces_module

#ifdef CRAY_ACC_WAR
@:CRAY_DECLARE_GLOBAL(real(kind(0d0)), dimension(:, :, :), rhoM)
Expand All @@ -35,7 +36,7 @@ contains

!> This subroutine inializes the module global array of mixture
!! densities in each grid cell
subroutine s_initialize_body_forces_module()
subroutine s_initialize_body_forces_module

! Simulation is at least 2D
if (n > 0) then
Expand All @@ -62,7 +63,7 @@ contains
!> This subroutine computes the acceleration at time t
subroutine s_compute_acceleration(t)

real(kind(0d0)) :: t
real(kind(0d0)), intent(in) :: t

if (m > 0) then
accel_bf(1) = g_x + k_x*sin(w_x*t - p_x)
Expand All @@ -80,9 +81,10 @@ contains

!> This subroutine calculates the mixture density at each cell
!! center
!! param q_cons_vf Conservative variable
subroutine s_compute_mixture_density(q_cons_vf)

type(scalar_field), dimension(sys_size), intent(IN) :: q_cons_vf
type(scalar_field), dimension(sys_size), intent(in) :: q_cons_vf
integer :: i, j, k, l !< standard iterators

!$acc parallel loop collapse(3) gang vector default(present)
Expand All @@ -102,11 +104,13 @@ contains

!> This subroutine calculates the source term due to body forces
!! so the system can be advanced in time
!! @param q_cons_vf Conservative variables
!! @param q_prim_vf Primitive variables
subroutine s_compute_body_forces_rhs(q_cons_vf, q_prim_vf, rhs_vf)

type(scalar_field), dimension(sys_size), intent(IN) :: q_prim_vf
type(scalar_field), dimension(sys_size), intent(IN) :: q_cons_vf
type(scalar_field), dimension(sys_size), intent(INOUT) :: rhs_vf
type(scalar_field), dimension(sys_size), intent(in) :: q_prim_vf
type(scalar_field), dimension(sys_size), intent(in) :: q_cons_vf
type(scalar_field), dimension(sys_size), intent(inout) :: rhs_vf

integer :: i, j, k, l !< Loop variables

Expand Down Expand Up @@ -172,7 +176,7 @@ contains

end subroutine s_compute_body_forces_rhs

subroutine s_finalize_body_forces_module()
subroutine s_finalize_body_forces_module

@:DEALLOCATE_GLOBAL(rhoM)

Expand Down
61 changes: 35 additions & 26 deletions src/simulation/m_boundary_conditions.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -18,18 +18,21 @@ module m_boundary_conditions

implicit none

private; public :: s_populate_primitive_variables_buffers, &
s_populate_capillary_buffers
private;
public :: s_populate_primitive_variables_buffers, &
s_populate_capillary_buffers

contains

!> The purpose of this procedure is to populate the buffers
!! of the conservative variables, depending on the selected
!! of the primitive variables, depending on the selected
!! boundary conditions.
!! @param q_prim_vf Primitive variable
subroutine s_populate_primitive_variables_buffers(q_prim_vf, pb, mv)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv

integer :: bc_loc, bc_dir

! Population of Buffers in x-direction =============================
Expand Down Expand Up @@ -214,9 +217,9 @@ contains

subroutine s_ghost_cell_extrapolation(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc
integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -325,9 +328,10 @@ contains

subroutine s_symmetry(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -606,9 +610,10 @@ contains

subroutine s_periodic(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -825,9 +830,10 @@ contains

subroutine s_axis(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!$acc parallel loop collapse(3) gang vector default(present)
Expand Down Expand Up @@ -897,9 +903,10 @@ contains

subroutine s_slip_wall(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -1038,9 +1045,10 @@ contains

subroutine s_no_slip_wall(q_prim_vf, pb, mv, bc_dir, bc_loc)

type(scalar_field), dimension(sys_size) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -1215,8 +1223,9 @@ contains

subroutine s_qbmm_extrapolation(pb, mv, bc_dir, bc_loc)

real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(INOUT) :: pb, mv
integer :: bc_dir, bc_loc
real(kind(0d0)), dimension(startx:, starty:, startz:, 1:, 1:), intent(inout) :: pb, mv
integer, intent(in) :: bc_dir, bc_loc

integer :: j, k, l, q, i

!< x-direction =========================================================
Expand Down Expand Up @@ -1348,7 +1357,7 @@ contains

subroutine s_populate_capillary_buffers(c_divs)

type(scalar_field), dimension(num_dims + 1) :: c_divs
type(scalar_field), dimension(num_dims + 1), intent(inout) :: c_divs
integer :: i, j, k, l

! x - direction
Expand Down
Loading

0 comments on commit 2a2d3d1

Please sign in to comment.