Skip to content

Commit e689a6b

Browse files
committed
renamed to bc_bound and fixed things
1 parent bf2a897 commit e689a6b

File tree

8 files changed

+64
-77
lines changed

8 files changed

+64
-77
lines changed

src/common/m_boundary_common.fpp

Lines changed: 19 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ module m_boundary_common
2222
type(scalar_field), dimension(:, :), allocatable :: bc_buffers
2323
!$acc declare create(bc_buffers)
2424

25-
type(boundary_flags) :: bc_flag
25+
type(boundary_bounds) :: bc_bound
2626

2727
#ifdef MFC_MPI
2828
integer, dimension(1:3, -1:1) :: MPI_BC_TYPE_TYPE, MPI_BC_BUFFER_TYPE
@@ -34,7 +34,7 @@ module m_boundary_common
3434
s_populate_capillary_buffers, &
3535
s_finalize_boundary_common_module
3636

37-
public :: bc_buffers, bc_flag
37+
public :: bc_buffers, bc_bound
3838

3939
#ifdef MFC_MPI
4040
public :: MPI_BC_TYPE_TYPE, MPI_BC_BUFFER_TYPE
@@ -44,7 +44,7 @@ contains
4444

4545
impure subroutine s_initialize_boundary_common_module()
4646

47-
bc_flag%xb = bc_x%beg; bc_flag%xe = bc_x%end; bc_flag%yb = bc_y%beg; bc_flag%ye = bc_y%end; bc_flag%zb = bc_z%beg; bc_flag%ze = bc_z%end
47+
bc_bound%xb = bc_x%beg; bc_bound%xe = bc_x%end; bc_bound%yb = bc_y%beg; bc_bound%ye = bc_y%end; bc_bound%zb = bc_z%beg; bc_bound%ze = bc_z%end
4848

4949
@:ALLOCATE(bc_buffers(1:num_dims, -1:1))
5050

@@ -71,17 +71,17 @@ contains
7171
!> The purpose of this procedure is to populate the buffers
7272
!! of the primitive variables, depending on the selected
7373
!! boundary conditions.
74-
impure subroutine s_populate_variables_buffers(q_prim_vf, pb, mv, bc_type, bc_flag)
74+
impure subroutine s_populate_variables_buffers(q_prim_vf, pb, mv, bc_type, bc_bound)
7575

7676
type(scalar_field), dimension(sys_size), intent(inout) :: q_prim_vf
7777
real(wp), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(inout) :: pb, mv
7878
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
79-
type(boundary_flags), intent(in) :: bc_flag
79+
type(boundary_bounds), intent(in) :: bc_bound
8080

8181
integer :: k, l
8282

8383
! Population of Buffers in x-direction
84-
if (bc_flag%xb >= 0) then
84+
if (bc_bound%xb >= 0) then
8585
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 1, -1)
8686
else
8787
!$acc parallel loop collapse(2) gang vector default(present)
@@ -105,7 +105,7 @@ contains
105105
end do
106106
end if
107107

108-
if (bc_flag%xe >= 0) then
108+
if (bc_bound%xe >= 0) then
109109
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 1, 1)
110110
else
111111
!$acc parallel loop collapse(2) gang vector default(present)
@@ -133,7 +133,7 @@ contains
133133

134134
if (n == 0) return
135135

136-
if (bc_flag%yb >= 0) then
136+
if (bc_bound%yb >= 0) then
137137
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 2, -1)
138138
else
139139
!$acc parallel loop collapse(2) gang vector default(present)
@@ -159,7 +159,7 @@ contains
159159
end do
160160
end if
161161

162-
if (bc_flag%ye >= 0) then
162+
if (bc_bound%ye >= 0) then
163163
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 2, 1)
164164
else
165165
!$acc parallel loop collapse(2) gang vector default(present)
@@ -187,7 +187,7 @@ contains
187187

188188
if (p == 0) return
189189

