DGModel1D Derived Type

type, public, extends(DGModel1D_t) :: DGModel1D


Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
type(MappedScalar1D), public :: dSdt
real(kind=prec), public :: dt
real(kind=prec), public :: entropy
type(MappedScalar1D), public :: flux
type(MappedScalar1D), public :: fluxDivergence
type(Geometry1D), public, pointer:: geometry
logical, public :: gradient_enabled =.false.
integer, public :: ioIterate =0
type(Mesh1D), public, pointer:: mesh
integer, public :: nvar
type(MappedScalar1D), public :: solution
type(MappedScalar1D), public :: solutionGradient
type(MappedScalar1D), public :: source
real(kind=prec), public :: t
procedure(SELF_timeIntegrator), public, pointer:: timeIntegrator=> Euler_timeIntegrator
type(MappedScalar1D), public :: workSol

Type-Bound Procedures

procedure, public :: BoundaryFlux => BoundaryFlux_DGModel1D

procedure, public :: CalculateEntropy => CalculateEntropy_DGModel1D

procedure, public :: CalculateSolutionGradient => CalculateSolutionGradient_DGModel1D

procedure, public :: CalculateTendency => CalculateTendency_DGModel1D

procedure, public :: Euler_timeIntegrator

  • public subroutine Euler_timeIntegrator(this, tn)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: tn

procedure, public :: FluxMethod => fluxmethod_DGModel1D

procedure, public :: ForwardStep => ForwardStep_Model

  • public subroutine ForwardStep_Model(this, tn, dt, ioInterval)

    Forward steps the model using the associated tendency procedure and time integrator

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: tn
    real(kind=prec), intent(in) :: dt
    real(kind=prec), intent(in) :: ioInterval

procedure, public :: Free => Free_DGModel1D_t

procedure, public :: GetSimulationTime

  • public subroutine GetSimulationTime(this, t)

    Returns the current simulation time stored in the model % t attribute

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(out) :: t

procedure, public :: IncrementIOCounter

  • public subroutine IncrementIOCounter(this)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this

procedure, public :: Init => Init_DGModel1D_t

  • public subroutine Init_DGModel1D_t(this, nvar, mesh, geometry)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(out) :: this
    integer, intent(in) :: nvar
    type(Mesh1D), intent(in), target:: mesh
    type(Geometry1D), intent(in), target:: geometry

procedure, public :: LowStorageRK2_timeIntegrator

  • public subroutine LowStorageRK2_timeIntegrator(this, tn)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: tn

procedure, public :: LowStorageRK3_timeIntegrator

  • public subroutine LowStorageRK3_timeIntegrator(this, tn)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: tn

procedure, public :: LowStorageRK4_timeIntegrator

  • public subroutine LowStorageRK4_timeIntegrator(this, tn)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: tn

procedure, public :: PreTendency => PreTendency_Model

  • public subroutine PreTendency_Model(this)

    PreTendency is a template routine that is used to house any additional calculations that you want to execute at the beginning of the tendency calculation routine. This default PreTendency simply returns back to the caller without executing any instructions

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this

procedure, public :: PrintType => PrintType_Model

  • public subroutine PrintType_Model(this)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this

procedure, public :: ReadModel => Read_DGModel1D_t

  • public subroutine Read_DGModel1D_t(this, fileName)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(inout) :: this
    character, intent(in) :: fileName

procedure, public :: ReportEntropy => ReportEntropy_Model

  • public subroutine ReportEntropy_Model(this)

    Base method for reporting the entropy of a model to stdout. Only override this procedure if additional reporting is needed. Alternatively, if you think additional reporting would be valuable for all models, open a pull request with modifications to this base method.

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this

procedure, public :: SetBoundaryCondition => setboundarycondition_DGModel1D

procedure, public :: SetGradientBoundaryCondition => setgradientboundarycondition_DGModel1D

procedure, public :: SetMetadata => SetMetadata_DGModel1D_t

