Skip to content

Commit 50799ab

Browse files
Added some inverse rotation calculations to the square case
1 parent ac0013d commit 50799ab

File tree

4 files changed

+42
-30
lines changed

4 files changed

+42
-30
lines changed

src/common/m_derived_types.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ module m_derived_types
295295

296296
real(wp), dimension(1:3) :: angles
297297
real(wp), dimension(1:3) :: step_angles
298-
real(wp), dimension(3:3) :: rotaiton_matrix !< matrix that converts from IB reference frame to fluid reference frame
298+
real(wp), dimension(1:3, 1:3) :: rotation_matrix !< matrix that converts from IB reference frame to fluid reference frame
299299

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

src/common/m_ib_patches.fpp

Lines changed: 14 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -512,6 +512,8 @@ contains
512512

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

516518
pi_inf = fluid_pp(1)%pi_inf
517519
gamma = fluid_pp(1)%gamma
@@ -522,13 +524,14 @@ contains
522524
y_centroid = patch_ib(patch_id)%y_centroid
523525
length_x = patch_ib(patch_id)%length_x
524526
length_y = patch_ib(patch_id)%length_y
527+
inverse_rotation(:, :) = patch_ib(patch_id)%rotation_matrix_inverse(:, :)
525528
526529
! Computing the beginning and the end x- and y-coordinates of the
527530
! rectangle based on its centroid and lengths
528-
x_boundary%beg = x_centroid - 0.5_wp*length_x
529-
x_boundary%end = x_centroid + 0.5_wp*length_x
530-
y_boundary%beg = y_centroid - 0.5_wp*length_y
531-
y_boundary%end = y_centroid + 0.5_wp*length_y
531+
x_boundary%beg = -0.5_wp*length_x
532+
x_boundary%end = 0.5_wp*length_x
533+
y_boundary%beg = -0.5_wp*length_y
534+
y_boundary%end = 0.5_wp*length_y
532535
533536
! Since the rectangular patch does not allow for its boundaries to
534537
! be smoothed out, the pseudo volume fraction is set to 1 to ensure
@@ -542,10 +545,13 @@ contains
542545
! variables of the current patch are assigned to this cell.
543546
do j = 0, n
544547
do i = 0, m
545-
if (x_boundary%beg <= x_cc(i) .and. &
546-
x_boundary%end >= x_cc(i) .and. &
547-
y_boundary%beg <= y_cc(j) .and. &
548-
y_boundary%end >= y_cc(j)) then
548+
! get the x and y coodinates in the local IB frame
549+
xy_local = [x_cc(i) - x_centroid, y_cc(j) - y_centroid]
550+
xy_local = matmul(inverse_rotation, xy_local)
551+
if (x_boundary%beg <= xy_local(1) .and. &
552+
x_boundary%end >= xy_local(1) .and. &
553+
y_boundary%beg <= xy_local(2) .and. &
554+
y_boundary%end >= xy_local(2)) then
549555
550556
! Updating the patch identities bookkeeping variable
551557
ib_markers_sf(i, j, 0) = patch_id

src/pre_process/m_global_parameters.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -546,7 +546,7 @@ contains
546546
patch_ib(i)%angular_vel(:) = 0._wp
547547

548548
! sets values of a rotation matrix which can be used when calculating rotaitons
549-
patch_ib(i)%rotation_matrix(:) = 0._wp
549+
patch_ib(i)%rotation_matrix = 0._wp
550550
patch_ib(i)%rotation_matrix(1, 1) = 1._wp
551551
patch_ib(i)%rotation_matrix(2, 2) = 1._wp
552552
patch_ib(i)%rotation_matrix(3, 3) = 1._wp

src/simulation/m_ibm.fpp

Lines changed: 26 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,9 @@ contains
9494
do i = 1, num_ibs
9595
if (patch_ib(i)%moving_ibm /= 0) then
9696
moving_immersed_boundary_flag = .true.
97-
exit
97+
9898
end if
99+
call s_update_ib_rotation_matrix(i)
99100
end do
100101

101102
! Allocating the patch identities bookkeeping variable
@@ -149,7 +150,7 @@ contains
149150
!! @param q_prim_vf Primitive variables
150151
!! @param pb Internal bubble pressure
151152
!! @param mv Mass of vapor in bubble
152-
pure subroutine s_ibm_correct_state(q_cons_vf, q_prim_vf, pb_in, mv_in)
153+
subroutine s_ibm_correct_state(q_cons_vf, q_prim_vf, pb_in, mv_in)
153154