190-
if (bc_flag%zb >= 0) then
190+
if (bc_bound%zb >= 0) then
191191
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 3, -1)
192192
else
193193
!$acc parallel loop collapse(2) gang vector default(present)
@@ -211,7 +211,7 @@ contains
211211
end do
212212
end if
213213

214-
if (bc_flag%ze >= 0) then
214+
if (bc_bound%ze >= 0) then
215215
call s_mpi_sendrecv_variables_buffers(q_prim_vf, pb, mv, 3, 1)
216216
else
217217
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1157,16 +1157,16 @@ contains
11571157

11581158
end subroutine s_qbmm_extrapolation
11591159

1160-
impure subroutine s_populate_capillary_buffers(c_divs, bc_type, bc_flag)
1160+
impure subroutine s_populate_capillary_buffers(c_divs, bc_type, bc_bound)
11611161

11621162
type(scalar_field), dimension(num_dims + 1), intent(inout) :: c_divs
11631163
type(integer_field), dimension(1:num_dims, -1:1), intent(in) :: bc_type
1164-
type(boundary_flags), intent(in) :: bc_flag
1164+
type(boundary_bounds), intent(in) :: bc_bound
11651165

11661166
integer :: k, l
11671167

11681168
!< x-direction
1169-
if (bc_flag%xb >= 0) then
1169+
if (bc_bound%xb >= 0) then
11701170
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 1, -1)
11711171
else
11721172
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1184,7 +1184,7 @@ contains
11841184
end do
11851185
end if
11861186

1187-
if (bc_flag%xe >= 0) then
1187+
if (bc_bound%xe >= 0) then
11881188
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 1, 1)
11891189
else
11901190
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1205,7 +1205,7 @@ contains
12051205
if (n == 0) return
12061206

12071207
!< y-direction
1208-
if (bc_flag%yb >= 0) then
1208+
if (bc_bound%yb >= 0) then
12091209
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 2, -1)
12101210
else
12111211
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1223,7 +1223,7 @@ contains
12231223
end do
12241224
end if
12251225

1226-
if (bc_flag%ye >= 0) then
1226+
if (bc_bound%ye >= 0) then
12271227
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 2, 1)
12281228
else
12291229
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1244,7 +1244,7 @@ contains
12441244
if (p == 0) return
12451245

12461246
!< z-direction
1247-
if (bc_flag%zb >= 0) then
1247+
if (bc_bound%zb >= 0) then
12481248
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 3, -1)
12491249
else
12501250
!$acc parallel loop collapse(2) gang vector default(present)
@@ -1262,7 +1262,7 @@ contains
12621262
end do
12631263
end if
12641264

1265-
if (bc_flag%ze >= 0) then
1265+
if (bc_bound%ze >= 0) then
12661266
call s_mpi_sendrecv_capilary_variables_buffers(c_divs, 3, 1)
12671267
else
12681268
!$acc parallel loop collapse(2) gang vector default(present)

src/common/m_derived_types.fpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -346,9 +346,9 @@ module m_derived_types
346346
end type mpi_io_airfoil_ib_var
347347
348348
!> Derived type for boundary flags
349-
type boundary_flags
349+
type boundary_bounds
350350
real(wp) :: xb, xe, yb, ye, zb, ze
351-
end type boundary_flags
351+
end type boundary_bounds
352352
353353
!> Derived type annexing integral regions
354354
type integral_parameters

src/pre_process/m_perturbation.fpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ contains
3232

3333
impure subroutine s_initialize_perturbation_module()
3434

35-
bc_flag%xb = bc_x%beg; bc_flag%xe = bc_x%end; bc_flag%yb = bc_y%beg; bc_flag%ye = bc_y%end; bc_flag%zb = bc_z%beg; bc_flag%ze = bc_z%end
35+
bc_bound%xb = bc_x%beg; bc_bound%xe = bc_x%end; bc_bound%yb = bc_y%beg; bc_bound%ye = bc_y%end; bc_bound%zb = bc_z%beg; bc_bound%ze = bc_z%end
3636

