Skip to content

Commit b2ad78a

Browse files
committed
Addressing more PR comments
1 parent e08bcae commit b2ad78a

File tree

4 files changed

+15
-12
lines changed

4 files changed

+15
-12
lines changed

src/simulation/m_bubbles_EE.fpp

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -170,6 +170,7 @@ contains
170170
real(wp) :: myR, myV, alf, myP, myRho, R2Vav, R3
171171
real(wp), dimension(num_fluids) :: myalpha, myalpha_rho
172172
real(wp) :: nbub !< Bubble number density
173+
real(wp) :: my_divu
173174

174175
integer :: i, j, k, l, q, ii !< Loop variables
175176

@@ -196,7 +197,7 @@ contains
196197
#:endcall GPU_PARALLEL_LOOP
197198

198199
adap_dt_stop_max = 0
199-
#:call GPU_PARALLEL_LOOP(collapse=3, private='[Rtmp, Vtmp, myalpha_rho, myalpha, myR, myV, alf, myP, myRho, R2Vav, R3, nbub, pb_local, mv_local, vflux, pbdot, rddot, n_tait, B_tait]', &
200+
#:call GPU_PARALLEL_LOOP(collapse=3, private='[Rtmp, Vtmp, myalpha_rho, myalpha, myR, myV, alf, myP, myRho, R2Vav, R3, nbub, pb_local, mv_local, vflux, pbdot, rddot, n_tait, B_tait, my_divu]', &
200201
& reduction='[[adap_dt_stop_max]]', reductionOp='[MAX]', &
201202
& copy='[adap_dt_stop_max]')
202203
do l = 0, p
@@ -293,19 +294,21 @@ contains
293294

294295
if (adap_dt) then
295296

297+
my_divu = real(divu_in%sf(j, k, l), kind=wp)
296298
call s_advance_step(myRho, myP, myR, myV, R0(q), &
297299
pb_local, pbdot, alf, n_tait, B_tait, &
298-
bub_adv_src(j, k, l), real(divu_in%sf(j, k, l), kind=wp), &
300+
bub_adv_src(j, k, l), my_divu, &
299301
dmBub_id, dmMass_v, dmMass_n, dmBeta_c, &
300302
dmBeta_t, dmCson, adap_dt_stop)
301303

302304
q_cons_vf(rs(q))%sf(j, k, l) = nbub*myR
303305
q_cons_vf(vs(q))%sf(j, k, l) = nbub*myV
304306

305307
else
308+
my_divu = real(divu_in%sf(j, k, l), kind=wp)
306309
rddot = f_rddot(myRho, myP, myR, myV, R0(q), &
307310
pb_local, pbdot, alf, n_tait, B_tait, &
308-
bub_adv_src(j, k, l), real(divu_in%sf(j, k, l), kind=wp), &
311+
bub_adv_src(j, k, l), my_divu, &
309312
dmCson)
310313
bub_v_src(j, k, l, q) = nbub*rddot
311314
bub_r_src(j, k, l, q) = q_cons_vf(vs(q))%sf(j, k, l)

src/simulation/m_ibm.fpp

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -226,7 +226,7 @@ contains
226226
else if (qbmm .and. .not. polytropic) then
227227
call s_interpolate_image_point(q_prim_vf, gp, &
228228
alpha_rho_IP, alpha_IP, pres_IP, vel_IP, c_IP, &
229-
r_IP, v_IP, pb_IP, mv_IP, nmom_IP, real(pb_in, kind=wp), real(mv_in, kind=wp), presb_IP, massv_IP)
229+
r_IP, v_IP, pb_IP, mv_IP, nmom_IP, pb_in, mv_in, presb_IP, massv_IP)
230230
else
231231
call s_interpolate_image_point(q_prim_vf, gp, &
232232
alpha_rho_IP, alpha_IP, pres_IP, vel_IP, c_IP)
@@ -803,13 +803,15 @@ contains
803803
804804
!> Function that uses the interpolation coefficients and the current state
805805
!! at the cell centers in order to estimate the state at the image point
806-
subroutine s_interpolate_image_point(q_prim_vf, gp, alpha_rho_IP, alpha_IP, pres_IP, vel_IP, c_IP, r_IP, v_IP, pb_IP, mv_IP, nmom_IP, pb_in, mv_in, presb_IP, massv_IP)
806+
subroutine s_interpolate_image_point(q_prim_vf, gp, alpha_rho_IP, alpha_IP, &
807+
pres_IP, vel_IP, c_IP, r_IP, v_IP, pb_IP, &
808+
mv_IP, nmom_IP, pb_in, mv_in, presb_IP, massv_IP)
807809
$:GPU_ROUTINE(parallelism='[seq]')
808810
type(scalar_field), &
809811
dimension(sys_size), &
810812
intent(IN) :: q_prim_vf !< Primitive Variables
811813
812-
real(wp), optional, dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(IN) :: pb_in, mv_in
814+
real(stp), optional, dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(IN) :: pb_in, mv_in
813815
814816
type(ghost_point), intent(IN) :: gp
815817
real(wp), intent(INOUT) :: pres_IP
@@ -909,8 +911,10 @@ contains
909911
if (.not. polytropic) then
910912
do q = 1, nb
911913
do l = 1, nnode
912-
presb_IP((q - 1)*nnode + l) = presb_IP((q - 1)*nnode + l) + coeff*pb_in(i, j, k, l, q)
913-
massv_IP((q - 1)*nnode + l) = massv_IP((q - 1)*nnode + l) + coeff*mv_in(i, j, k, l, q)
914+
presb_IP((q - 1)*nnode + l) = presb_IP((q - 1)*nnode + l) + &
915+
coeff*real(pb_in(i, j, k, l, q), kind=wp)
916+
massv_IP((q - 1)*nnode + l) = massv_IP((q - 1)*nnode + l) + &
917+
coeff*real(mv_in(i, j, k, l, q), kind=wp)
914918
end do
915919
end do
916920
end if

src/simulation/m_rhs.fpp

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2010,13 +2010,11 @@ contains
20102010
@:DEALLOCATE(q_cons_qp%vf(j)%sf)
20112011
@:DEALLOCATE(q_prim_qp%vf(j)%sf)
20122012
else
2013-
!$:GPU_EXIT_DATA(detach='[q_prim_qp%vf(j)%sf]')
20142013
nullify (q_prim_qp%vf(j)%sf)
20152014
end if
20162015
end do
20172016
20182017
do j = adv_idx%beg, adv_idx%end
2019-
!$:GPU_EXIT_DATA(detach='[q_prim_qp%vf(j)%sf]')
20202018
nullify (q_prim_qp%vf(j)%sf)
20212019
end do
20222020

src/simulation/p_main.fpp

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,6 @@ program p_main
3333
real(wp) :: start, finish
3434
integer :: nt
3535

36-
logical :: status
37-
3836
call system_clock(COUNT=cpu_start, COUNT_RATE=cpu_rate)
3937

4038
call nvtxStartRange("INIT")

0 commit comments

Comments
 (0)