Skip to content

Commit 98475aa

Browse files
committed
Refactor the use of ix, iy, and iz
1 parent 587e6fc commit 98475aa

13 files changed

+376
-487
lines changed

src/common/m_variables_conversion.fpp

Lines changed: 17 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -81,9 +81,6 @@ module m_variables_conversion
8181

8282
end interface ! ============================================================
8383

84-
integer, public :: ixb, ixe, iyb, iye, izb, ize
85-
!$acc declare create(ixb, ixe, iyb, iye, izb, ize)
86-
8784
!! In simulation, gammas, pi_infs, and qvs are already declared in m_global_variables
8885
#ifndef MFC_SIMULATION
8986
real(kind(0d0)), allocatable, public, dimension(:) :: gammas, gs_min, pi_infs, ps_inf, cvs, qvs, qvps
@@ -628,26 +625,7 @@ contains
628625

629626
integer :: i, j
630627

631-
#ifdef MFC_PRE_PROCESS
632-
ixb = 0; iyb = 0; izb = 0;
633-
ixe = m; iye = n; ize = p;
634-
#else
635-
ixb = -buff_size
636-
ixe = m - ixb
637-
638-
iyb = 0; iye = 0; izb = 0; ize = 0;
639-
if (n > 0) then
640-
iyb = -buff_size; iye = n - iyb
641-
642-
if (p > 0) then
643-
izb = -buff_size; ize = p - izb
644-
end if
645-
end if
646-
#endif
647-
648-
!$acc enter data copyin(ixb, ixe, iyb, iye, izb, ize)
649628
!$acc enter data copyin(is1b, is1e, is2b, is2e, is3b, is3e)
650-
!$acc update device(ixb, ixe, iyb, iye, izb, ize)
651629

652630
#ifdef MFC_SIMULATION
653631
@:ALLOCATE_GLOBAL(gammas (1:num_fluids))
@@ -784,15 +762,16 @@ contains
784762

785763
!Initialize mv at the quadrature nodes based on the initialized moments and sigma
786764
subroutine s_initialize_mv(qK_cons_vf, mv)
765+
787766
type(scalar_field), dimension(sys_size), intent(in) :: qK_cons_vf
788-
real(kind(0d0)), dimension(ixb:, iyb:, izb:, 1:, 1:), intent(inout) :: mv
767+
real(kind(0d0)), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(inout) :: mv
789768

790769
integer :: i, j, k, l
791770
real(kind(0d0)) :: mu, sig, nbub_sc
792771

793-
do l = izb, ize
794-
do k = iyb, iye
795-
do j = ixb, ixe
772+
do l = idwbuff(3)%beg, idwbuff(3)%end
773+
do k = idwbuff(2)%beg, idwbuff(2)%end
774+
do j = idwbuff(1)%beg, idwbuff(1)%end
796775

797776
nbub_sc = qK_cons_vf(bubxb)%sf(j, k, l)
798777

@@ -816,15 +795,15 @@ contains
816795
!Initialize pb at the quadrature nodes using isothermal relations (Preston model)
817796
subroutine s_initialize_pb(qK_cons_vf, mv, pb)
818797
type(scalar_field), dimension(sys_size), intent(in) :: qK_cons_vf
819-
real(kind(0d0)), dimension(ixb:, iyb:, izb:, 1:, 1:), intent(in) :: mv
820-
real(kind(0d0)), dimension(ixb:, iyb:, izb:, 1:, 1:), intent(inout) :: pb
798+
real(kind(0d0)), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(in) :: mv
799+
real(kind(0d0)), dimension(idwbuff(1)%beg:, idwbuff(2)%beg:, idwbuff(3)%beg:, 1:, 1:), intent(inout) :: pb
821800

822801
integer :: i, j, k, l
823802
real(kind(0d0)) :: mu, sig, nbub_sc
824803

825-
do l = izb, ize
826-
do k = iyb, iye
827-
do j = ixb, ixe
804+
do l = idwbuff(3)%beg, idwbuff(3)%end
805+
do k = idwbuff(2)%beg, idwbuff(2)%end
806+
do j = idwbuff(1)%beg, idwbuff(1)%end
828807

829808
nbub_sc = qK_cons_vf(bubxb)%sf(j, k, l)
830809

