Skip to content

Commit e927790

Browse files
author
Diego Vaca
committed
Remove stop commands from GPU regions
1 parent 18ac868 commit e927790

File tree

4 files changed

+31
-54
lines changed

4 files changed

+31
-54
lines changed

src/simulation/m_bubbles_EL.fpp

Lines changed: 15 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -234,7 +234,7 @@ contains
234234
end do
235235
close (94)
236236
else
237-
stop "if you include lagrange bubbles, you have to initialize them in input/lag_bubbles.dat"
237+
stop "Lagrange bubbles: you have to initialize them in input/lag_bubbles.dat"
238238
end if
239239
else
240240
if (proc_rank == 0) print *, 'Restarting lagrange bubbles at save_count: ', save_count
@@ -315,6 +315,16 @@ contains
315315
cell = -buff_size
316316
call s_locate_cell(mtn_pos(bub_id, 1:3, 1), cell, mtn_s(bub_id, 1:3, 1))
317317

318+
! Check if the bubble is located in the ghost cell of a symmetric boundary
319+
if (bc_x%beg == -2 .and. cell(1) < 0) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_x%beg)."
320+
if (bc_x%end == -2 .and. cell(1) > m) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_x%end)."
321+
if (bc_y%beg == -2 .and. cell(2) < 0) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_y%beg)."
322+
if (bc_y%end == -2 .and. cell(2) > n) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_y%end)."
323+
if (p > 0) then
324+
if (bc_z%beg == -2 .and. cell(3) < 0) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_z%beg)."
325+
if (bc_z%end == -2 .and. cell(3) > p) stop "Lagrange bubble is in the ghost cells of a symmetric boundary (bc_z%end)."
326+
end if
327+
318328
! If particle is in the ghost cells, find the closest non-ghost cell
319329
cell(1) = min(max(cell(1), 0), m)
320330
cell(2) = min(max(cell(2), 0), n)
@@ -343,17 +353,15 @@ contains
343353
gas_mv(bub_id, 1) = pv*volparticle*(1._wp/(R_v*Tw))*(massflag) ! vapermass
344354
gas_mg(bub_id) = (gas_p(bub_id, 1) - pv*(massflag))*volparticle*(1._wp/(R_n*Tw)) ! gasmass
345355
if (gas_mg(bub_id) <= 0._wp) then
346-
stop 'the initial mass of gas inside the bubble is negative. Check your initial conditions'
356+
stop 'The initial mass of gas inside the bubble is negative. Check your initial conditions'
347357
end if
348358
totalmass = gas_mg(bub_id) + gas_mv(bub_id, 1) ! totalmass
349359

350360
! Bubble natural frequency
351361
concvap = gas_mv(bub_id, 1)/(gas_mv(bub_id, 1) + gas_mg(bub_id))
352362
omegaN = (3._wp*(gas_p(bub_id, 1) - pv*(massflag)) + 4._wp*(1._wp/Web)/bub_R0(bub_id))/rhol
353363
if (pv*(massflag) > gas_p(bub_id, 1)) then
354-
print *, 'Not allowed: bubble initially located in a region with pressure below the vapor pressure'
355-
print *, 'location:', mtn_pos(bub_id, 1:3, 1)
356-
stop
364+
stop "Lagrange bubble initially located in a region with pressure below the vapor pressure."
357365
end if
358366
omegaN = sqrt(omegaN/bub_R0(bub_id)**2._wp)
359367

@@ -794,7 +802,7 @@ contains
794802
real(wp) :: charvol, charpres, charvol2, charpres2
795803
integer, dimension(3) :: cellaux
796804
integer :: i, j, k
797-
integer :: mapCells_pinf, smearGrid, smearGridz
805+
integer :: smearGrid, smearGridz
798806
logical :: celloutside
799807

800808
scoord = mtn_s(bub_id, 1:3, 2)
@@ -882,15 +890,8 @@ contains
882890
else if (lag_params%cluster_type >= 2) then
883891
! Bubble dynamic closure from Maeda and Colonius (2018)
884892

885-
! Range of cells included in Omega
886-
if (lag_params%smooth_type == 1) then
887-
mapCells_pinf = mapCells
888-
else
889-
stop "lag_params%cluster_type: 2 requires lag_params%smooth_type: 1."
890-
end if
891-
892893
! Include the cell that contains the bubble (mapCells+1+mapCells)
893-
smearGrid = mapCells_pinf - (-mapCells_pinf) + 1
894+
smearGrid = mapCells - (-mapCells) + 1
894895
smearGridz = smearGrid
895896
if (p == 0) smearGridz = 1
896897

