Skip to content

Commit a2b0637

Browse files
authored
Merge pull request #66 from anshgupta1234/fix_65
2 parents 2f05478 + a616866 commit a2b0637

File tree

1 file changed

+49
-85
lines changed

1 file changed

+49
-85
lines changed

src/common/m_variables_conversion.fpp

Lines changed: 49 additions & 85 deletions
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ module m_variables_conversion
101101
real(kind(0d0)) :: pres_avg !< averaging for bubble mixture speed of sound
102102
!> @}
103103

104-
integer :: ixb, ixe, iyb, iye, izb, ize
104+
integer, public :: ixb, ixe, iyb, iye, izb, ize
105105
!$acc declare create(ixb, ixe, iyb, iye, izb, ize)
106106

107107
!! In simulation, gammas and pi_infs is already declared in m_global_variables
@@ -134,76 +134,7 @@ module m_variables_conversion
134134

135135
contains
136136

137-
!> This procedure calculates the pressure based on energy when
138-
!! there are no bubbles present and model_eqns != 4
139-
!! @param energy Energy
140-
!! @param alf Void Fraction
141-
!! @param dyn_p Dynamic Pressure
142-
!! @param pi_inf Liquid Stiffness
143-
!! @param gamma Specific Heat Ratio
144-
!! @param pres Pressure to calculate
145-
subroutine s_compute_pressure_from_energy(energy, alf, dyn_p, pi_inf, gamma, pres)
146-
!$acc routine seq
147-
148-
real(kind(0d0)) :: energy, alf
149-
150-
real(kind(0d0)), intent(IN) :: dyn_p
151-
real(kind(0d0)), intent(OUT) :: pres
152-
153-
real(kind(0d0)) :: pi_inf, gamma
154-
155-
pres = (energy - dyn_p - pi_inf)/gamma
156-
157-
end subroutine s_compute_pressure_from_energy
158-
159-
!> This procedure calculates the pressure when there
160-
!! are bubbles present and model_eqns != 4
161-
!! @param energy Energy
162-
!! @param alf Void Fraction
163-
!! @param dyn_p Dynamic Pressure
164-
!! @param pi_inf Liquid Stiffness
165-
!! @param gamma Specific Heat Ratio
166-
!! @param pres Pressure to calculate
167-
subroutine s_compute_pressure_from_bubbles(energy, alf, dyn_p, pi_inf, gamma, pres)
168-
!$acc routine seq
169-
170-
real(kind(0d0)) :: energy, alf
171-
172-
real(kind(0d0)), intent(IN) :: dyn_p
173-
real(kind(0d0)), intent(OUT) :: pres
174-
175-
real(kind(0d0)) :: pi_inf, gamma
176-
177-
pres = ((energy - dyn_p)/(1.d0 - alf) - pi_inf)/gamma
178-
179-
end subroutine s_compute_pressure_from_bubbles
180-
181-
!> This procedure calculates the pressure when model_eqns = 4
182-
!! @param energy Energy
183-
!! @param alf Void Fraction
184-
!! @param dyn_p Dynamic Pressure
185-
!! @param pi_inf Liquid Stiffness
186-
!! @param gamma Specific Heat Ratio
187-
!! @param pres Pressure to calculate
188-
subroutine s_compute_pressure_4eqns(energy, alf, dyn_p, pi_inf, gamma, pres)
189-
!$acc routine seq
190-
191-
real(kind(0d0)) :: energy, alf
192-
193-
real(kind(0d0)), intent(IN) :: dyn_p
194-
real(kind(0d0)), intent(OUT) :: pres
195-
196-
real(kind(0d0)) :: pi_inf, gamma
197-
198-
pres = (pref + pi_inf)* &
199-
(energy/ &
200-
(rhoref*(1 - alf)) &
201-
)**(1/gamma + 1) - pi_inf
202-
203-
end subroutine s_compute_pressure_4eqns
204-
205-
!> This procedure conditionally calls the appropriate pressure-computing
206-
!! subroutine.
137+
!> This procedure conditionally calculates the appropriate pressure
207138
!! @param energy Energy
208139
!! @param alf Void Fraction
209140
!! @param dyn_p Dynamic Pressure
@@ -224,11 +155,14 @@ contains
224155
! for computing pressure is targeted by the procedure pointer
225156

