LinearEuler3D Derived Type

type, public, extends(LinearEuler3D_t) :: LinearEuler3D


Inherits

type~~lineareuler3d~~InheritsGraph type~lineareuler3d LinearEuler3D type~lineareuler3d_t LinearEuler3D_t type~lineareuler3d->type~lineareuler3d_t type~dgmodel3d DGModel3D type~lineareuler3d_t->type~dgmodel3d type~dgmodel3d_t DGModel3D_t type~dgmodel3d->type~dgmodel3d_t type~model Model type~dgmodel3d_t->type~model type~mappedscalar3d MappedScalar3D type~dgmodel3d_t->type~mappedscalar3d solution, source, fluxDivergence, dSdt, workSol type~semhex SEMHex type~dgmodel3d_t->type~semhex geometry type~mesh3d Mesh3D type~dgmodel3d_t->type~mesh3d mesh type~mappedvector3d MappedVector3D type~dgmodel3d_t->type~mappedvector3d solutionGradient, flux c_ptr c_ptr type~mappedscalar3d->c_ptr jas_gpu type~mappedscalar3d_t MappedScalar3D_t type~mappedscalar3d->type~mappedscalar3d_t type~vector3d Vector3D type~semhex->type~vector3d x, nHat type~tensor3d Tensor3D type~semhex->type~tensor3d dxds, dsdx type~scalar3d Scalar3D type~semhex->type~scalar3d nScale, J type~mesh3d->c_ptr sideInfo_gpu type~mesh3d_t Mesh3D_t type~mesh3d->type~mesh3d_t type~mappedvector3d_t MappedVector3D_t type~mappedvector3d->type~mappedvector3d_t type~vector3d->c_ptr blas_handle, interior_gpu, boundary_gpu, extBoundary_gpu, avgBoundary_gpu, boundaryNormal_gpu, interpWork1, interpWork2 type~vector3d_t Vector3D_t type~vector3d->type~vector3d_t type~tensor3d->c_ptr blas_handle, interior_gpu, boundary_gpu, extBoundary_gpu type~tensor3d_t Tensor3D_t type~tensor3d->type~tensor3d_t type~mappedscalar3d_t->type~semhex geometry type~mappedscalar3d_t->type~scalar3d type~scalar3d->c_ptr blas_handle, interior_gpu, boundary_gpu, boundarynormal_gpu, extBoundary_gpu, avgBoundary_gpu, interpWork1, interpWork2 type~scalar3d_t Scalar3D_t type~scalar3d->type~scalar3d_t type~semmesh SEMMesh type~mesh3d_t->type~semmesh type~mappedvector3d_t->type~semhex geometry type~mappedvector3d_t->type~vector3d type~self_dataobj SELF_DataObj type~vector3d_t->type~self_dataobj type~tensor3d_t->type~self_dataobj type~scalar3d_t->type~self_dataobj type~domaindecomposition DomainDecomposition type~semmesh->type~domaindecomposition decomp type~lagrange Lagrange type~self_dataobj->type~lagrange interp EquationParser EquationParser type~self_dataobj->EquationParser eqn type~metadata Metadata type~self_dataobj->type~metadata meta type~domaindecomposition->c_ptr elemToRank_gpu type~domaindecomposition_t DomainDecomposition_t type~domaindecomposition->type~domaindecomposition_t type~lagrange->c_ptr qWeights_gpu, iMatrix_gpu, dMatrix_gpu, dgMatrix_gpu, bMatrix_gpu type~lagrange_t Lagrange_t type~lagrange->type~lagrange_t type~lagrange_t->c_ptr blas_handle

Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
real(kind=prec), public :: c =1.0_prec
type(MappedScalar3D), public :: dSdt
real(kind=prec), public :: dt
real(kind=prec), public :: entropy
type(MappedVector3D), public :: flux
type(MappedScalar3D), public :: fluxDivergence
real(kind=prec), public :: g =0.0_prec
type(SEMHex), public, pointer:: geometry
logical, public :: gradient_enabled =.false.
integer, public :: ioIterate =0
type(Mesh3D), public, pointer:: mesh
integer, public :: nvar
logical, public :: prescribed_bcs_enabled =.true.
real(kind=prec), public :: rho0 =1.0_prec
type(MappedScalar3D), public :: solution
type(MappedVector3D), public :: solutionGradient
type(MappedScalar3D), public :: source
real(kind=prec), public :: t
logical, public :: tecplot_enabled =.true.
procedure(SELF_timeIntegrator), public, pointer:: timeIntegrator=> Euler_timeIntegrator
type(MappedScalar3D), public :: workSol

Type-Bound Procedures

procedure, public :: AdditionalFree => AdditionalFree_Model

  • public subroutine AdditionalFree_Model(this)

    Arguments

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