@@ -855,19 +834,16 @@ contains
855834
!! @param iz Index bounds in third coordinate direction
856835
subroutine s_convert_conservative_to_primitive_variables(qK_cons_vf, &
857836
qK_prim_vf, &
858-
gm_alphaK_vf, &
859-
ix, iy, iz)
837+
ibounds, &
838+
gm_alphaK_vf)
860839

861840
type(scalar_field), dimension(sys_size), intent(in) :: qK_cons_vf
862841
type(scalar_field), dimension(sys_size), intent(inout) :: qK_prim_vf
842+
type(int_bounds_info), dimension(1:3), intent(in) :: ibounds
863843
type(scalar_field), &
864844
allocatable, optional, dimension(:), &
865845
intent(in) :: gm_alphaK_vf
866846

867-
type(int_bounds_info), optional, intent(in) :: ix, iy, iz
868-
869-
type(int_bounds_info) :: aix, aiy, aiz
870-
871847
real(kind(0d0)), dimension(num_fluids) :: alpha_K, alpha_rho_K
872848
real(kind(0d0)), dimension(2) :: Re_K
873849
real(kind(0d0)) :: rho_K, gamma_K, pi_inf_K, qv_K, dyn_pres_K
@@ -910,14 +886,10 @@ contains
910886
end if
911887
#:endif
912888

913-
if (present(ix)) then; aix = ix; else; aix%beg = ixb; aix%end = ixe; end if
914-
if (present(iy)) then; aiy = iy; else; aiy%beg = iyb; aiy%end = iye; end if
915-
if (present(iz)) then; aiz = iz; else; aiz%beg = izb; aiz%end = ize; end if
916-
917-
!$acc parallel loop collapse(3) gang vector default(present) copyin(aix, aiy, aiz) private(alpha_K, alpha_rho_K, Re_K, nRtmp, rho_K, gamma_K, pi_inf_K, qv_K, dyn_pres_K, R3tmp, rhoyks)
918-
do l = aiz%beg, aiz%end
919-
do k = aiy%beg, aiy%end
920-
do j = aix%beg, aix%end
889+
!$acc parallel loop collapse(3) gang vector default(present) private(alpha_K, alpha_rho_K, Re_K, nRtmp, rho_K, gamma_K, pi_inf_K, qv_K, dyn_pres_K, R3tmp, rhoyks)
890+
do l = ibounds(3)%beg, ibounds(3)%end
891+
do k = ibounds(2)%beg, ibounds(2)%end
892+
do j = ibounds(1)%beg, ibounds(1)%end
921893
dyn_pres_K = 0d0
922894

923895
!$acc loop seq

src/post_process/m_global_parameters.fpp

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,13 @@ module m_global_parameters
130130
type(int_bounds_info) :: temperature_idx !< Indexes of first & last temperature eqns.
131131
!> @}
132132

133+
! Cell Indices for the (local) interior points (O-m, O-n, 0-p).
134+
type(int_bounds_info) :: idwint(1:3)
135+
136+
! Cell Indices for the entire (local) domain. In simulation, this includes
137+
! the buffer region. idwbuff and idwint are the same otherwise.
138+
type(int_bounds_info) :: idwbuff(1:3)
139+
133140
!> @name Boundary conditions in the x-, y- and z-coordinate directions
134141
!> @{
135142
type(int_bounds_info) :: bc_x, bc_y, bc_z
@@ -259,7 +266,6 @@ module m_global_parameters
259266
real(kind(0d0)) :: poly_sigma
260267
real(kind(0d0)) :: sigR
261268
integer :: nmom
262-
263269
!> @}
264270

265271
!> @name surface tension coefficient
@@ -642,6 +648,14 @@ contains
642648
tempxb = temperature_idx%beg
643649
tempxe = temperature_idx%end
644650

651+
! Configuring Coordinate Direction Indexes =========================
652+
653+
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
654+
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p
655+
656+
! There is no buffer region in pre_process and post_process.
657+
idwbuff(1) = idwint(1); idwbuff(2) = idwint(2); idwbuff(3) = idwint(3)
658+
645659
! ==================================================================
646660

647661
#ifdef MFC_MPI

src/post_process/m_start_up.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -180,7 +180,7 @@ subroutine s_perform_time_step(t_step)
180180
end if
181181