@@ -964,9 +965,6 @@ contains
964965
f_pinfl = charpres2/charvol2
965966
vol = charvol
966967
dc = (3._wp*abs(vol)/(4._wp*pi))**(1._wp/3._wp)
967-
else
968-
969-
stop "Check cluterflag. Exiting."
970968

971969
end if
972970

@@ -1015,7 +1013,6 @@ contains
10151013
mtn_vel(k, 1:3, 1) = mtn_vel(k, 1:3, 1) + dt*mtn_dveldt(k, 1:3, 1)
10161014
gas_p(k, 1) = gas_p(k, 1) + dt*gas_dpdt(k, 1)
10171015
gas_mv(k, 1) = gas_mv(k, 1) + dt*gas_dmvdt(k, 1)
1018-
if (intfc_rad(k, 1) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
10191016
end do
10201017

10211018
call s_transfer_data_to_tmp()
@@ -1038,7 +1035,6 @@ contains
10381035
mtn_vel(k, 1:3, 2) = mtn_vel(k, 1:3, 1) + dt*mtn_dveldt(k, 1:3, 1)
10391036
gas_p(k, 2) = gas_p(k, 1) + dt*gas_dpdt(k, 1)
10401037
gas_mv(k, 2) = gas_mv(k, 1) + dt*gas_dmvdt(k, 1)
1041-
if (intfc_rad(k, 2) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
10421038
end do
10431039

10441040
elseif (stage == 2) then
@@ -1051,7 +1047,6 @@ contains
10511047
mtn_vel(k, 1:3, 1) = mtn_vel(k, 1:3, 1) + dt*(mtn_dveldt(k, 1:3, 1) + mtn_dveldt(k, 1:3, 2))/2._wp
10521048
gas_p(k, 1) = gas_p(k, 1) + dt*(gas_dpdt(k, 1) + gas_dpdt(k, 2))/2._wp
10531049
gas_mv(k, 1) = gas_mv(k, 1) + dt*(gas_dmvdt(k, 1) + gas_dmvdt(k, 2))/2._wp
1054-
if (intfc_rad(k, 1) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
10551050
end do
10561051

10571052
call s_transfer_data_to_tmp()
@@ -1076,7 +1071,6 @@ contains
10761071
mtn_vel(k, 1:3, 2) = mtn_vel(k, 1:3, 1) + dt*mtn_dveldt(k, 1:3, 1)
10771072
gas_p(k, 2) = gas_p(k, 1) + dt*gas_dpdt(k, 1)
10781073
gas_mv(k, 2) = gas_mv(k, 1) + dt*gas_dmvdt(k, 1)
1079-
if (intfc_rad(k, 2) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
10801074
end do
10811075

10821076
elseif (stage == 2) then
@@ -1089,7 +1083,6 @@ contains
10891083
mtn_vel(k, 1:3, 2) = mtn_vel(k, 1:3, 1) + dt*(mtn_dveldt(k, 1:3, 1) + mtn_dveldt(k, 1:3, 2))/4._wp
10901084
gas_p(k, 2) = gas_p(k, 1) + dt*(gas_dpdt(k, 1) + gas_dpdt(k, 2))/4._wp
10911085
gas_mv(k, 2) = gas_mv(k, 1) + dt*(gas_dmvdt(k, 1) + gas_dmvdt(k, 2))/4._wp
1092-
if (intfc_rad(k, 2) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
10931086
end do
10941087
elseif (stage == 3) then
10951088
!$acc parallel loop gang vector default(present) private(k)
@@ -1101,7 +1094,6 @@ contains
11011094
mtn_vel(k, 1:3, 1) = mtn_vel(k, 1:3, 1) + (2._wp/3._wp)*dt*(mtn_dveldt(k, 1:3, 1)/4._wp + mtn_dveldt(k, 1:3, 2)/4._wp + mtn_dveldt(k, 1:3, 3))
11021095
gas_p(k, 1) = gas_p(k, 1) + (2._wp/3._wp)*dt*(gas_dpdt(k, 1)/4._wp + gas_dpdt(k, 2)/4._wp + gas_dpdt(k, 3))
11031096
gas_mv(k, 1) = gas_mv(k, 1) + (2._wp/3._wp)*dt*(gas_dmvdt(k, 1)/4._wp + gas_dmvdt(k, 2)/4._wp + gas_dmvdt(k, 3))
1104-
if (intfc_rad(k, 1) <= 0._wp) stop "Negative bubble radius encountered, please reduce dt"
11051097
end do
11061098

11071099
call s_transfer_data_to_tmp()

src/simulation/m_bubbles_EL_kernels.fpp

Lines changed: 6 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -317,51 +317,27 @@ contains
317317

318318
! x-dir
319319
if (bc_x%beg == -2 .and. (cell(1) <= mapCells - 1)) then
320-
if (cell(1) >= 0) then
321-
cellaux(1) = abs(cellaux(1)) - 1
322-
else
323-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_x%beg)."
324-
end if
320+
cellaux(1) = abs(cellaux(1)) - 1
325321
end if
326322
if (bc_x%end == -2 .and. (cell(1) >= m + 1 - mapCells)) then
327-
if (cell(1) <= m) then
328-
cellaux(1) = cellaux(1) - (2*(cellaux(1) - m) - 1)
329-
else
330-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_x%end)."
331-
end if
323+
cellaux(1) = cellaux(1) - (2*(cellaux(1) - m) - 1)
332324
end if
333325

334326
!y-dir
335327
if (bc_y%beg == -2 .and. (cell(2) <= mapCells - 1)) then
336-
if (cell(2) >= 0) then
337-
cellaux(2) = abs(cellaux(2)) - 1
338-
else
339-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_y%beg)."
340-
end if
328+
cellaux(2) = abs(cellaux(2)) - 1
341329
end if
342330
if (bc_y%end == -2 .and. (cell(2) >= n + 1 - mapCells)) then
343-
if (cell(2) <= n) then
344-
cellaux(2) = cellaux(2) - (2*(cellaux(2) - n) - 1)
345-
else
346-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_y%end)."
347-
end if
331+
cellaux(2) = cellaux(2) - (2*(cellaux(2) - n) - 1)
348332
end if
349333

350334
if (p > 0) then
351335
!z-dir
352336
if (bc_z%beg == -2 .and. (cell(3) <= mapCells - 1)) then
353-
if (cell(3) >= 0) then
354-
cellaux(3) = abs(cellaux(3)) - 1
355-
else
356-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_z%beg)."
357-
end if
337+
cellaux(3) = abs(cellaux(3)) - 1
358338
end if
359339
if (bc_z%end == -2 .and. (cell(3) >= p + 1 - mapCells)) then
360-
if (cell(3) <= p) then
361-
cellaux(3) = cellaux(3) - (2*(cellaux(3) - p) - 1)
362-
else
363-
stop "Lagrangian bubbles must not be located in the ghost cells of a symmetric boundary (bc_z%end)."
364-
end if
340+
cellaux(3) = cellaux(3) - (2*(cellaux(3) - p) - 1)
365341
end if
366342
end if
367343

