Skip to content
Merged
Show file tree
Hide file tree
Changes from 11 commits
Commits
Show all changes
49 commits
Select commit Hold shift + click to select a range
d953d5b
Pushing from local
danieljvickers Sep 15, 2025
9f6af97
Succesfully added RK time stepping
danieljvickers Oct 2, 2025
8d3941d
Finalizing time-step module
danieljvickers Oct 2, 2025
734b649
Addded handlers for new case file parameters
danieljvickers Oct 2, 2025
e1c3b3f
added hooks for a rotation matrix
danieljvickers Oct 2, 2025
effd324
Added the rotation matrix calculation, which will be needed for ident…
danieljvickers Oct 2, 2025
ac0013d
Finished adding velocity update, but now I need to fix compiler errors
danieljvickers Oct 2, 2025
50799ab
Added some inverse rotation calculations to the square case
danieljvickers Oct 7, 2025
c04cfae
Ready to test with a rotated square
danieljvickers Oct 7, 2025
e80952b
Ran test case and everything appears to be working
danieljvickers Oct 7, 2025
6ddc795
Spelling and formatting run
danieljvickers Oct 7, 2025
ce5f071
Fixed single-precision building
danieljvickers Oct 7, 2025
007949d
Updated patch_IB rotation values
danieljvickers Oct 8, 2025
ddfcd0f
Updated 2D airfoil
danieljvickers Oct 8, 2025
0cabfff
Finished adding support for existing IB geometries. They will all now…
danieljvickers Oct 8, 2025
372ddf0
Fixed compiler issue with airfoil changes. All tests pass locally
danieljvickers Oct 8, 2025
603b42f
Updated rectangle levelset
danieljvickers Oct 8, 2025
ab29c8a
Swapped out Id values
danieljvickers Oct 8, 2025
71437fd
Modified the cuboid levelset to use local coords
danieljvickers Oct 8, 2025
fcccef7
Final levelset calculation updated
danieljvickers Oct 8, 2025
d13de48
Fixed compiling errors'
danieljvickers Oct 8, 2025
91e0f50
Temporary fix for issue involving cuboid normal vector selection. Com…
danieljvickers Oct 8, 2025
42e1177
Fixed airfoil shape, but it is not rotating yet
danieljvickers Oct 9, 2025
367bea6
I am dumb. Do not look at this commit. It has nothing for you.
danieljvickers Oct 9, 2025
24b25ec
Need to generate new golden files for the locations of the airfoil ar…
danieljvickers Oct 9, 2025
c6c55b7
Updated the golden files for this test case after realizing that ther…
danieljvickers Oct 9, 2025
c7c8d8a
Formatting and spelling
danieljvickers Oct 9, 2025
6b1ee94
Changes to the case file to support new rotational system
danieljvickers Oct 9, 2025
3208814
Resolved memory not being reset for rectangles and cuboids. Also fixe…
danieljvickers Oct 10, 2025
9dc62dd
Fixing macOS runners failing due to contera version difference
danieljvickers Oct 10, 2025
6febe45
Ran formatting
danieljvickers Oct 10, 2025
78fd281
Fixed issue with pre-processing not applying correct initial rotation…
danieljvickers Oct 10, 2025
7cf947e
Formatting
danieljvickers Oct 10, 2025
63c87c5
Adding OpenMP/OpenACC tags for vecturs used in paralel loop for GPU s…
danieljvickers Oct 10, 2025
1af3670
found an error in 3d Airfoil case that is unrelated to the frontier C…
danieljvickers Oct 12, 2025
5a60a7f
Merge branch 'master' into add-rotating-mibms
danieljvickers Oct 12, 2025
272ca02
Build with one task for testing
wilfonba Oct 13, 2025
8fc4902
.github
danieljvickers Oct 13, 2025
64fa336
Found my error. Thanks Ben for being a rubber ducky :)
danieljvickers Oct 13, 2025
29db19a
Integrated with new time stepper code
danieljvickers Oct 13, 2025
c29ec88
Resolved error. Ready to merge
danieljvickers Oct 13, 2025
604e1db
Merge branch 'add-rotating-mibms' of github.com:danieljvickers/MFC in…
danieljvickers Oct 13, 2025
cbfb2da
Formatting
danieljvickers Oct 13, 2025
7560a02
Added a tumbling rectangle case
danieljvickers Oct 15, 2025
8906927
Fixed GPU errors on NVHPC
danieljvickers Oct 16, 2025
d4a1280
Generated golden files for totating sphere
danieljvickers Oct 16, 2025
876f16a
Updated case file to be longer
danieljvickers Oct 16, 2025
f1b6fb7
Formatting
danieljvickers Oct 16, 2025
21d0594
Spelling
danieljvickers Oct 16, 2025
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
10 changes: 10 additions & 0 deletions src/common/m_derived_types.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -290,6 +290,13 @@ module m_derived_types
real(wp) :: x_centroid, y_centroid, z_centroid !<
!! Location of the geometric center, i.e. the centroid, of the patch. It
!! is specified through its x-, y- and z-coordinates, respectively.
real(wp) :: step_x_centroid, step_y_centroid, step_z_centroid !<
!! Centroid locations of intermediate steps in the time_stepper module