3737
if (mixlayer_perturb) then
3838
mixlayer_bc_fd = 2
@@ -624,7 +624,7 @@ contains
624624
do q = 1, elliptic_smoothing_iters
625625

626626
! Communication of buffer regions and apply boundary conditions
627-
call s_populate_variables_buffers(q_prim_vf, pb%sf, mv%sf, bc_type, bc_flag)
627+
call s_populate_variables_buffers(q_prim_vf, pb%sf, mv%sf, bc_type, bc_bound)
628628

629629
! Perform smoothing and store in temp array
630630
if (n == 0) then

src/simulation/m_cbc.fpp

Lines changed: 27 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -101,10 +101,10 @@ module m_cbc
101101
!$acc declare create(is1, is2, is3)
102102
103103
integer :: dj
104-
type(boundary_flags) :: bc_flag !< Boundary flags
104+
type(boundary_bounds) :: bc_bound !< Boundary flags
105105
integer :: cbc_dir, cbc_loc
106106
integer :: flux_cbc_index
107-
!$acc declare create(dj, bc_flag, cbc_dir, cbc_loc, flux_cbc_index)
107+
!$acc declare create(dj, bc_bound, cbc_dir, cbc_loc, flux_cbc_index)
108108
109109
!! GRCBC inputs for subsonic inflow and outflow conditions consisting of
110110
!! inflow velocities, pressure, density and void fraction as well as
@@ -392,23 +392,23 @@ contains
392392
! Associating the procedural pointer to the appropriate subroutine
393393
! that will be utilized in the conversion to the mixture variables
394394
395-
bc_flag%xb = bc_x%beg
396-
bc_flag%xe = bc_x%end
395+
bc_bound%xb = bc_x%beg
396+
bc_bound%xe = bc_x%end
397397
398-
!$acc update device(bc_flag)
398+
!$acc update device(bc_bound)
399399
400400
if (n > 0) then
401-
bc_flag%yb = bc_y%beg
402-
bc_flag%ye = bc_y%end
401+
bc_bound%yb = bc_y%beg
402+
bc_bound%ye = bc_y%end
403403
404-
!$acc update device(bc_flag)
404+
!$acc update device(bc_bound)
405405
end if
406406
407407
if (p > 0) then
408-
bc_flag%zb = bc_z%beg
409-
bc_flag%ze = bc_z%end
408+
bc_bound%zb = bc_z%beg
409+
bc_bound%ze = bc_z%end
410410
411-
!$acc update device(bc_flag)
411+
!$acc update device(bc_bound)
412412
end if
413413
414414
! Allocate GRCBC inputs
@@ -911,14 +911,14 @@ contains
911911
912912
Ma = vel(dir_idx(1))/c
913913
914-
if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_SLIP_WALL) .or. &
915-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_SLIP_WALL)) then
914+
if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_SLIP_WALL) .or. &
915+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_SLIP_WALL)) then
916916
call s_compute_slip_wall_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds)
917-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_NR_SUB_BUFFER) .or. &
918-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_NR_SUB_BUFFER)) then
917+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_NR_SUB_BUFFER) .or. &
918+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_NR_SUB_BUFFER)) then
919919
call s_compute_nonreflecting_subsonic_buffer_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds, dYs_ds)
920-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_NR_SUB_INFLOW) .or. &
921-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_NR_SUB_INFLOW)) then
920+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_NR_SUB_INFLOW) .or. &
921+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_NR_SUB_INFLOW)) then
922922
call s_compute_nonreflecting_subsonic_inflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds)
923923
! Add GRCBC for Subsonic Inflow
924924
if (bc_${XYZ}$%grcbc_in) then
@@ -938,8 +938,8 @@ contains
938938
end do
939939
L(advxe) = rho*c**2._wp*(1._wp + Ma)*(vel(dir_idx(1)) + vel_in(${CBC_DIR}$, dir_idx(1))*sign(1, cbc_loc))/Del_in(${CBC_DIR}$) + c*(1._wp + Ma)*(pres - pres_in(${CBC_DIR}$))/Del_in(${CBC_DIR}$)
940940
end if
941-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_NR_SUB_OUTFLOW) .or. &
942-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_NR_SUB_OUTFLOW)) then
941+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_NR_SUB_OUTFLOW) .or. &
942+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_NR_SUB_OUTFLOW)) then
943943
call s_compute_nonreflecting_subsonic_outflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds, dYs_ds)
944944
! Add GRCBC for Subsonic Outflow (Pressure)
945945
if (bc_${XYZ}$%grcbc_out) then
@@ -950,17 +950,17 @@ contains
950950
L(advxe) = L(advxe) + rho*c**2._wp*(1._wp - Ma)*(vel(dir_idx(1)) + vel_out(${CBC_DIR}$, dir_idx(1))*sign(1, cbc_loc))/Del_out(${CBC_DIR}$)
951951
end if
952952
end if
953-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_FF_SUB_OUTFLOW) .or. &
954-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_FF_SUB_OUTFLOW)) then
953+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_FF_SUB_OUTFLOW) .or. &
954+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_FF_SUB_OUTFLOW)) then
955955
call s_compute_force_free_subsonic_outflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds)
956-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_CP_SUB_OUTFLOW) .or. &
957-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_CP_SUB_OUTFLOW)) then
956+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_CP_SUB_OUTFLOW) .or. &
957+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_CP_SUB_OUTFLOW)) then
958958
call s_compute_constant_pressure_subsonic_outflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds)
959-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_SUP_INFLOW) .or. &
960-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_SUP_INFLOW)) then
959+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_SUP_INFLOW) .or. &
960+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_SUP_INFLOW)) then
961961
call s_compute_supersonic_inflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds)
962-
else if ((cbc_loc == -1 .and. bc_flag%${XYZ}$b == BC_CHAR_SUP_OUTFLOW) .or. &
963-
(cbc_loc == 1 .and. bc_flag%${XYZ}$e == BC_CHAR_SUP_OUTFLOW)) then
962+
else if ((cbc_loc == -1 .and. bc_bound%${XYZ}$b == BC_CHAR_SUP_OUTFLOW) .or. &
963+
(cbc_loc == 1 .and. bc_bound%${XYZ}$e == BC_CHAR_SUP_OUTFLOW)) then
964964
call s_compute_supersonic_outflow_L(lambda, L, rho, c, mf, dalpha_rho_ds, dpres_ds, dvel_ds, dadv_ds, dYs_ds)
965965
end if
966966