procedure, public :: SetSimulationTime

  • public subroutine SetSimulationTime(this, t)

    Sets the model % t attribute with the provided simulation time

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    real(kind=prec), intent(in) :: t
  • public subroutine SetSolutionFromChar_DGModel1D_t(this, eqnChar)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(inout) :: this
    character(len=SELF_EQUATION_LENGTH), intent(in) :: eqnChar(1:this%solution%nVar)
  • public subroutine SetSolutionFromEqn_DGModel1D_t(this, eqn)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(inout) :: this
    type(EquationParser), intent(in) :: eqn(1:this%solution%nVar)

generic, public :: SetTimeIntegrator => SetTimeIntegrator_withChar

  • public subroutine SetTimeIntegrator_withChar(this, integrator)

    Sets the time integrator method, using a character input

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    character, intent(in) :: integrator

procedure, public :: SourceMethod => sourcemethod_DGModel1D

procedure, public :: UpdateGRK2 => UpdateGRK2_DGModel1D

  • public subroutine UpdateGRK2_DGModel1D(this, m)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D), intent(inout) :: this
    integer, intent(in) :: m

procedure, public :: UpdateGRK3 => UpdateGRK3_DGModel1D

  • public subroutine UpdateGRK3_DGModel1D(this, m)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D), intent(inout) :: this
    integer, intent(in) :: m

procedure, public :: UpdateGRK4 => UpdateGRK4_DGModel1D

  • public subroutine UpdateGRK4_DGModel1D(this, m)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D), intent(inout) :: this
    integer, intent(in) :: m

procedure, public :: UpdateSolution => UpdateSolution_DGModel1D

  • public subroutine UpdateSolution_DGModel1D(this, dt)

    Computes a solution update as , where dt is either provided through the interface or taken as the Model's stored time step size (model % dt)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D), intent(inout) :: this
    real(kind=prec), intent(in), optional :: dt

procedure, public :: WriteModel => Write_DGModel1D_t

  • public subroutine Write_DGModel1D_t(this, fileName)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(inout) :: this
    character, intent(in), optional :: fileName

procedure, public :: WriteTecplot => WriteTecplot_DGModel1D_t

  • public subroutine WriteTecplot_DGModel1D_t(this, filename)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel1D_t), intent(inout) :: this
    character, intent(in), optional :: filename

procedure, public :: entropy_func => entropy_func_Model

  • public pure function entropy_func_Model(this, s) result(e)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)

    Return Value real(kind=prec)

procedure, public :: flux1D => flux1d_Model

  • public pure function flux1d_Model(this, s, dsdx) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: flux2D => flux2d_Model

  • public pure function flux2d_Model(this, s, dsdx) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:2)

    Return Value real(kind=prec)(1:this%nvar,1:2)

procedure, public :: flux3D => flux3d_Model

  • public pure function flux3d_Model(this, s, dsdx) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:3)

    Return Value real(kind=prec)(1:this%nvar,1:3)

procedure, public :: hbc1d_NoNormalFlow => hbc1d_Generic_Model

  • public pure function hbc1d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc1d_Prescribed => hbc1d_Prescribed_Model

  • public pure function hbc1d_Prescribed_Model(this, x, t) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc1d_Radiation => hbc1d_Generic_Model

  • public pure function hbc1d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc2d_NoNormalFlow => hbc2d_Generic_Model

  • public pure function hbc2d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat(1:2)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc2d_Prescribed => hbc2d_Prescribed_Model

  • public pure function hbc2d_Prescribed_Model(this, x, t) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x(1:2)
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc2d_Radiation => hbc2d_Generic_Model

  • public pure function hbc2d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat(1:2)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc3d_NoNormalFlow => hbc3d_Generic_Model

  • public pure function hbc3d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat(1:3)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc3d_Prescribed => hbc3d_Prescribed_Model

  • public pure function hbc3d_Prescribed_Model(this, x, t) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x(1:3)
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: hbc3d_Radiation => hbc3d_Generic_Model

  • public pure function hbc3d_Generic_Model(this, s, nhat) result(exts)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: nhat(1:3)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: pbc1d_NoNormalFlow => pbc1d_Generic_Model

  • public pure function pbc1d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar)
    real(kind=prec), intent(in) :: nhat

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: pbc1d_Prescribed => pbc1d_Prescribed_Model

  • public pure function pbc1d_Prescribed_Model(this, x, t) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: pbc1d_Radiation => pbc1d_Generic_Model

  • public pure function pbc1d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar)
    real(kind=prec), intent(in) :: nhat

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: pbc2d_NoNormalFlow => pbc2d_Generic_Model

  • public pure function pbc2d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:2)
    real(kind=prec), intent(in) :: nhat(1:2)

    Return Value real(kind=prec)(1:this%nvar,1:2)