real(wp), dimension(1:3) :: angles
real(wp), dimension(1:3) :: step_angles
real(wp), dimension(1:3, 1:3) :: rotation_matrix !< matrix that converts from IB reference frame to fluid reference frame
real(wp), dimension(1:3, 1:3) :: rotation_matrix_inverse !< matrix that converts from fluid reference frame to IB reference frame

real(wp) :: c, p, t, m

Expand Down Expand Up @@ -322,6 +329,9 @@ module m_derived_types
!! Patch conditions for moving imersed boundaries
integer :: moving_ibm ! 0 for no moving, 1 for moving, 2 for moving on forced path
real(wp), dimension(1:3) :: vel
real(wp), dimension(1:3) :: step_vel ! velocity array used to store intermediate steps in the time_stepper module
real(wp), dimension(1:3) :: angular_vel
real(wp), dimension(1:3) :: step_angular_vel ! velocity array used to store intermediate steps in the time_stepper module

end type ib_patch_parameters

Expand Down
69 changes: 60 additions & 9 deletions src/common/m_ib_patches.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module m_ib_patches

implicit none

private; public :: s_apply_ib_patches
private; public :: s_apply_ib_patches, s_update_ib_rotation_matrix

real(wp) :: x_centroid, y_centroid, z_centroid
real(wp) :: length_x, length_y, length_z
Expand Down Expand Up @@ -512,6 +512,8 @@ contains

integer :: i, j, k !< generic loop iterators
real(wp) :: pi_inf, gamma, lit_gamma !< Equation of state parameters
real(wp), dimension(1:3) :: xy_local !< x and y coordinates in local IB frame
real(wp), dimension(1:3, 1:3) :: inverse_rotation

pi_inf = fluid_pp(1)%pi_inf
gamma = fluid_pp(1)%gamma
Expand All @@ -522,13 +524,14 @@ contains
y_centroid = patch_ib(patch_id)%y_centroid
length_x = patch_ib(patch_id)%length_x
length_y = patch_ib(patch_id)%length_y
inverse_rotation(:, :) = patch_ib(patch_id)%rotation_matrix_inverse(:, :)

! Computing the beginning and the end x- and y-coordinates of the
! rectangle based on its centroid and lengths
x_boundary%beg = x_centroid - 0.5_wp*length_x
x_boundary%end = x_centroid + 0.5_wp*length_x
y_boundary%beg = y_centroid - 0.5_wp*length_y
y_boundary%end = y_centroid + 0.5_wp*length_y
x_boundary%beg = -0.5_wp*length_x
x_boundary%end = 0.5_wp*length_x
y_boundary%beg = -0.5_wp*length_y
y_boundary%end = 0.5_wp*length_y

! Since the rectangular patch does not allow for its boundaries to
! be smoothed out, the pseudo volume fraction is set to 1 to ensure
Expand All @@ -542,10 +545,13 @@ contains
! variables of the current patch are assigned to this cell.
do j = 0, n
do i = 0, m
if (x_boundary%beg <= x_cc(i) .and. &
x_boundary%end >= x_cc(i) .and. &
y_boundary%beg <= y_cc(j) .and. &
y_boundary%end >= y_cc(j)) then
! get the x and y coordinates in the local IB frame
xy_local = [x_cc(i) - x_centroid, y_cc(j) - y_centroid, 0._wp]
xy_local = matmul(inverse_rotation, xy_local)
if (x_boundary%beg <= xy_local(1) .and. &
x_boundary%end >= xy_local(1) .and. &
y_boundary%beg <= xy_local(2) .and. &
y_boundary%end >= xy_local(2)) then

! Updating the patch identities bookkeeping variable
ib_markers_sf(i, j, 0) = patch_id
Expand Down Expand Up @@ -987,6 +993,51 @@ contains

end subroutine s_ib_model

!> Subroutine that computes a rotation matrix for converting to the rotating frame of the boundary
subroutine s_update_ib_rotation_matrix(patch_id)

integer, intent(in) :: patch_id
integer :: i

real(wp), dimension(3, 3, 3) :: rotation
real(wp) :: angle

