Time derivative of Euler field, the residuals function.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(euler_1D), | intent(in) | :: | self | Euler field. |
||
real(kind=R_P), | intent(in), | optional | :: | t | Time. |
Euler field time derivative.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module.
function dEuler_dt(self, t) result(dState_dt)
!---------------------------------------------------------------------------------------------------------------------------------
!< Time derivative of Euler field, the residuals function.
!---------------------------------------------------------------------------------------------------------------------------------
class(euler_1D), intent(IN) :: self !< Euler field.
real(R_P), optional, intent(IN) :: t !< Time.
class(integrand), allocatable :: dState_dt !< Euler field time derivative.
real(R_P), allocatable :: F(:,:) !< Fluxes of conservative variables.
real(R_P), allocatable :: P(:,:) !< Primitive variables.
real(R_P), allocatable :: PR(:,:,:) !< Left (1) and right (2) (reconstructed) interface values of primitive variables.
integer(I_P) :: i !< Counter.
!---------------------------------------------------------------------------------------------------------------------------------
!---------------------------------------------------------------------------------------------------------------------------------
associate (Ni=>self%Ni, Ng=>self%Ng, Nc=>self%Nc, Np=>self%Np, Ns=>self%Ns, U=>self%U, previous=>self%previous)
! allocate temporary arrays
allocate(F(1:Nc, 0:Ni)) ; F = 0._R_P
allocate(P(1:Np, 1-Ng:Ni+Ng)) ; P = 0._R_P
allocate(PR(1:Np, 1:2, 0:Ni+1)) ; PR = 0._R_P
! compute primitive variables
do i=1, Ni
P(:, i) = self%conservative2primitive(U(:, i))
enddo
call self%impose_boundary_conditions(primitive=P)
call self%reconstruct_interfaces_states(primitive=P, r_primitive=PR)
! compute fluxes by solving Rimeann Problems at each interface
do i=0, Ni
call self%riemann_solver(r1=PR(Ns+3, 2, i ), u1=PR(Ns+1, 2, i ), p1=PR(Ns+2, 2, i ), g1=PR(Ns+4, 2, i ), &
r4=PR(Ns+3, 1, i+1), u4=PR(Ns+1, 1, i+1), p4=PR(Ns+2, 1, i+1), g4=PR(Ns+4, 1, i+1), &
F=F(:, i))
if (Ns>1) then
if (F(1, i)>0._R_P) then
F(1:self%Ns, i) = PR(1:Ns, 2, i )/PR(Ns+3, 2, i )*F(1, i)
else
F(1:self%Ns, i) = PR(1:Ns, 1, i+1)/PR(Ns+3, 1, i+1)*F(1, i)
endif
endif
enddo
! compute residuals
allocate(euler_1D :: dState_dt)
select type(dState_dt)
class is(euler_1D)
dState_dt = self
do i=1, Ni
dState_dt%U(:, i) = (F(:, i - 1) - F(:, i)) / self%Dx
enddo
endselect
endassociate
return
!---------------------------------------------------------------------------------------------------------------------------------
endfunction dEuler_dt