Skip to content

Commit 30c4f8f

Browse files
committed
push for testing
1 parent e69c4ef commit 30c4f8f

File tree

1 file changed

+26
-30
lines changed

1 file changed

+26
-30
lines changed

src/simulation/m_riemann_solvers.fpp

Lines changed: 26 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -2784,10 +2784,32 @@ contains
27842784
E_starR = ((s_R - vel%R(1))*E%R - pTot_R*vel%R(1) + p_star*s_M)/(s_R - s_M)
27852785

27862786
! (5) Compute left/right state vectors and fluxes
2787-
call s_compute_hlld_state_variables(rho%L, vel%L, B%L, E%L, pTot_L, rhoL_star, s_M, E_starL, s_L, &
2788-
U_L, F_L, U_starL, F_starL, sqrt_rhoL_star, vL_star, wL_star)
2789-
call s_compute_hlld_state_variables(rho%R, vel%R, B%R, E%R, pTot_R, rhoR_star, s_M, E_starR, s_R, &
2790-
U_R, F_R, U_starR, F_starR, sqrt_rhoR_star, vR_star, wR_star)
2787+
U_L = [rho%L, rho%L*vel%L(1:3), B%L(2:3), E%L]
2788+
U_starL = [rhoL_star, rhoL_star*s_M, rhoL_star*vel%L(2:3), B%L(2:3), E_starL]
2789+
U_R = [rho%R, rho%R*vel%R(1:3), B%R(2:3), E%R]
2790+
U_starR = [rhoR_star, rhoR_star*s_M, rhoR_star*vel%R(2:3), B%R(2:3), E_starR]
2791+
2792+
F_L(1) = U_L(2)
2793+
F_L(2) = U_L(2)*vel%L(1) - B%L(1)*B%L(1) + pTot_L
2794+
F_L(3:4) = U_L(2)*vel%L(2:3) - B%L(1)*B%L(2:3)
2795+
F_L(5:6) = vel%L(1)*B%L(2:3) - vel%L(2:3)*B%L(1)
2796+
F_L(7) = (E%L + pTot_L)*vel%L(1) - B%L(1)*(vel%L(1)*B%L(1) + vel%L(2)*B%L(2) + vel%L(3)*B%L(3))
2797+
2798+
F_R(1) = U_R(2)
2799+
F_R(2) = U_R(2)*vel%R(1) - B%R(1)*B%R(1) + pTot_R
2800+
F_R(3:4) = U_R(2)*vel%R(2:3) - B%R(1)*B%R(2:3)
2801+
F_R(5:6) = vel%R(1)*B%R(2:3) - vel%R(2:3)*B%R(1)
2802+
F_R(7) = (E%R + pTot_R)*vel%R(1) - B%R(1)*(vel%R(1)*B%R(1) + vel%R(2)*B%R(2) + vel%R(3)*B%R(3))
2803+
! Compute the star flux using HLL relation
2804+
F_starL = F_L + s_M*(U_starL - U_L)
2805+
F_starR = F_R + s_M*(U_starR - U_R)
2806+
! Compute the rotational (Alfvén) speeds
2807+
s_starL = s_M - abs(B%L(1))/sqrt(rhoL_star)
2808+
s_starR = s_M + abs(B%L(1))/sqrt(rhoR_star)
2809+
! Compute the double–star states [Miyoshi Eqns. (59)-(62)]
2810+
sqrt_rhoL_star = sqrt(rhoL_star); sqrt_rhoR_star = sqrt(rhoR_star)
2811+
vL_star = vel%L(2); wL_star = vel%L(3)
2812+
vR_star = vel%R(2); wR_star = vel%R(3)
27912813

27922814
! (6) Compute the double–star states [Miyoshi Eqns. (59)-(62)]
27932815
denom_ds = sqrt_rhoL_star + sqrt_rhoR_star
@@ -2851,34 +2873,8 @@ contains
28512873

28522874
call s_finalize_riemann_solver(flux_vf, flux_src_vf, flux_gsrc_vf, &
28532875
norm_dir, ix, iy, iz)
2854-
28552876
end subroutine s_hlld_riemann_solver
28562877

2857-
subroutine s_compute_hlld_state_variables(rho, vel, B, E, pTot, rho_star, s_M, E_star, s_wave, &
2858-
U, F, U_star, F_star, sqrt_rho_star, v_star, w_star)
2859-
implicit none
2860-
! Input parameters
2861-
real(wp), intent(in) :: rho, pTot, rho_star, s_M, E_star, s_wave, E
2862-
real(wp), dimension(:), intent(in) :: vel, B
2863-
! Output parameters
2864-
real(wp), dimension(7), intent(out) :: U, F, U_star, F_star
2865-
real(wp), intent(out) :: sqrt_rho_star, v_star, w_star
2866-
! Compute the base/star state vector
2867-
U = [rho, rho*vel(1:3), B(2:3), E]
2868-
U_star = [rho_star, rho_star*s_M, rho_star*vel(2:3), B(2:3), E_star]
2869-
! Compute the flux vector
2870-
F(1) = U(2)
2871-
F(2) = U(2)*vel(1) - B(1)*B(1) + pTot
2872-
F(3:4) = U(2)*vel(2:3) - B(1)*B(2:3)
2873-
F(5:6) = vel(1)*B(2:3) - vel(2:3)*B(1)
2874-
F(7) = (E + pTot)*vel(1) - B(1)*(vel(1)*B(1) + vel(2)*B(2) + vel(3)*B(3))
2875-
! Compute the star flux using HLL relation
2876-
F_star = F + s_wave*(U_star - U)
2877-
! Compute additional parameters needed for double-star states
2878-
sqrt_rho_star = sqrt(rho_star)
2879-
v_star = vel(2)
2880-
w_star = vel(3)
2881-
end subroutine s_compute_hlld_state_variables
28822878

28832879
!> The computation of parameters, the allocation of memory,
28842880
!! the association of pointers and/or the execution of any

0 commit comments

Comments
 (0)