procedure, public :: pbc2d_Prescribed => pbc2d_Prescribed_Model

  • public pure function pbc2d_Prescribed_Model(this, x, t) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x(1:2)
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar,1:2)

procedure, public :: pbc2d_Radiation => pbc2d_Generic_Model

  • public pure function pbc2d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:2)
    real(kind=prec), intent(in) :: nhat(1:2)

    Return Value real(kind=prec)(1:this%nvar,1:2)

procedure, public :: pbc3d_NoNormalFlow => pbc3d_Generic_Model

  • public pure function pbc3d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:3)
    real(kind=prec), intent(in) :: nhat(1:3)

    Return Value real(kind=prec)(1:this%nvar,1:3)

procedure, public :: pbc3d_Prescribed => pbc3d_Prescribed_Model

  • public pure function pbc3d_Prescribed_Model(this, x, t) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: x(1:3)
    real(kind=prec), intent(in) :: t

    Return Value real(kind=prec)(1:this%nvar,1:3)

procedure, public :: pbc3d_Radiation => pbc3d_Generic_Model

  • public pure function pbc3d_Generic_Model(this, dsdx, nhat) result(extDsdx)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:3)
    real(kind=prec), intent(in) :: nhat(1:3)

    Return Value real(kind=prec)(1:this%nvar,1:3)

procedure, public :: riemannflux1d => riemannflux1d_Model

  • public pure function riemannflux1d_Model(this, sL, sR, dsdx, nhat) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: sL(1:this%nvar)
    real(kind=prec), intent(in) :: sR(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar)
    real(kind=prec), intent(in) :: nhat

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: riemannflux2d => riemannflux2d_Model

  • public pure function riemannflux2d_Model(this, sL, sR, dsdx, nhat) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: sL(1:this%nvar)
    real(kind=prec), intent(in) :: sR(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:2)
    real(kind=prec), intent(in) :: nhat(1:2)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: riemannflux3d => riemannflux3d_Model

  • public pure function riemannflux3d_Model(this, sL, sR, dsdx, nhat) result(flux)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: sL(1:this%nvar)
    real(kind=prec), intent(in) :: sR(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:3)
    real(kind=prec), intent(in) :: nhat(1:3)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: source1d => source1d_Model

  • public pure function source1d_Model(this, s, dsdx) result(source)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: source2d => source2d_Model

  • public pure function source2d_Model(this, s, dsdx) result(source)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:2)

    Return Value real(kind=prec)(1:this%nvar)

procedure, public :: source3d => source3d_Model

  • public pure function source3d_Model(this, s, dsdx) result(source)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(in) :: this
    real(kind=prec), intent(in) :: s(1:this%nvar)
    real(kind=prec), intent(in) :: dsdx(1:this%nvar,1:3)

    Return Value real(kind=prec)(1:this%nvar)

Source Code

  type,extends(DGModel1D_t) :: DGModel1D

  contains

    procedure :: UpdateSolution => UpdateSolution_DGModel1D

    procedure :: CalculateEntropy => CalculateEntropy_DGModel1D
    procedure :: BoundaryFlux => BoundaryFlux_DGModel1D
    procedure :: FluxMethod => fluxmethod_DGModel1D
    procedure :: SourceMethod => sourcemethod_DGModel1D
    procedure :: SetBoundaryCondition => setboundarycondition_DGModel1D
    procedure :: SetGradientBoundaryCondition => setgradientboundarycondition_DGModel1D

    procedure :: UpdateGRK2 => UpdateGRK2_DGModel1D
    procedure :: UpdateGRK3 => UpdateGRK3_DGModel1D
    procedure :: UpdateGRK4 => UpdateGRK4_DGModel1D

    procedure :: CalculateSolutionGradient => CalculateSolutionGradient_DGModel1D
    procedure :: CalculateTendency => CalculateTendency_DGModel1D

  endtype DGModel1D