182182
! Converting the conservative variables to the primitive ones
183-
call s_convert_conservative_to_primitive_variables(q_cons_vf, q_prim_vf)
183+
call s_convert_conservative_to_primitive_variables(q_cons_vf, q_prim_vf, idwbuff)
184184

185185
end subroutine s_perform_time_step
186186

src/pre_process/m_global_parameters.fpp

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,13 @@ module m_global_parameters
108108
type(int_bounds_info) :: species_idx !< Indexes of first & last concentration eqns.
109109
type(int_bounds_info) :: temperature_idx !< Indexes of first & last temperature eqns.
110110

111+
! Cell Indices for the (local) interior points (O-m, O-n, 0-p).
112+
type(int_bounds_info) :: idwint(1:3)
113+
114+
! Cell Indices for the entire (local) domain. In simulation, this includes
115+
! the buffer region. idwbuff and idwint are the same otherwise.
116+
type(int_bounds_info) :: idwbuff(1:3)
117+
111118
type(int_bounds_info) :: bc_x, bc_y, bc_z !<
112119
!! Boundary conditions in the x-, y- and z-coordinate directions
113120

@@ -722,6 +729,14 @@ contains
722729
tempxb = temperature_idx%beg
723730
tempxe = temperature_idx%end
724731

732+
! Configuring Coordinate Direction Indexes =========================
733+
734+
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
735+
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p
736+
737+
! There is no buffer region in pre_process and post_process.
738+
idwbuff(1) = idwint(1); idwbuff(2) = idwint(2); idwbuff(3) = idwint(3)
739+
725740
! ==================================================================
726741

727742
#ifdef MFC_MPI

src/pre_process/m_initial_condition.fpp

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,8 @@ contains
124124
! preexisting initial condition data files were read in on start-up
125125
if (old_ic) then
126126
call s_convert_conservative_to_primitive_variables(q_cons_vf, &
127-
q_prim_vf)
127+
q_prim_vf, &
128+
idwbuff)
128129
end if
129130

130131
! 3D Patch Geometries =============================================

src/simulation/m_bubbles.fpp

Lines changed: 1 addition & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -58,15 +58,6 @@ contains
5858
subroutine s_initialize_bubbles_module
5959

6060
integer :: i, j, k, l, q
61-
type(int_bounds_info) :: ix, iy, iz
62-
63-
! Configuring Coordinate Direction Indexes =========================
64-
ix%beg = -buff_size; iy%beg = 0; iz%beg = 0
65-
66-
if (n > 0) iy%beg = -buff_size; if (p > 0) iz%beg = -buff_size
67-
68-
ix%end = m - ix%beg; iy%end = n - iy%beg; iz%end = p - iz%beg
69-
! ==================================================================
7061

7162
@:ALLOCATE_GLOBAL(rs(1:nb))
7263
@:ALLOCATE_GLOBAL(vs(1:nb))
@@ -89,7 +80,7 @@ contains
8980
!$acc update device(ps, ms)
9081
end if
9182

92-
@:ALLOCATE(divu%sf(ix%beg:ix%end, iy%beg:iy%end, iz%beg:iz%end))
83+
@:ALLOCATE(divu%sf(idwbuff(1)%beg:idwbuff(1)%end, idwbuff(2)%beg:idwbuff(2)%end, idwbuff(3)%beg:idwbuff(3)%end))
9384
@:ACC_SETUP_SFs(divu)
9485

9586
@:ALLOCATE_GLOBAL(bub_adv_src(0:m, 0:n, 0:p))

src/simulation/m_chemistry.fpp

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -17,10 +17,8 @@ module m_chemistry
1717

1818
implicit none
1919

20-
type(int_bounds_info), private :: ix, iy, iz
2120
type(scalar_field), private :: grads(1:3)
2221

23-
!$acc declare create(ix, iy, iz)
2422
!$acc declare create(grads)
2523

2624
contains
@@ -29,16 +27,11 @@ contains
2927

3028
integer :: i
3129

32-
ix%beg = -buff_size
33-
if (n > 0) then; iy%beg = -buff_size; else; iy%beg = 0; end if
34-
if (p > 0) then; iz%beg = -buff_size; else; iz%beg = 0; end if
35-
36-
ix%end = m - ix%beg; iy%end = n - iy%beg; iz%end = p - iz%beg
37-
38-
!$acc update device(ix, iy, iz)
39-
4030
do i = 1, 3
41-
@:ALLOCATE(grads(i)%sf(ix%beg:ix%end, iy%beg:iy%end, iz%beg:iz%end))
31+
@:ALLOCATE(grads(i)%sf(&
32+
& idwbuff(1)%beg:idwbuff(1)%end, &
33+
& idwbuff(2)%beg:idwbuff(2)%end, &
34+
& idwbuff(3)%beg:idwbuff(3)%end))
4235
end do
4336

