SELF_MappedScalar_1D Module


Uses

  • module~~self_mappedscalar_1d~2~~UsesGraph module~self_mappedscalar_1d~2 SELF_MappedScalar_1D module~self_mappedscalar_1d_t SELF_MappedScalar_1D_t module~self_mappedscalar_1d~2->module~self_mappedscalar_1d_t iso_c_binding iso_c_binding module~self_mappedscalar_1d~2->iso_c_binding module~self_gpu~2 SELF_GPU module~self_mappedscalar_1d~2->module~self_gpu~2 module~self_mappedscalar_1d_t->iso_c_binding module~self_geometry_1d SELF_Geometry_1D module~self_mappedscalar_1d_t->module~self_geometry_1d module~self_lagrange~3 SELF_Lagrange module~self_mappedscalar_1d_t->module~self_lagrange~3 FEQParse FEQParse module~self_mappedscalar_1d_t->FEQParse module~self_constants SELF_Constants module~self_mappedscalar_1d_t->module~self_constants module~self_hdf5 SELF_HDF5 module~self_mappedscalar_1d_t->module~self_hdf5 HDF5 HDF5 module~self_mappedscalar_1d_t->HDF5 module~self_scalar_1d~3 SELF_Scalar_1D module~self_mappedscalar_1d_t->module~self_scalar_1d~3 module~self_mesh_1d SELF_Mesh_1D module~self_mappedscalar_1d_t->module~self_mesh_1d module~self_gpu~2->iso_c_binding module~self_gpu_enums~2 SELF_GPU_enums module~self_gpu~2->module~self_gpu_enums~2 module~self_geometry_1d->module~self_lagrange~3 module~self_geometry_1d->module~self_constants module~self_geometry_1d->module~self_scalar_1d~3 module~self_geometry_1d->module~self_mesh_1d module~self_supportroutines SELF_SupportRoutines module~self_geometry_1d->module~self_supportroutines module~self_data SELF_Data module~self_geometry_1d->module~self_data module~self_lagrange~3->iso_c_binding module~self_lagrange~3->module~self_constants iso_fortran_env iso_fortran_env module~self_lagrange~3->iso_fortran_env module~self_lagrange_t SELF_Lagrange_t module~self_lagrange~3->module~self_lagrange_t module~self_constants->iso_c_binding module~self_constants->iso_fortran_env module~self_hdf5->module~self_constants module~self_hdf5->HDF5 module~self_hdf5->iso_fortran_env mpi mpi module~self_hdf5->mpi module~self_scalar_1d_t SELF_Scalar_1D_t module~self_scalar_1d~3->module~self_scalar_1d_t module~self_mesh_1d->iso_c_binding module~self_mesh_1d->module~self_lagrange~3 module~self_mesh_1d->module~self_constants module~self_mesh_1d->module~self_hdf5 module~self_mesh_1d->HDF5 module~self_mesh_1d->module~self_scalar_1d~3 module~self_mesh_1d->module~self_supportroutines module~self_mesh SELF_Mesh module~self_mesh_1d->module~self_mesh module~self_mesh_1d->module~self_data module~self_gpu_enums~2->iso_c_binding module~self_supportroutines->module~self_constants module~self_supportroutines->iso_fortran_env module~self_scalar_1d_t->iso_c_binding module~self_scalar_1d_t->module~self_lagrange~3 module~self_scalar_1d_t->FEQParse module~self_scalar_1d_t->module~self_constants module~self_scalar_1d_t->module~self_hdf5 module~self_scalar_1d_t->HDF5 module~self_scalar_1d_t->module~self_data module~self_metadata SELF_Metadata module~self_scalar_1d_t->module~self_metadata module~self_mesh->iso_c_binding module~self_mesh->module~self_constants module~self_domaindecomposition SELF_DomainDecomposition module~self_mesh->module~self_domaindecomposition module~self_lagrange_t->iso_c_binding module~self_lagrange_t->module~self_constants module~self_lagrange_t->module~self_hdf5 module~self_lagrange_t->HDF5 module~self_lagrange_t->module~self_supportroutines module~self_lagrange_t->iso_fortran_env module~self_quadrature SELF_Quadrature module~self_lagrange_t->module~self_quadrature module~self_data->iso_c_binding module~self_data->module~self_lagrange~3 module~self_data->FEQParse module~self_data->module~self_constants module~self_data->module~self_hdf5 module~self_data->HDF5 module~self_data->module~self_metadata module~self_metadata->module~self_hdf5 module~self_metadata->HDF5 module~self_quadrature->module~self_constants module~self_quadrature->iso_fortran_env module~self_domaindecomposition_t SELF_DomainDecomposition_t module~self_domaindecomposition->module~self_domaindecomposition_t module~self_domaindecomposition_t->iso_c_binding module~self_domaindecomposition_t->module~self_lagrange~3 module~self_domaindecomposition_t->module~self_constants module~self_domaindecomposition_t->module~self_supportroutines module~self_domaindecomposition_t->mpi