src/simulation/m_ibm.fpp

Lines changed: 11 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -97,8 +97,8 @@ contains
9797

9898
! Initialize the ip component of each ghost point
9999
do i = 1, num_gps
100-
allocate (ghost_points(i)%ip%alpha_rho(num_fluids))
101-
allocate (ghost_points(i)%ip%alpha(num_fluids))
100+
@:ALLOCATE(ghost_points(i)%ip%alpha_rho(num_fluids))
101+
@:ALLOCATE(ghost_points(i)%ip%alpha(num_fluids))
102102
ghost_points(i)%ip%vel = 0.0_wp
103103
ghost_points(i)%ip%pressure = 0.0_wp
104104

@@ -107,19 +107,19 @@ contains
107107
end if
108108

109109
if (bubbles_euler) then
110-
allocate (ghost_points(i)%ip%r(nb))
111-
allocate (ghost_points(i)%ip%v(nb))
110+
@:ALLOCATE(ghost_points(i)%ip%r(nb))
111+
@:ALLOCATE(ghost_points(i)%ip%v(nb))
112112
if (.not. polytropic) then
113-
allocate (ghost_points(i)%ip%pb(nb))
114-
allocate (ghost_points(i)%ip%mv(nb))
113+
@:ALLOCATE(ghost_points(i)%ip%pb(nb))
114+
@:ALLOCATE(ghost_points(i)%ip%mv(nb))
115115
end if
116116
end if
117117