4437
!$acc kernels

src/simulation/m_data_output.fpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -510,7 +510,7 @@ contains
510510
if (.not. file_exist) call s_create_directory(trim(t_step_dir))
511511

512512
if (prim_vars_wrt .or. (n == 0 .and. p == 0)) then
513-
call s_convert_conservative_to_primitive_variables(q_cons_vf, q_prim_vf)
513+
call s_convert_conservative_to_primitive_variables(q_cons_vf, q_prim_vf, idwbuff)
514514
do i = 1, sys_size
515515
!$acc update host(q_prim_vf(i)%sf(:,:,:))
516516
end do

src/simulation/m_global_parameters.fpp

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -238,6 +238,15 @@ module m_global_parameters
238238

239239
!$acc declare create(bub_idx)
240240

241+
! Cell Indices for the (local) interior points (O-m, O-n, 0-p).
242+
type(int_bounds_info) :: idwint(1:3)
243+
!$acc declare create(idwint)
244+
245+
! Cell Indices for the entire (local) domain. In simulation, this includes
246+
! the buffer region. idwbuff and idwint are the same otherwise.
247+
type(int_bounds_info) :: idwbuff(1:3)
248+
!$acc declare create(idwbuff)
249+
241250
!> @name The number of fluids, along with their identifying indexes, respectively,
242251
!! for which viscous effects, e.g. the shear and/or the volume Reynolds (Re)
243252
!! numbers, will be non-negligible.
@@ -702,8 +711,6 @@ contains
702711
integer :: i, j, k
703712
integer :: fac
704713

705-
type(int_bounds_info) :: ix, iy, iz
706-
707714
#:if not MFC_CASE_OPTIMIZATION
708715
! Determining the degree of the WENO polynomials
709716
weno_polyn = (weno_order - 1)/2
@@ -1037,18 +1044,27 @@ contains
10371044
end if
10381045

10391046
! Configuring Coordinate Direction Indexes =========================
1040-
if (bubbles) then
1041-
ix%beg = -buff_size; iy%beg = 0; iz%beg = 0
1042-
if (n > 0) then
1043-
iy%beg = -buff_size
1044-
if (p > 0) then
1045-
iz%beg = -buff_size
1046-
end if
1047-
end if
1047+
idwint(1)%beg = 0; idwint(2)%beg = 0; idwint(3)%beg = 0
1048+
idwint(1)%end = m; idwint(2)%end = n; idwint(3)%end = p
10481049

1049-
ix%end = m - ix%beg; iy%end = n - iy%beg; iz%end = p - iz%beg
1050+
idwbuff(1)%beg = -buff_size
1051+
if (num_dims > 1) then; idwbuff(2)%beg = -buff_size; else; idwbuff(2)%beg = 0; end if
1052+
if (num_dims > 2) then; idwbuff(3)%beg = -buff_size; else; idwbuff(3)%beg = 0; end if
10501053

1051-
@:ALLOCATE_GLOBAL(ptil(ix%beg:ix%end, iy%beg:iy%end, iz%beg:iz%end))
1054+
idwbuff(1)%end = idwint(1)%end - idwbuff(1)%beg
1055+
idwbuff(2)%end = idwint(2)%end - idwbuff(2)%beg
1056+
idwbuff(3)%end = idwint(3)%end - idwbuff(3)%beg
1057+
1058+
!$acc update device(idwint, idwbuff)
1059+
1060+
! ==================================================================
1061+
1062+
! Configuring Coordinate Direction Indexes =========================
1063+
if (bubbles) then
1064+
@:ALLOCATE_GLOBAL(ptil(&
1065+
& idwbuff(1)%beg:idwbuff(1)%end, &
1066+
& idwbuff(2)%beg:idwbuff(2)%end, &
1067+
& idwbuff(3)%beg:idwbuff(3)%end))
10521068
end if
10531069

10541070
if (probe_wrt) then

0 commit comments

Comments
 (0)