Skip to content

Commit

Permalink
velocity BCs
Browse files Browse the repository at this point in the history
  • Loading branch information
wilfonba committed Feb 8, 2024
1 parent 2b5b65f commit 158fc26
Show file tree
Hide file tree
Showing 6 changed files with 42 additions and 16 deletions.
2 changes: 1 addition & 1 deletion src/pre_process/include/2dHardcodedIC.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@
q_prim_vf(contxe)%sf(i, j, 0) = alph*1d0

if (y_cc(j) > 0.0436) then
pInterface = 1d5 + 950**9.81*0.0439
pInterface = 1d5 + 950*9.81*0.0439
q_prim_vf(E_idx)%sf(i, j, 0) = pInterface + 1d0*9.81*(y_cc(j) - 0.0436)
else
q_prim_vf(E_idx)%sf(i, j, 0) = 1d5 + 950d0*9.81*(y_cc(j))
Expand Down
24 changes: 23 additions & 1 deletion src/pre_process/include/3dHardcodedIC.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@
real(kind(0d0)) :: minValX300, minValZ300
integer :: q300, p300

real(kind(0d0)) :: ih3, alph3
real(kind(0d0)) :: ih3, alph3, ih, alph, pInterface

Check warning on line 12 in src/pre_process/include/3dHardcodedIC.fpp

View workflow job for this annotation

GitHub Actions / Spell Check

"alph" should be "alpha".

Check warning on line 12 in src/pre_process/include/3dHardcodedIC.fpp

View workflow job for this annotation

GitHub Actions / Spell Check

"alph" should be "alpha".

integer :: i1, i2
real(kind(0d0)), dimension(0:199,0:199) :: ihPerlin
Expand Down Expand Up @@ -103,6 +103,28 @@
! 1000d0*9.8*(ih3 - y_cc(j))
! end if

case(3300) ! 3D Interface

ih = 0.00186 - 0.00186/40*(sin(2*pi/1.86d-3*z_cc(k) + pi/2) + sin((2*pi/1.86d-3)*x_cc(i)+pi/2))
alph = 5d-1*(1 + tanh((y_cc(j) - ih)/1d-16))

if (alph < 1e-6) alph = 1e-6
if (alph > 1 - 1e-6) alph = 1 - 1e-6

if (sigma .ne. dflt_real) q_prim_vf(c_idx)%sf(i, j, 0) = alph
q_prim_vf(advxb)%sf(i, j, k) = 1 - alph
q_prim_vf(advxe)%sf(i, j, k) = alph
q_prim_vf(contxb)%sf(i, j, k) = (1 - alph)*950d0
q_prim_vf(contxe)%sf(i, j, k) = alph*1d0

if (y_cc(j) > 0.00186) then
pInterface = 1d5 + 950*9.81*0.00186
q_prim_vf(E_idx)%sf(i, j, k) = pInterface + 1d0*9.81*(y_cc(j) - 0.00186)
else
q_prim_vf(E_idx)%sf(i, j, k) = 1d5 + 950d0*9.81*(y_cc(j))
end if


case default
call s_int_to_str(patch_id, iStr)
call s_mpi_abort("Invalid hcid specified for patch " // trim(iStr))
Expand Down
24 changes: 13 additions & 11 deletions src/simulation/m_boundary_conditions.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -25,11 +25,12 @@ contains
!> The purpose of this procedure is to populate the buffers
!! of the conservative variables, depending on the selected
!! boundary conditions.
subroutine s_populate_primitive_variables_buffers(q_prim_vf, pb, mv)
subroutine s_populate_primitive_variables_buffers(q_prim_vf, pb, mv, mytime)

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

! Population of Buffers in x-direction =============================

Expand All @@ -43,7 +44,7 @@ contains
case (-15) ! Slip wall BC at beginning
call s_slip_wall(q_prim_vf, pb, mv, 1, -1)
case (-16) ! No-slip wall BC at beginning
call s_no_slip_wall(q_prim_vf, pb, mv, 1, -1)
call s_no_slip_wall(q_prim_vf, pb, mv, 1, -1, mytime)
case default ! Processor BC at beginning
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 1, -1)
Expand All @@ -59,7 +60,7 @@ contains
case (-15) ! Slip wall BC at end
call s_slip_wall(q_prim_vf, pb, mv, 1, 1)
case (-16) ! No-slip wall bc at end
call s_no_slip_wall(q_prim_vf, pb, mv, 1, 1)
call s_no_slip_wall(q_prim_vf, pb, mv, 1, 1, mytime)
case default ! Processor BC at end
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 1, 1)
Expand Down Expand Up @@ -103,7 +104,7 @@ contains
case (-15) ! Slip wall BC at beginning
call s_slip_wall(q_prim_vf, pb, mv, 2, -1)
case (-16) ! No-slip wall BC at beginning
call s_no_slip_wall(q_prim_vf, pb, mv, 2, -1)
call s_no_slip_wall(q_prim_vf, pb, mv, 2, -1, mytime)
case default ! Processor BC at beginning
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 2, -1)
Expand All @@ -119,7 +120,7 @@ contains
case (-15) ! Slip wall BC at end
call s_slip_wall(q_prim_vf, pb, mv, 2, 1)
case (-16) ! No-slip wall BC at end
call s_no_slip_wall(q_prim_vf, pb, mv, 2, 1)
call s_no_slip_wall(q_prim_vf, pb, mv, 2, 1, mytime)
case default ! Processor BC at end
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 2, 1)
Expand Down Expand Up @@ -163,7 +164,7 @@ contains
case (-15) ! Slip wall BC at beginning
call s_slip_wall(q_prim_vf, pb, mv, 3, -1)
case (-16) ! No-slip wall BC at beginning
call s_no_slip_wall(q_prim_vf, pb, mv, 3, -1)
call s_no_slip_wall(q_prim_vf, pb, mv, 3, -1, mytime)
case default ! Processor BC at beginning
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 3, -1)
Expand All @@ -179,7 +180,7 @@ contains
case (-15) ! Slip wall BC at end
call s_slip_wall(q_prim_vf, pb, mv, 3, 1)
case (-16) ! No-slip wall BC at end
call s_no_slip_wall(q_prim_vf, pb, mv, 3, 1)
call s_no_slip_wall(q_prim_vf, pb, mv, 3, 1, mytime)
case default ! Processor BC at end
call s_mpi_sendrecv_conservative_variables_buffers( &
q_prim_vf, pb, mv, 3, 1)
Expand Down Expand Up @@ -1035,12 +1036,13 @@ contains