226157
if ((model_eqns /= 4) .and. (bubbles .neqv. .true.)) then
227-
call s_compute_pressure_from_energy(energy, alf, dyn_p, pi_inf, gamma, pres)
158+
pres = (energy - dyn_p - pi_inf)/gamma
228159
else if ((model_eqns /= 4) .and. bubbles) then
229-
call s_compute_pressure_from_bubbles(energy, alf, dyn_p, pi_inf, gamma, pres)
160+
pres = ((energy - dyn_p)/(1.d0 - alf) - pi_inf)/gamma
230161
else
231-
call s_compute_pressure_4eqns(energy, alf, dyn_p, pi_inf, gamma, pres)
162+
pres = (pref + pi_inf)* &
163+
(energy/ &
164+
(rhoref*(1 - alf)) &
165+
)**(1/gamma + 1) - pi_inf
232166
end if
233167

234168
end subroutine s_compute_pressure
@@ -264,9 +198,10 @@ contains
264198
real(kind(0d0)), pointer :: rho_K, gamma_K, pi_inf_K
265199

266200
!> Post process requires rho_sf/gamma_sf/pi_inf_sf to be
267-
!! updated instead of rho/gamma/pi_inf. Therefore, the
201+
!! updated alongside of rho/gamma/pi_inf. Therefore, the
268202
!! versions of these variables appended with '_K' represent
269-
!! pointers that target the correct variable.
203+
!! pointers that target the correct variable. At the end,
204+
!! rho/gamma/pi_inf are updated for post process.
270205
#ifdef MFC_POST_PROCESS
271206
rho_K => rho_sf(i, j, k)
272207
gamma_K => gamma_sf(i, j, k)
@@ -283,6 +218,12 @@ contains
283218
gamma_K = q_vf(gamma_idx)%sf(i, j, k)
284219
pi_inf_K = q_vf(pi_inf_idx)%sf(i, j, k)
285220

221+
#ifdef MFC_POST_PROCESS
222+
rho = rho_K
223+
gamma = gamma_K
224+
pi_inf = pi_inf_K
225+
#endif
226+
286227
end subroutine s_convert_mixture_to_mixture_variables ! ----------------
287228

288229
!> This procedure is used alongside with the gamma/pi_inf
@@ -319,9 +260,10 @@ contains
319260
real(kind(0d0)), pointer :: rho_K, gamma_K, pi_inf_K
320261

321262
!> Post process requires rho_sf/gamma_sf/pi_inf_sf to be
322-
!! updated instead of rho/gamma/pi_inf. Therefore, the
263+
!! updated alongside of rho/gamma/pi_inf. Therefore, the
323264
!! versions of these variables appended with '_K' represent
324-
!! pointers that target the correct variable.
265+
!! pointers that target the correct variable. At the end,
266+
!! rho/gamma/pi_inf are updated for post process.
325267
#ifdef MFC_POST_PROCESS
326268
rho_K => rho_sf(j, k, l)
327269
gamma_K => gamma_sf(j, k, l)
@@ -376,6 +318,12 @@ contains
376318
end if
377319
end if
378320

321+
#ifdef MFC_POST_PROCESS
322+
rho = rho_K
323+
gamma = gamma_K
324+
pi_inf = pi_inf_K
325+
#endif
326+
379327
end subroutine s_convert_species_to_mixture_variables_bubbles ! ----------------
380328

381329
!> This subroutine is designed for the volume fraction model
@@ -414,9 +362,10 @@ contains
414362
real(kind(0d0)), pointer :: rho_K, gamma_K, pi_inf_K
415363