! construct the x, y, and z rotation matrices
if (num_dims == 3) then
! also compute the x and y axes in 3D
angle = patch_ib(patch_id)%angles(1)
rotation(1, 1, :) = [1._wp, 0._wp, 0._wp]
rotation(1, 2, :) = [0._wp, cos(angle), -sin(angle)]
rotation(1, 3, :) = [0._wp, sin(angle), cos(angle)]

angle = patch_ib(patch_id)%angles(2)
rotation(2, 1, :) = [cos(angle), 0._wp, sin(angle)]
rotation(2, 2, :) = [0._wp, 1._wp, 0._wp]
rotation(2, 3, :) = [-sin(angle), 0._wp, cos(angle)]

! apply the y rotation to the x rotation
patch_ib(patch_id)%rotation_matrix(:, :) = matmul(rotation(1, :, :), rotation(2, :, :))
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = matmul(transpose(rotation(2, :, :)), transpose(rotation(1, :, :)))
end if

! z component first, since it applies in 2D and 3D
angle = patch_ib(patch_id)%angles(3)
rotation(3, 1, :) = [cos(angle), -sin(angle), 0._wp]
rotation(3, 2, :) = [sin(angle), cos(angle), 0._wp]
rotation(3, 3, :) = [0._wp, 0._wp, 1._wp]

if (num_dims == 3) then
! apply the z rotation to the xy rotation in 3D
patch_ib(patch_id)%rotation_matrix(:, :) = matmul(patch_ib(patch_id)%rotation_matrix(:, :), rotation(3, :, :))
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = matmul(transpose(rotation(3, :, :)), patch_ib(patch_id)%rotation_matrix_inverse(:, :))
else
! write out only the z rotation in 2D
patch_ib(patch_id)%rotation_matrix(:, :) = rotation(3, :, :)
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = transpose(rotation(3, :, :))
end if

end subroutine s_update_ib_rotation_matrix

subroutine s_convert_cylindrical_to_cartesian_coord(cyl_y, cyl_z)
$:GPU_ROUTINE(parallelism='[seq]')

Expand Down
13 changes: 10 additions & 3 deletions src/pre_process/m_global_parameters.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -541,9 +541,16 @@ contains

! Variables to handle moving imersed boundaries, defaulting to no movement
patch_ib(i)%moving_ibm = 0
patch_ib(i)%vel(1) = 0._wp
patch_ib(i)%vel(2) = 0._wp
patch_ib(i)%vel(3) = 0._wp
patch_ib(i)%vel(:) = 0._wp
patch_ib(i)%angles(:) = 0._wp
patch_ib(i)%angular_vel(:) = 0._wp

! sets values of a rotation matrix which can be used when calculating rotations
patch_ib(i)%rotation_matrix = 0._wp
patch_ib(i)%rotation_matrix(1, 1) = 1._wp
patch_ib(i)%rotation_matrix(2, 2) = 1._wp
patch_ib(i)%rotation_matrix(3, 3) = 1._wp
patch_ib(i)%rotation_matrix_inverse = patch_ib(i)%rotation_matrix
end do

! Fluids physical parameters
Expand Down
5 changes: 5 additions & 0 deletions src/pre_process/m_initial_condition.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -180,6 +180,8 @@ contains
!! primitive variables are converted to conservative ones.
impure subroutine s_generate_initial_condition

integer :: i

! Converting the conservative variables to the primitive ones given
! preexisting initial condition data files were read in on start-up
if (old_ic) then
Expand All @@ -190,6 +192,9 @@ contains
end if

if (ib) then
do i = 1, num_ibs
! call s_update_ib_rotation_matrix(i)
end do
call s_apply_ib_patches(ib_markers%sf, levelset, levelset_norm)
end if
call s_apply_icpp_patches(patch_id_fp, q_prim_vf)
Expand Down
54 changes: 26 additions & 28 deletions src/simulation/m_ibm.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -94,8 +94,9 @@ contains
do i = 1, num_ibs
if (patch_ib(i)%moving_ibm /= 0) then
moving_immersed_boundary_flag = .true.
exit

end if
call s_update_ib_rotation_matrix(i)
end do

! Allocating the patch identities bookkeeping variable
Expand All @@ -116,8 +117,8 @@ contains
call s_mpi_allreduce_integer_sum(num_inner_gps, max_num_inner_gps)

$:GPU_UPDATE(device='[num_gps, num_inner_gps]')
@:ALLOCATE(ghost_points(1:int(max_num_gps * 1.2)))
@:ALLOCATE(inner_points(1:int(max_num_inner_gps * 1.2)))
@:ALLOCATE(ghost_points(1:int(max_num_gps * 1.5)))
@:ALLOCATE(inner_points(1:int(max_num_inner_gps * 1.5)))

$:GPU_ENTER_DATA(copyin='[ghost_points,inner_points]')