procedure, public :: AdditionalInit => AdditionalInit_Model

  • public subroutine AdditionalInit_Model(this)

    Arguments

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

procedure, public :: AdditionalOutput => AdditionalOutput_Model

  • public subroutine AdditionalOutput_Model(this, fileid)

    Arguments

    TypeIntentOptionalAttributesName
    class(Model), intent(inout) :: this
    integer(kind=HID_T), intent(in) :: fileid

procedure, public :: CalculateEntropy => CalculateEntropy_DGModel3D

procedure, public :: CalculateSolutionGradient => CalculateSolutionGradient_DGModel3D

procedure, public :: CalculateTendency => CalculateTendency_DGModel3D

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 :: 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_DGModel3D_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_DGModel3D_t

  • public subroutine Init_DGModel3D_t(this, mesh, geometry)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel3D_t), intent(out) :: this
    type(Mesh3D), intent(in), target:: mesh
    type(SEMHex), 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_DGModel3D_t

  • public subroutine Read_DGModel3D_t(this, fileName)

    Arguments

    TypeIntentOptionalAttributesName
    class(DGModel3D_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 :: ReportMetrics => ReportMetrics_DGModel3D_t

  • public subroutine ReportMetrics_DGModel3D_t(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(DGModel3D_t), intent(inout) :: this

procedure, public :: ReportUserMetrics => ReportUserMetrics_Model

  • public subroutine ReportUserMetrics_Model(this)

    Method that can be overridden by users to report their own custom metrics after file io

    Arguments

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

procedure, public :: SetGradientBoundaryCondition => setgradientboundarycondition_DGModel3D

  • public subroutine setgradientboundarycondition_DGModel3D(this)

    Boundary conditions for the solution are set to 0 for the external state to provide radiation type boundary conditions.

    Arguments

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

procedure, public :: SetMetadata => SetMetadata_LinearEuler3D_t

procedure, public :: SetNumberOfVariables => SetNumberOfVariables_LinearEuler3D_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

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_LinearEuler3D_t

procedure, public :: SphericalSoundWave => SphericalSoundWave_LinearEuler3D_t

  • public subroutine SphericalSoundWave_LinearEuler3D_t(this, rhoprime, Lr, x0, y0, z0)

    This subroutine sets the initial condition for a weak blast wave problem. The initial condition is given by

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(LinearEuler3D_t), intent(inout) :: this
    real(kind=prec), intent(in) :: rhoprime
    real(kind=prec), intent(in) :: Lr
    real(kind=prec), intent(in) :: x0
    real(kind=prec), intent(in) :: y0
    real(kind=prec), intent(in) :: z0

procedure, public :: UpdateGRK2 => UpdateGRK2_DGModel3D

  • public subroutine UpdateGRK2_DGModel3D(this, m)

    Arguments

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

procedure, public :: UpdateGRK3 => UpdateGRK3_DGModel3D

  • public subroutine UpdateGRK3_DGModel3D(this, m)

    Arguments

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

procedure, public :: UpdateGRK4 => UpdateGRK4_DGModel3D

  • public subroutine UpdateGRK4_DGModel3D(this, m)

    Arguments

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

procedure, public :: UpdateSolution => UpdateSolution_DGModel3D

  • public subroutine UpdateSolution_DGModel3D(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(DGModel3D), intent(inout) :: this
    real(kind=prec), intent(in), optional :: dt

procedure, public :: WriteModel => Write_DGModel3D_t

  • public subroutine Write_DGModel3D_t(this, fileName)

    Arguments

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

procedure, public :: WriteTecplot => WriteTecplot_DGModel3D_t

  • public subroutine WriteTecplot_DGModel3D_t(this, filename)

    Arguments

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

procedure, public :: boundaryflux => boundaryflux_LinearEuler3D

procedure, public :: entropy_func => entropy_func_LinearEuler3D_t

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

    The entropy function is the sum of kinetic and internal energy For the linear model, this is

    Read more…

    Arguments

    TypeIntentOptionalAttributesName
    class(LinearEuler3D_t), 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_LinearEuler3D_t

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

    Arguments

    TypeIntentOptionalAttributesName
    class(LinearEuler3D_t), 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 :: fluxmethod => fluxmethod_LinearEuler3D

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_LinearEuler3D_t

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

    Uses a local lax-friedrich's upwind flux The max eigenvalue is taken as the sound speed

    Arguments

    TypeIntentOptionalAttributesName
    class(LinearEuler3D_t), 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 :: setboundarycondition => setboundarycondition_LinearEuler3D

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(LinearEuler3D_t) :: LinearEuler3D
  contains
    procedure :: setboundarycondition => setboundarycondition_LinearEuler3D
    procedure :: boundaryflux => boundaryflux_LinearEuler3D
    procedure :: fluxmethod => fluxmethod_LinearEuler3D

  endtype LinearEuler3D