154155
type(scalar_field), &
155156
dimension(sys_size), &
@@ -267,13 +268,15 @@ contains
267268
! we know the object is not moving if moving_ibm is 0 (false)
268269
vel_g = 0._wp
269270
else
270-
radial_vector = physical_loc - (patch_ib(patch_id)%x_centroid, &
271-
patch_ib(patch_id)%y_centroid, patch_ib(patch_id)%z_centroid)
272-
rotational_velocity = cross_product(matmul(patch_ib(patch_id)%rotation_matrix, patch_ib(patch_id)%angular_vel), radial_vector)
271+
! get the vector that points from the centroid to the ghost
272+
radial_vector = physical_loc - [patch_ib(patch_id)%x_centroid, &
273+
patch_ib(patch_id)%y_centroid, patch_ib(patch_id)%z_centroid]
274+
! convert the angular velcoity from the inertial reference frame to the fluids frame, then convert to linear velocity
275+
rotation_velocity = cross_product(matmul(patch_ib(patch_id)%rotation_matrix, patch_ib(patch_id)%angular_vel), radial_vector)
273276
do q = 1, 3
274277
! if mibm is 1 or 2, then the boundary may be moving
275278
vel_g(q) = patch_ib(patch_id)%vel(q) ! add the linear velocity
276-
vel_g(q) = vel_g(q) + rotational_velocity(q) ! add the rotational velocity
279+
vel_g(q) = vel_g(q) + rotation_velocity(q) ! add the rotational velocity
277280
end do
278281
end if
279282
end if
@@ -902,8 +905,8 @@ contains
902905

903906
end subroutine s_interpolate_image_point
904907

905-
!> Subroutine the updates the moving imersed boundary positions via Euler's method
906-
impure subroutine s_update_mib_rotation_matrix(patch_id)
908+
!> Subroutine that computes a rotation matrix for converting to the rotating frame of the boundary
909+
impure subroutine s_update_ib_rotation_matrix(patch_id)
907910

908911
integer, intent(in) :: patch_id
909912
integer :: i
@@ -915,33 +918,36 @@ contains
915918
if (num_dims == 3) then
916919
! also compute the x and y axes in 3D
917920
angle = patch_ib(patch_id)%angles(1)
918-
rotation(1, 1, :) = (1._wp, 0._wp , 0._wp )
919-
rotation(1, 2, :) = (0._wp, cos(angle), -sin(angle))
920-
rotation(1, 3, :) = (0._wp, sin(angle), cos(angle) )
921+
rotation(1, 1, :) = [1._wp, 0._wp , 0._wp ]
922+
rotation(1, 2, :) = [0._wp, cos(angle), -sin(angle)]
923+
rotation(1, 3, :) = [0._wp, sin(angle), cos(angle) ]
921924

922925
angle = patch_ib(patch_id)%angles(2)
923-
rotation(2, 1, :) = (cos(angle) , 0._wp, sin(angle))
924-
rotation(2, 2, :) = (0._wp , 1._wp, 0._wp )
925-
rotation(2, 3, :) = (-sin(angle), 0._wp, cos(angle))
926+
rotation(2, 1, :) = [cos(angle) , 0._wp, sin(angle)]
927+
rotation(2, 2, :) = [0._wp , 1._wp, 0._wp ]
928+
rotation(2, 3, :) = [-sin(angle), 0._wp, cos(angle)]
926929

927930
! apply the y rotation to the x rotation
928-
rotation(1, :, :) = matmul(rotation(1, :, :), rotation(2, :, :))
931+
patch_ib(patch_id)%rotation_matrix(:, :) = matmul(rotation(1, :, :), rotation(2, :, :))
932+
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = matmul(tranpose(rotation(2, :, :)), transpose(rotation(1, :, :)))
929933
end if
930934
! z component first, since it applies in 2D and 3D
931935
angle = patch_ib(patch_id)%angles(3)
932-
rotation(3, 1, :) = (cos(angle), -sin(angle), 0._wp)
933-
rotation(3, 2, :) = (sin(angle), cos(angle) , 0._wp)
934-
rotation(3, 3, :) = (0._wp , 0._wp , 1._wp)
936+
rotation(3, 1, :) = [cos(angle), -sin(angle), 0._wp]
937+
rotation(3, 2, :) = [sin(angle), cos(angle) , 0._wp]
938+
rotation(3, 3, :) = [0._wp , 0._wp , 1._wp]
935939

936940
if (num_dims == 3) then
937941
! apply the z rotation to the xy rotation in 3D
938-
patch_ib(patch_id)%rotation_matrix(:, :) = matmul(rotation(1, :, :), rotation(3, :, :))
942+
patch_ib(patch_id)%rotation_matrix(:, :) = matmul(patch_ib(patch_id)%rotation_matrix(:, :), rotation(3, :, :))
943+
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = matmul(transpose(rotation(3, :, :)), patch_ib(patch_id)%rotation_matrix_inverse(:, :))
939944
else
940945
! write out only the z rotation in 2D
941946
patch_ib(patch_id)%rotation_matrix(:, :) = rotation(3, :, :)
947+
patch_ib(patch_id)%rotation_matrix_inverse(:, :) = transpose(rotation(3, :, :))
942948
end if
943949

944-
end subroutine s_update_mib_rotation_matrix
950+
end subroutine s_update_ib_rotation_matrix
945951

946952
!> Resets the current indexes of immersed boundaries and replaces them after updating
947953
!> the position of each moving immersed boundary

0 commit comments

Comments
 (0)