Contents


Interfaces

interface

  • public subroutine DGDerivative_BoundaryContribution_1D_gpu(bMatrix, qWeights, bf, df, N, nVar, nEl) bind(c,name="0")

    Arguments

    TypeIntentOptionalAttributesName
    type(c_ptr), value:: bMatrix
    type(c_ptr), value:: qWeights
    type(c_ptr), value:: bf
    type(c_ptr), value:: df
    integer(kind=c_int), value:: N
    integer(kind=c_int), value:: nVar
    integer(kind=c_int), value:: nEl

interface

  • public subroutine JacobianWeight_1D_gpu(scalar, dxds, N, nVar, nEl) bind(c,name="0")

    Arguments

    TypeIntentOptionalAttributesName
    type(c_ptr), value:: scalar
    type(c_ptr), value:: dxds
    integer(kind=c_int), value:: N
    integer(kind=c_int), value:: nVar
    integer(kind=c_int), value:: nEl

Derived Types

type, public, extends(MappedScalar1D_t) :: MappedScalar1D

Components

TypeVisibilityAttributesNameInitial
integer, public :: M
integer, public :: N
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: avgBoundary
character(len=3), public :: backend ="cpu"
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: boundary
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: boundarynormal
type(EquationParser), public, allocatable:: eqn(:)
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: extBoundary
type(Geometry1D), public, pointer:: geometry=> null()
logical, public :: geometry_associated =.false.
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: interior
type(Lagrange), public, pointer:: interp
type(Metadata), public, allocatable:: meta(:)
integer, public :: nElem
integer, public :: nVar

Type-Bound Procedures

procedure, public :: AssociateGeometry => AssociateGeometry_MappedScalar1D_t
procedure, public :: AverageSides => AverageSides_Scalar1D_t
procedure, public :: BoundaryInterp => BoundaryInterp_Scalar1D_t
generic, public :: Derivative => Derivative_Scalar1D_t
procedure, public :: DissociateGeometry => DissociateGeometry_MappedScalar1D_t
procedure, public :: Free => Free_Scalar1D_t
generic, public :: GridInterp => GridInterp_Scalar1D_t
procedure, public :: Init => Init_Scalar1D_t
generic, public :: MappedDGDerivative => MappedDGDerivative_MappedScalar1D_t, MappedDGDerivative_MappedScalar1D
procedure, private :: MappedDGDerivative_MappedScalar1D
generic, public :: MappedDerivative => MappedDerivative_MappedScalar1D_t, MappedDerivative_MappedScalar1D
procedure, private :: MappedDerivative_MappedScalar1D
procedure, public :: SetDescription => SetDescription_DataObj
generic, public :: SetEquation => SetEquation_DataObj
procedure, public :: SetInteriorFromEquation => SetInteriorFromEquation_MappedScalar1D
procedure, public :: SetName => SetName_DataObj
procedure, public :: SetUnits => SetUnits_DataObj
procedure, public :: SideExchange => SideExchange_MappedScalar1D
procedure, public :: UpdateDevice => UpdateDevice_Scalar1D_t
procedure, public :: UpdateHost => UpdateHost_Scalar1D_t
generic, public :: WriteHDF5 => WriteHDF5_Scalar1D_t

Subroutines

public subroutine MappedDGDerivative_MappedScalar1D(this, df)

Arguments

TypeIntentOptionalAttributesName
class(MappedScalar1D), intent(in) :: this
type(c_ptr), intent(inout) :: df

public subroutine MappedDerivative_MappedScalar1D(this, df)

Arguments

TypeIntentOptionalAttributesName
class(MappedScalar1D), intent(in) :: this
type(c_ptr), intent(inout) :: df

public subroutine SetInteriorFromEquation_MappedScalar1D(this, time)

Sets the this % interior attribute using the eqn attribute, geometry (for physical positions), and provided simulation time.

Arguments

TypeIntentOptionalAttributesName
class(MappedScalar1D), intent(inout) :: this
real(kind=prec), intent(in) :: time

public subroutine SideExchange_MappedScalar1D(this, mesh)

Arguments

TypeIntentOptionalAttributesName
class(MappedScalar1D), intent(inout) :: this
type(Mesh1D), intent(inout) :: mesh