m_variables_conversion Module

@file m_variables_conversion.f90 @brief Contains module m_variables_conversion @author S. Bryngelson, K. Schimdmayer, V. Coralic, J. Meng, K. Maeda, T. Colonius @version 1.0 @date JUNE 06 2019 @brief This module features a database of subroutines that allow for the conversion of state variables from one type into another. At this time, the state variables type conversions below are available: 1) Mixture => Mixture 2) Species => Mixture 3) Conservative => Primitive 5) Conservative => Flux 6) Primitive => Conservative 8) Primitive => Flux


Uses

  • module~~m_variables_conversion~~UsesGraph module~m_variables_conversion m_variables_conversion module~m_global_parameters m_global_parameters module~m_variables_conversion->module~m_global_parameters m_derived_types m_derived_types module~m_variables_conversion->m_derived_types module~m_mpi_proxy m_mpi_proxy module~m_variables_conversion->module~m_mpi_proxy module~nvtx nvtx module~m_variables_conversion->module~nvtx module~m_global_parameters->m_derived_types openacc openacc module~m_global_parameters->openacc mpi mpi module~m_global_parameters->mpi module~m_mpi_proxy->module~m_global_parameters module~m_mpi_proxy->m_derived_types module~m_mpi_proxy->mpi iso_c_binding iso_c_binding module~nvtx->iso_c_binding

Used by

  • module~~m_variables_conversion~~UsedByGraph module~m_variables_conversion m_variables_conversion module~m_bubbles m_bubbles module~m_bubbles->module~m_variables_conversion program~p_main p_main program~p_main->module~m_variables_conversion module~m_start_up m_start_up program~p_main->module~m_start_up module~m_riemann_solvers m_riemann_solvers program~p_main->module~m_riemann_solvers module~m_qbmm m_qbmm program~p_main->module~m_qbmm module~m_rhs m_rhs program~p_main->module~m_rhs module~m_time_steppers m_time_steppers program~p_main->module~m_time_steppers module~m_derived_variables m_derived_variables program~p_main->module~m_derived_variables module~m_start_up->module~m_variables_conversion module~m_riemann_solvers->module~m_variables_conversion module~m_riemann_solvers->module~m_bubbles module~m_qbmm->module~m_variables_conversion module~m_rhs->module~m_variables_conversion module~m_rhs->module~m_bubbles module~m_rhs->module~m_riemann_solvers module~m_rhs->module~m_qbmm module~m_time_steppers->module~m_bubbles module~m_time_steppers->module~m_rhs module~m_derived_variables->module~m_time_steppers

Contents


Variables

TypeVisibilityAttributesNameInitial
procedure(s_convert_abstract_to_mixture_variables), public, pointer:: s_convert_to_mixture_variables=> null()

Pointer to the procedure utilized to convert either the mixture or the species variables into the mixture variables, based on model equations


Subroutines

public subroutine s_convert_mixture_to_mixture_variables(qK_vf, rho_K, gamma_K, pi_inf_K, Re_K, i, j, k)

This procedure is used alongside with the gamma/pi_inf model to transfer the density, the specific heat ratio function and liquid stiffness function from the vector of conservative or primitive variables to their scalar counterparts. @param qK_vf conservative or primitive variables @param i cell index to transfer mixture variables @param j cell index to transfer mixture variables @param k cell index to transfer mixture variables @param rho_K density @param gamma_K specific heat ratio function @param pi_inf_K liquid stiffness @param Re_k Reynolds number

Arguments

TypeIntentOptionalAttributesName
type(scalar_field), intent(in), dimension(sys_size):: qK_vf
real(kind=kind(0d0)), intent(out) :: rho_K
real(kind=kind(0d0)), intent(out) :: gamma_K
real(kind=kind(0d0)), intent(out) :: pi_inf_K
real(kind=kind(0d0)), intent(out), dimension(2):: Re_K
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: k

public subroutine s_convert_species_to_mixture_variables_bubbles(qK_vf, rho_K, gamma_K, pi_inf_K, Re_K, i, j, k)

This procedure is used alongside with the gamma/pi_inf model to transfer the density, the specific heat ratio function and liquid stiffness function from the vector of conservative or primitive variables to their scalar counterparts. Specifially designed for when subgrid bubbles must be included. @param qK_vf primitive variables @param rho_K density @param gamma_K specific heat ratio @param pi_inf_K liquid stiffness @param Re_K mixture Reynolds number @param i Cell index @param j Cell index @param k Cell index

Arguments

TypeIntentOptionalAttributesName
type(scalar_field), intent(in), dimension(sys_size):: qK_vf
real(kind=kind(0d0)), intent(out) :: rho_K
real(kind=kind(0d0)), intent(out) :: gamma_K
real(kind=kind(0d0)), intent(out) :: pi_inf_K
real(kind=kind(0d0)), intent(out), dimension(2):: Re_K
integer, intent(in) :: i
integer, intent(in) :: j
integer, intent(in) :: k

public subroutine s_convert_species_to_mixture_variables(qK_vf, rho_K, gamma_K, pi_inf_K, Re_K, k, l, r)

This subroutine is designed for the volume fraction model and provided a set of either conservative or primitive variables, computes the density, the specific heat ratio function and the liquid stiffness function from q_vf and stores the results into rho, gamma and pi_inf. @param qK_vf primitive variables @param rho_K density @param gamma_K specific heat ratio @param pi_inf_K liquid stiffness @param Re_K mixture Reynolds number @param k Cell index @param l Cell index @param r Cell index