end subroutine s_slip_wall

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

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
integer :: j, k, l, q, i
real(kind(0d0)) :: t

!< x-direction =========================================================
if (bc_dir == 1) then
Expand Down Expand Up @@ -1101,7 +1103,7 @@ contains
elseif (bc_dir == 2) then

if (bc_loc == -1) then !< bc_y%beg

!$acc parallel loop collapse(4) gang vector default(present)
do i = 1, sys_size
do k = 0, p
Expand All @@ -1112,7 +1114,7 @@ contains
-q_prim_vf(i)%sf(l, j - 1, k) + 2d0*bc_y%vb1
elseif (i == momxb + 1 .and. num_dims > 1) then
q_prim_vf(i)%sf(l, -j, k) = &
-q_prim_vf(i)%sf(l, j - 1, k) + 2d0*bc_y%vb2
-q_prim_vf(i)%sf(l, j - 1, k) + 2d0*(0.5*sin(600*pi*t))
elseif (i == momxb + 2 .and. num_dims > 2) then
q_prim_vf(i)%sf(l, -j, k) = &
-q_prim_vf(i)%sf(l, j - 1, k) + 2d0*bc_y%vb3
Expand All @@ -1136,7 +1138,7 @@ contains
-q_prim_vf(i)%sf(l, n - (j - 1), k) + 2d0*bc_y%ve1
elseif (i == momxb + 1 .and. num_dims > 1) then
q_prim_vf(i)%sf(l, n + j, k) = &
-q_prim_vf(i)%sf(l, n - (j - 1), k) + 2d0*bc_y%ve2
-q_prim_vf(i)%sf(l, n - (j - 1), k) + 2d0*(0.5*sin(600*pi*t))
elseif (i == momxb + 2 .and. num_dims > 2) then
q_prim_vf(i)%sf(l, n + j, k) = &
-q_prim_vf(i)%sf(l, n - (j - 1), k) + 2d0*bc_y%ve3
Expand Down
3 changes: 2 additions & 1 deletion src/simulation/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -375,7 +375,8 @@ module m_global_parameters

real(kind(0d0)) :: mytime !< Current simulation time
real(kind(0d0)) :: finaltime !< Final simulation time

!$acc declare create(mytime)

logical :: weno_flat, riemann_flat, cu_mpi

type(pres_field), allocatable, dimension(:) :: pb_ts
Expand Down
4 changes: 2 additions & 2 deletions src/simulation/m_rhs.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -664,7 +664,7 @@ contains
real(kind(0d0)) :: myR, myV, alf, myP, myRho, R2Vav
integer :: ndirs

real(kind(0d0)) :: mytime, sound
real(kind(0d0)) :: sound
real(kind(0d0)) :: start, finish
real(kind(0d0)) :: s2, const_sos, s1

Expand Down Expand Up @@ -727,7 +727,7 @@ contains
call nvtxEndRange

call nvtxStartRange("RHS-MPI")
call s_populate_primitive_variables_buffers(q_prim_qp%vf, pb, mv)
call s_populate_primitive_variables_buffers(q_prim_qp%vf, pb, mv, mytime)
call nvtxEndRange

if (t_step == t_step_stop) return
Expand Down
1 change: 1 addition & 0 deletions src/simulation/m_start_up.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1091,6 +1091,7 @@ contains
t_step
end if
mytime = mytime + dt
!$acc update device(mytime)

if (probe_wrt) then
do i = 1, sys_size
Expand Down

0 comments on commit 158fc26

Please sign in to comment.