src/simulation/m_checker.fpp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -332,6 +332,7 @@ contains
332332
@:PROHIBIT(bubbles_lagrange .and. file_per_process, "file_per_process must be false for bubbles_lagrange")
333333
@:PROHIBIT(bubbles_lagrange .and. n==0, "bubbles_lagrange accepts 2D and 3D simulations only")
334334
@:PROHIBIT(bubbles_lagrange .and. model_eqns==3, "The 6-equation flow model does not support bubbles_lagrange")
335+
@:PROHIBIT(bubbles_lagrange .and. lag_params%cluster_type>=2 .and. lag_params%smooth_type/=1, "cluster_type=2 requires smooth_type=1")
335336
end subroutine s_check_inputs_bubbles_lagrange
336337
337338
!> Checks constraints on continuum damage model parameters

src/simulation/m_start_up.fpp

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1405,9 +1405,17 @@ contains
14051405
end if
14061406

14071407
if (bubbles_lagrange) then
1408+
!$acc update host(intfc_rad)
1409+
do i = 1, nBubs
1410+
if (ieee_is_nan(intfc_rad(i, 1)) .or. intfc_rad(i, 1) <= 0._wp) then
1411+
print *, "Bubble radius is negative or NaN", proc_rank, t_step, i, intfc_rad(i, 1)
1412+
error stop "Bubble radius is negative or NaN, please reduce dt"
1413+
end if
1414+
end do
1415+
14081416
!$acc update host(q_beta%vf(1)%sf)
14091417
call s_write_data_files(q_cons_ts(1)%vf, q_T_sf, q_prim_vf, save_count, q_beta%vf(1))
1410-
!$acc update host(Rmax_stats, Rmin_stats, gas_p, gas_mv, intfc_rad, intfc_vel)
1418+
!$acc update host(Rmax_stats, Rmin_stats, gas_p, gas_mv, intfc_vel)
14111419
call s_write_restart_lag_bubbles(save_count) !parallel
14121420
if (lag_params%write_bubbles_stats) call s_write_lag_bubble_stats()
14131421
else

0 commit comments

Comments
 (0)