Arguments

TypeIntentOptionalAttributesName
type(scalar_field), intent(in), dimension(sys_size):: qK_vf
real(kind=kind(0d0)), intent(out) :: rho_K
real(kind=kind(0d0)), intent(out) :: gamma_K
real(kind=kind(0d0)), intent(out) :: pi_inf_K
real(kind=kind(0d0)), intent(out), dimension(2):: Re_K
integer, intent(in) :: k
integer, intent(in) :: l
integer, intent(in) :: r

public subroutine s_convert_species_to_mixture_variables_acc(rho_K, gamma_K, pi_inf_K, alpha_K, alpha_rho_K, Re_K, k, l, r)

Arguments

TypeIntentOptionalAttributesName
real(kind=kind(0d0)), intent(out) :: rho_K
real(kind=kind(0d0)), intent(out) :: gamma_K
real(kind=kind(0d0)), intent(out) :: pi_inf_K
real(kind=kind(0d0)), intent(inout), dimension(:):: alpha_K
real(kind=kind(0d0)), intent(inout), dimension(:):: alpha_rho_K
real(kind=kind(0d0)), intent(out), dimension(:):: Re_K

Partial densities and volume fractions

integer, intent(in) :: k
integer, intent(in) :: l
integer, intent(in) :: r

public subroutine s_convert_species_to_mixture_variables_bubbles_acc(rho_K, gamma_K, pi_inf_K, alpha_K, alpha_rho_K, k, l, r)

Arguments

TypeIntentOptionalAttributesName
real(kind=kind(0d0)), intent(inout) :: rho_K
real(kind=kind(0d0)), intent(inout) :: gamma_K
real(kind=kind(0d0)), intent(inout) :: pi_inf_K
real(kind=kind(0d0)), intent(in), dimension(:):: alpha_K

Partial densities and volume fractions

real(kind=kind(0d0)), intent(in), dimension(:):: alpha_rho_K

Partial densities and volume fractions

integer, intent(in) :: k
integer, intent(in) :: l
integer, intent(in) :: r

The computation of parameters, the allocation of memory, the association of pointers and/or the execution of any other procedures that are necessary to setup the module.

Arguments

None

public subroutine s_convert_conservative_to_primitive_variables(qK_cons_vf, qK_prim_vf, gm_alphaK_vf, ix, iy, iz)

The following procedure handles the conversion between the conservative variables and the primitive variables. @param qK_cons_vf Conservative variables @param qK_prim_vf Primitive variables @param gm_alphaK_vf Gradient magnitude of the volume fraction @param ix Index bounds in first coordinate direction @param iy Index bounds in second coordinate direction @param iz Index bounds in third coordinate direction

Arguments

TypeIntentOptionalAttributesName
type(scalar_field), intent(inout), dimension(sys_size):: qK_cons_vf
type(scalar_field), intent(inout), dimension(sys_size):: qK_prim_vf
type(scalar_field), intent(in), allocatable, dimension(:):: gm_alphaK_vf
type(int_bounds_info), intent(in) :: ix
type(int_bounds_info), intent(in) :: iy
type(int_bounds_info), intent(in) :: iz

public subroutine s_convert_primitive_to_conservative_variables(qK_prim_vf, qK_cons_vf, gm_alphaK_vf, ix, iy, iz)

The following procedure handles the conversion between the primitive variables and the conservative variables. @param qK_prim_vf Primitive variables @param qK_cons_vf Conservative variables @param gm_alphaK_vf Gradient magnitude of the volume fractions @param ix Index bounds in the first coordinate direction @param iy Index bounds in the second coordinate direction @param iz Index bounds in the third coordinate direction

Arguments

TypeIntentOptionalAttributesName
type(scalar_field), intent(in), dimension(sys_size):: qK_prim_vf
type(scalar_field), intent(inout), dimension(sys_size):: qK_cons_vf
type(scalar_field), intent(in), allocatable, dimension(:):: gm_alphaK_vf
type(int_bounds_info), intent(in) :: ix
type(int_bounds_info), intent(in) :: iy
type(int_bounds_info), intent(in) :: iz

public subroutine s_convert_primitive_to_flux_variables(qK_prim_vf, FK_vf, FK_src_vf, is1, is2, is3, s2b, s3b)

The following subroutine handles the conversion between the primitive variables and the Eulerian flux variables. @param qK_prim_vf Primitive variables @param FK_vf Flux variables @param FK_src_vf Flux source variables @param ix Index bounds in the first coordinate direction @param iy Index bounds in the second coordinate direction @param iz Index bounds in the third coordinate direction

Arguments

TypeIntentOptionalAttributesName
real(kind=kind(0d0)), intent(in), dimension(0:, s2b:, s3b:, 1:):: qK_prim_vf
real(kind=kind(0d0)), intent(inout), dimension(0:, s2b:, s3b:, 1:):: FK_vf
real(kind=kind(0d0)), intent(inout), dimension(0:, s2b:, s3b:, advxb:):: FK_src_vf
type(int_bounds_info), intent(in) :: is1
type(int_bounds_info), intent(in) :: is2
type(int_bounds_info), intent(in) :: is3
integer :: s2b
integer :: s3b

Arguments

None