@@ -26,6 +26,15 @@ module m_bubbles
2626 real (kind (0.d0 )) :: rho_mw !< Bubble wall properties (Ando 2010 )
2727 !$acc declare create(chi_vw, k_mw, rho_mw)
2828
29+ !> @name Bubble dynamic source terms
30+ !> @{
31+ real (kind (0d0 )), allocatable, dimension (:, :, :) :: bub_adv_src
32+ real (kind (0d0 )), allocatable, dimension (:, :, :, :) :: bub_r_src, bub_v_src, bub_p_src, bub_m_src
33+ !$acc declare create(bub_adv_src, bub_r_src, bub_v_src, bub_p_src, bub_m_src)
34+
35+ type(scalar_field) :: divu !< matrix for div(u)
36+ !$acc declare create(divu)
37+
2938 integer , allocatable, dimension (:) :: rs, vs, ms, ps
3039 !$acc declare create(rs, vs, ms, ps)
3140
@@ -34,6 +43,15 @@ contains
3443 subroutine s_initialize_bubbles_module ()
3544
3645 integer :: i, j, k, l, q
46+ type(int_bounds_info) :: ix, iy, iz
47+
48+ ! Configuring Coordinate Direction Indexes =========================
49+ ix%beg = - buff_size; iy%beg = 0 ; iz%beg = 0
50+
51+ if (n > 0 ) iy%beg = - buff_size; if (p > 0 ) iz%beg = - buff_size
52+
53+ ix%end = m - ix%beg; iy%end = n - iy%beg; iz%end = p - iz%beg
54+ ! ==================================================================
3755
3856 @:ALLOCATE(rs(1 :nb))
3957 @:ALLOCATE(vs(1 :nb))
@@ -56,6 +74,69 @@ contains
5674 !$acc update device(ps, ms)
5775 end if
5876
77+ @:ALLOCATE(divu%sf(ix%beg:ix%end, iy%beg:iy%end, iz%beg:iz%end))
78+
79+ @:ALLOCATE(bub_adv_src(0 :m, 0 :n, 0 :p))
80+ @:ALLOCATE(bub_r_src(0 :m, 0 :n, 0 :p, 1 :nb))
81+ @:ALLOCATE(bub_v_src(0 :m, 0 :n, 0 :p, 1 :nb))
82+ @:ALLOCATE(bub_p_src(0 :m, 0 :n, 0 :p, 1 :nb))
83+ @:ALLOCATE(bub_m_src(0 :m, 0 :n, 0 :p, 1 :nb))
84+
85+ end subroutine
86+
87+ subroutine s_compute_bubbles_rhs (idir , q_prim_vf )
88+
89+ type(scalar_field), dimension (sys_size), intent (IN ) :: q_prim_vf
90+ integer :: idir
91+ integer :: i, j, k, l, q
92+
93+ if (idir == 1 ) then
94+
95+ if (.not. qbmm) then
96+ !$acc parallel loop collapse(3 ) gang vector default(present)
97+ do l = 0 , p
98+ do k = 0 , n
99+ do j = 0 , m
100+ divu%sf(j, k, l) = 0d0
101+ divu%sf(j, k, l) = &
102+ 5d-1 / dx(j)* (q_prim_vf(contxe + idir)%sf(j + 1 , k, l) - &
103+ q_prim_vf(contxe + idir)%sf(j - 1 , k, l))
104+
105+ end do
106+ end do
107+ end do
108+ end if
109+
110+ elseif (idir == 2 ) then
111+
112+ !$acc parallel loop collapse(3 ) gang vector default(present)
113+ do l = 0 , p
114+ do k = 0 , n
115+ do j = 0 , m
116+ divu%sf(j, k, l) = divu%sf(j, k, l) + &
117+ 5d-1 / dy(k)* (q_prim_vf(contxe + idir)%sf(j, k + 1 , l) - &
118+ q_prim_vf(contxe + idir)%sf(j, k - 1 , l))
119+
120+ end do
121+ end do
122+ end do
123+
124+ elseif (idir == 3 ) then
125+
126+ !$acc parallel loop collapse(3 ) gang vector default(present)
127+ do l = 0 , p
128+ do k = 0 , n
129+ do j = 0 , m
130+ divu%sf(j, k, l) = divu%sf(j, k, l) + &
131+ 5d-1 / dz(l)* (q_prim_vf(contxe + idir)%sf(j, k, l + 1 ) - &
132+ q_prim_vf(contxe + idir)%sf(j, k, l - 1 ))
133+
134+ end do
135+ end do
136+ end do
137+
138+ end if
139+
59140 end subroutine
60141
61142 !> The purpose of this procedure is to compute the source terms
@@ -68,21 +149,13 @@ contains
68149 !! @param bub_v_src Bubble velocity equation source
69150 !! @param bub_p_src Bubble pressure equation source
70151 !! @param bub_m_src Bubble mass equation source
71- subroutine s_compute_bubble_source (bub_adv_src , bub_r_src , bub_v_src , bub_p_src , bub_m_src , divu , nbub , &
72- q_cons_vf , q_prim_vf , t_step , id , rhs_vf )
152+ subroutine s_compute_bubble_source (nbub , q_cons_vf , q_prim_vf , t_step , id , rhs_vf )
73153
74154 type(scalar_field), dimension (sys_size), intent (IN ) :: q_prim_vf, q_cons_vf
75155 type(scalar_field), dimension (sys_size), intent (INOUT ) :: rhs_vf
76- type(scalar_field), intent (IN ) :: divu
77156 real (kind (0d0 )), dimension (0 :m, 0 :n, 0 :p), intent (INOUT ) :: nbub
78157 integer , intent (IN ) :: t_step, id
79158
80- real (kind (0d0 )), dimension (0 :m, 0 :n, 0 :p), intent (INOUT ) :: bub_adv_src
81- real (kind (0d0 )), dimension (0 :m, 0 :n, 0 :p, 1 :nb), intent (INOUT ) :: bub_r_src, &
82- bub_v_src, &
83- bub_p_src, &
84- bub_m_src
85-
86159 !< Bubble number density
87160
88161 real (kind (0d0 )) :: tmp1, tmp2, tmp3, tmp4, &
0 commit comments