Expand Down Expand Up @@ -149,7 +150,7 @@ contains
!! @param q_prim_vf Primitive variables
!! @param pb Internal bubble pressure
!! @param mv Mass of vapor in bubble
pure subroutine s_ibm_correct_state(q_cons_vf, q_prim_vf, pb_in, mv_in)
subroutine s_ibm_correct_state(q_cons_vf, q_prim_vf, pb_in, mv_in)

type(scalar_field), &
dimension(sys_size), &
Expand Down Expand Up @@ -182,6 +183,8 @@ contains
real(wp), dimension(3) :: norm !< Normal vector from GP to IP
real(wp), dimension(3) :: physical_loc !< Physical loc of GP
real(wp), dimension(3) :: vel_g !< Velocity of GP
real(wp), dimension(3) :: radial_vector !< vector from centroid to ghost point
real(wp), dimension(3) :: rotation_velocity !< speed of the ghost point due to rotation

real(wp) :: nbub
real(wp) :: buf
Expand Down Expand Up @@ -265,9 +268,15 @@ contains
! we know the object is not moving if moving_ibm is 0 (false)
vel_g = 0._wp
else
! get the vector that points from the centroid to the ghost
radial_vector = physical_loc - [patch_ib(patch_id)%x_centroid, &
patch_ib(patch_id)%y_centroid, patch_ib(patch_id)%z_centroid]
! convert the angular velocity from the inertial reference frame to the fluids frame, then convert to linear velocity
rotation_velocity = cross_product(matmul(patch_ib(patch_id)%rotation_matrix, patch_ib(patch_id)%angular_vel), radial_vector)
do q = 1, 3
! if mibm is 1 or 2, then the boundary may be moving
vel_g(q) = patch_ib(patch_id)%vel(q)
vel_g(q) = patch_ib(patch_id)%vel(q) ! add the linear velocity
vel_g(q) = vel_g(q) + rotation_velocity(q) ! add the rotational velocity
end do
end if
end if
Expand Down Expand Up @@ -896,26 +905,6 @@ contains

end subroutine s_interpolate_image_point

!> Subroutine the updates the moving imersed boundary positions via Euler's method
impure subroutine s_propagate_mib(patch_id)

integer, intent(in) :: patch_id
integer :: i

! start by using euler's method naiively, but eventually incorporate more sophistocation
if (patch_ib(patch_id)%moving_ibm == 1) then
! this continues with euler's method, which is obviously not that great and we need to add acceleration
do i = 1, 3
patch_ib(patch_id)%vel(i) = patch_ib(patch_id)%vel(i) + 0.0*dt ! TODO :: ADD EXTERNAL FORCES HERE
end do

patch_ib(patch_id)%x_centroid = patch_ib(patch_id)%x_centroid + patch_ib(patch_id)%vel(1)*dt
patch_ib(patch_id)%y_centroid = patch_ib(patch_id)%y_centroid + patch_ib(patch_id)%vel(2)*dt
patch_ib(patch_id)%z_centroid = patch_ib(patch_id)%z_centroid + patch_ib(patch_id)%vel(3)*dt
end if

end subroutine s_propagate_mib

!> Resets the current indexes of immersed boundaries and replaces them after updating
!> the position of each moving immersed boundary
impure subroutine s_update_mib(num_ibs, levelset, levelset_norm)
Expand All @@ -929,10 +918,9 @@ contains
! Clears the existing immersed boundary indices
ib_markers%sf = 0

! recalulcate the rotation matrix based upon the new angles
do i = 1, num_ibs
if (patch_ib(i)%moving_ibm /= 0) then
call s_propagate_mib(i) ! TODO :: THIS IS DONE TERRIBLY WITH EULER METHOD
end if
if (patch_ib(i)%moving_ibm /= 0) call s_update_ib_rotation_matrix(i)
end do

! recompute the new ib_patch locations and broadcast them.
Expand Down Expand Up @@ -963,4 +951,14 @@ contains

end subroutine s_finalize_ibm_module

function cross_product(a, b) result(c)
implicit none
real(8), intent(in) :: a(3), b(3)
real(8) :: c(3)

c(1) = a(2)*b(3) - a(3)*b(2)
c(2) = a(3)*b(1) - a(1)*b(3)
c(3) = a(1)*b(2) - a(2)*b(1)
end function cross_product

end module m_ibm
4 changes: 0 additions & 4 deletions src/simulation/m_start_up.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -1135,10 +1135,6 @@ contains
end do
end if

if (moving_immersed_boundary_flag) then
call s_update_mib(num_ibs, levelset, levelset_norm)
end if

call s_compute_derived_variables(t_step)


Expand Down
Loading
Loading