118118
if (qbmm) then
119-
allocate (ghost_points(i)%ip%nmom(nb*nmom))
119+
@:ALLOCATE(ghost_points(i)%ip%nmom(nb*nmom))
120120
if (.not. polytropic) then
121-
allocate (ghost_points(i)%ip%presb(nb*nnode))
122-
allocate (ghost_points(i)%ip%massv(nb*nnode))
121+
@:ALLOCATE(ghost_points(i)%ip%presb(nb*nnode))
122+
@:ALLOCATE(ghost_points(i)%ip%massv(nb*nnode))
123123
end if
124124
end if
125125
end do
@@ -872,21 +872,8 @@ contains
872872

873873
!> Subroutine to deallocate memory reserved for the IBM module
874874
impure subroutine s_finalize_ibm_module()
875-
integer :: i
876-
877-
if (allocated(ghost_points)) then
878-
do i = 1, size(ghost_points)
879-
if (allocated(ghost_points(i)%ip%alpha_rho)) deallocate (ghost_points(i)%ip%alpha_rho)
880-
if (allocated(ghost_points(i)%ip%alpha)) deallocate (ghost_points(i)%ip%alpha)
881-
if (allocated(ghost_points(i)%ip%r)) deallocate (ghost_points(i)%ip%r)
882-
if (allocated(ghost_points(i)%ip%v)) deallocate (ghost_points(i)%ip%v)
883-
if (allocated(ghost_points(i)%ip%pb)) deallocate (ghost_points(i)%ip%pb)
884-
if (allocated(ghost_points(i)%ip%mv)) deallocate (ghost_points(i)%ip%mv)
885-
if (allocated(ghost_points(i)%ip%nmom)) deallocate (ghost_points(i)%ip%nmom)
886-
if (allocated(ghost_points(i)%ip%presb)) deallocate (ghost_points(i)%ip%presb)
887-
if (allocated(ghost_points(i)%ip%massv)) deallocate (ghost_points(i)%ip%massv)
888-
end do
889-
end if
875+
876+
if (allocated(ghost_points)) deallocate(ghost_points)
890877

891878
@:DEALLOCATE(ib_markers%sf)
892879
@:DEALLOCATE(levelset%sf)

src/simulation/m_rhs.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -674,7 +674,7 @@ contains
674674
call nvtxEndRange
675675

676676
call nvtxStartRange("RHS-COMMUNICATION")
677-
call s_populate_variables_buffers(q_prim_qp%vf, pb, mv, bc_type, bc_flag)
677+
call s_populate_variables_buffers(q_prim_qp%vf, pb, mv, bc_type, bc_bound)
678678
call nvtxEndRange
679679

680680
call nvtxStartRange("RHS-ELASTIC")

src/simulation/m_surface_tension.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -290,7 +290,7 @@ contains
290290
end do
291291
end do
292292

293-
call s_populate_capillary_buffers(c_divs, bc_type, bc_flag)
293+
call s_populate_capillary_buffers(c_divs, bc_type, bc_bound)
294294

295295
iv%beg = 1; iv%end = num_dims + 1
296296

src/simulation/m_time_steppers.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -940,7 +940,7 @@ contains
940940

941941
elseif (bubbles_lagrange) then
942942

943-
call s_populate_variables_buffers(q_prim_vf, pb_ts(1)%sf, mv_ts(1)%sf, bc_type, bc_flag)
943+
call s_populate_variables_buffers(q_prim_vf, pb_ts(1)%sf, mv_ts(1)%sf, bc_type, bc_bound)
944944
call s_compute_bubble_EL_dynamics(q_cons_ts(1)%vf, q_prim_vf, t_step, rhs_vf, stage)
945945
call s_transfer_data_to_tmp()
946946
call s_smear_voidfraction()

0 commit comments

Comments
 (0)