416364
!> Post process requires rho_sf/gamma_sf/pi_inf_sf to be
417-
!! updated instead of rho/gamma/pi_inf. Therefore, the
365+
!! updated alongside of rho/gamma/pi_inf. Therefore, the
418366
!! versions of these variables appended with '_K' represent
419-
!! pointers that target the correct variable.
367+
!! pointers that target the correct variable. At the end,
368+
!! rho/gamma/pi_inf are updated for post process.
420369
#ifdef MFC_POST_PROCESS
421370
rho_K => rho_sf(k, l, r)
422371
gamma_K => gamma_sf(k, l, r)
@@ -480,6 +429,12 @@ contains
480429
G_K = max(0d0, G_K)
481430
end if
482431

432+
#ifdef MFC_POST_PROCESS
433+
rho = rho_K
434+
gamma = gamma_K
435+
pi_inf = pi_inf_K
436+
#endif
437+
483438
end subroutine s_convert_species_to_mixture_variables ! ----------------
484439

485440
subroutine s_convert_species_to_mixture_variables_acc(rho_K, &
@@ -746,7 +701,7 @@ contains
746701
gm_alphaK_vf, &
747702
ix, iy, iz)
748703

749-
type(scalar_field), dimension(sys_size), intent(INOUT) :: qK_cons_vf
704+
type(scalar_field), dimension(sys_size), intent(IN) :: qK_cons_vf
750705
type(scalar_field), dimension(sys_size), intent(INOUT) :: qK_prim_vf
751706

752707
type(scalar_field), &
@@ -786,6 +741,10 @@ contains
786741
alpha_K(i) = qK_cons_vf(advxb + i - 1)%sf(j, k, l)
787742
end do
788743

744+
do i = 1, contxe
745+
qK_prim_vf(i)%sf(j, k, l) = qK_cons_vf(i)%sf(j, k, l)
746+
end do
747+
789748
if (model_eqns /= 4) then
790749
#ifdef MFC_SIMULATION
791750
! If in simulation, use acc mixture subroutines
@@ -814,6 +773,7 @@ contains
814773
#ifdef MFC_SIMULATION
815774
rho_K = max(rho_K, sgm_eps)
816775
#endif
776+
817777
!$acc loop seq
818778
do i = momxb, momxe
819779
if (model_eqns /= 4) then
@@ -826,10 +786,10 @@ contains
826786
/qK_cons_vf(1)%sf(j, k, l)
827787
end if
828788
end do
829-
830789
call s_compute_pressure(qK_cons_vf(E_idx)%sf(j, k, l), &
831790
qK_cons_vf(alf_idx)%sf(j, k, l), &
832791
dyn_pres_K, pi_inf_K, gamma_K, pres)
792+
833793
qK_prim_vf(E_idx)%sf(j, k, l) = pres
834794

835795
if (bubbles) then
@@ -867,6 +827,10 @@ contains
867827
end if
868828
end do
869829
end if
830+
831+
do i = advxb, advxe
832+
qK_prim_vf(i)%sf(j, k, l) = qK_cons_vf(i)%sf(j, k, l)
833+
end do
870834
end do
871835
end do
872836
end do
@@ -919,7 +883,7 @@ contains
919883
rho, gamma, pi_inf)
920884

921885
! Transferring the continuity equation(s) variable(s)
922-
do i = 1, cont_idx%end
886+
do i = 1, contxe
923887
q_cons_vf(i)%sf(j, k, l) = q_prim_vf(i)%sf(j, k, l)
924888
end do
925889

@@ -928,7 +892,7 @@ contains
928892
dyn_pres = 0d0
929893

930894
! Computing momenta and dynamic pressure from velocity
931-
do i = mom_idx%beg, mom_idx%end
895+
do i = momxb, momxe
932896
q_cons_vf(i)%sf(j, k, l) = rho*q_prim_vf(i)%sf(j, k, l)
933897
dyn_pres = dyn_pres + q_cons_vf(i)%sf(j, k, l)* &
934898
q_prim_vf(i)%sf(j, k, l)/2d0
@@ -1170,4 +1134,4 @@ contains
11701134

11711135
end subroutine s_finalize_variables_conversion_module ! ----------------
11721136

1173-
end module m_variables_conversion
1137+
end module m_variables_conversion

0 commit comments

Comments
 (0)