Scalar1D_t Derived Type

type, public, extends(SELF_DataObj) :: Scalar1D_t


Inherits

type~~scalar1d_t~~InheritsGraph type~scalar1d_t Scalar1D_t type~self_dataobj SELF_DataObj type~scalar1d_t->type~self_dataobj 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~lagrange_t Lagrange_t type~lagrange->type~lagrange_t c_ptr c_ptr type~lagrange_t->c_ptr blas_handle

Inherited by

type~~scalar1d_t~~InheritedByGraph type~scalar1d_t Scalar1D_t type~scalar1d Scalar1D type~scalar1d->type~scalar1d_t type~scalar1d~2 Scalar1D type~scalar1d~2->type~scalar1d_t type~scalar1d~3 Scalar1D type~scalar1d~3->type~scalar1d_t type~geometry1d Geometry1D type~geometry1d->type~scalar1d x, dxds type~mappedscalar1d_t MappedScalar1D_t type~mappedscalar1d_t->type~scalar1d type~mappedscalar1d_t->type~geometry1d geometry type~dgmodel1d_t DGModel1D_t type~dgmodel1d_t->type~geometry1d geometry type~mappedscalar1d MappedScalar1D type~dgmodel1d_t->type~mappedscalar1d solution, solutionGradient, flux, source, fluxDivergence, dSdt, workSol type~mappedscalar1d->type~mappedscalar1d_t type~mappedscalar1d~2 MappedScalar1D type~mappedscalar1d~2->type~mappedscalar1d_t type~dgmodel1d DGModel1D type~dgmodel1d->type~dgmodel1d_t type~dgmodel1d~2 DGModel1D type~dgmodel1d~2->type~dgmodel1d_t type~nulldgmodel1d_t NullDGModel1D_t type~nulldgmodel1d_t->type~dgmodel1d type~burgers1d_t Burgers1D_t type~burgers1d_t->type~dgmodel1d type~advection_diffusion_1d_t advection_diffusion_1d_t type~advection_diffusion_1d_t->type~dgmodel1d type~nulldgmodel1d NullDGModel1D type~nulldgmodel1d->type~nulldgmodel1d_t type~nulldgmodel1d~2 NullDGModel1D type~nulldgmodel1d~2->type~nulldgmodel1d_t type~advection_diffusion_1d advection_diffusion_1d type~advection_diffusion_1d->type~advection_diffusion_1d_t type~burgers1d~2 Burgers1D type~burgers1d~2->type~burgers1d_t type~burgers1d Burgers1D type~burgers1d->type~burgers1d_t type~advection_diffusion_1d~2 advection_diffusion_1d type~advection_diffusion_1d~2->type~advection_diffusion_1d_t

Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
integer, public :: M
integer, public :: N
real(kind=prec), public, pointer, contiguous, dimension(:,:,:):: avgBoundary
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
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 :: AverageSides => AverageSides_Scalar1D_t

procedure, public :: BoundaryInterp => BoundaryInterp_Scalar1D_t

generic, public :: Derivative => Derivative_Scalar1D_t

  • public subroutine Derivative_Scalar1D_t(this, df)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    real(kind=prec), intent(inout) :: df(1:this%N+1,1:this%nelem,1:this%nvar)

procedure, private :: Derivative_Scalar1D_t

  • public subroutine Derivative_Scalar1D_t(this, df)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    real(kind=prec), intent(inout) :: df(1:this%N+1,1:this%nelem,1:this%nvar)

procedure, public :: Free => Free_Scalar1D_t

  • public subroutine Free_Scalar1D_t(this)

    Arguments

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

generic, public :: GridInterp => GridInterp_Scalar1D_t

  • public subroutine GridInterp_Scalar1D_t(this, f)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    real(kind=prec), intent(inout) :: f(1:this%M+1,1:this%nelem,1:this%nvar)

procedure, private :: GridInterp_Scalar1D_t

  • public subroutine GridInterp_Scalar1D_t(this, f)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    real(kind=prec), intent(inout) :: f(1:this%M+1,1:this%nelem,1:this%nvar)

procedure, public :: Init => Init_Scalar1D_t

  • public subroutine Init_Scalar1D_t(this, interp, nVar, nElem)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(out) :: this
    type(Lagrange), intent(in), target:: interp
    integer, intent(in) :: nVar
    integer, intent(in) :: nElem

procedure, public :: SetDescription => SetDescription_DataObj

  • public subroutine SetDescription_DataObj(this, ivar, description)

    Set the description of the ivar-th variable

    Arguments

    TypeIntentOptionalAttributesName
    class(SELF_DataObj), intent(inout) :: this
    integer, intent(in) :: ivar
    character, intent(in) :: description

generic, public :: SetEquation => SetEquation_DataObj

  • public subroutine SetEquation_DataObj(this, ivar, eqnChar)

    Sets the equation parser for the ivar-th variable

    Arguments

    TypeIntentOptionalAttributesName
    class(SELF_DataObj), intent(inout) :: this
    integer, intent(in) :: ivar
    character, intent(in) :: eqnChar

procedure, public :: SetName => SetName_DataObj

  • public subroutine SetName_DataObj(this, ivar, name)

    Set the name of the ivar-th variable

    Arguments

    TypeIntentOptionalAttributesName
    class(SELF_DataObj), intent(inout) :: this
    integer, intent(in) :: ivar
    character, intent(in) :: name

procedure, public :: SetUnits => SetUnits_DataObj

  • public subroutine SetUnits_DataObj(this, ivar, units)

    Set the units of the ivar-th variable

    Arguments

    TypeIntentOptionalAttributesName
    class(SELF_DataObj), intent(inout) :: this
    integer, intent(in) :: ivar
    character, intent(in) :: units

procedure, public :: UpdateDevice => UpdateDevice_Scalar1D_t

procedure, public :: UpdateHost => UpdateHost_Scalar1D_t

generic, public :: WriteHDF5 => WriteHDF5_Scalar1D_t

  • public subroutine WriteHDF5_Scalar1D_t(this, fileId, group)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    integer(kind=HID_T), intent(in) :: fileId
    character, intent(in) :: group

procedure, private :: WriteHDF5_Scalar1D_t

  • public subroutine WriteHDF5_Scalar1D_t(this, fileId, group)

    Arguments

    TypeIntentOptionalAttributesName
    class(Scalar1D_t), intent(in) :: this
    integer(kind=HID_T), intent(in) :: fileId
    character, intent(in) :: group

Source Code

  type,extends(SELF_DataObj),public :: Scalar1D_t

    real(prec),pointer,contiguous,dimension(:,:,:) :: interior
    real(prec),pointer,contiguous,dimension(:,:,:) :: boundary
    real(prec),pointer,contiguous,dimension(:,:,:) :: boundarynormal
    real(prec),pointer,contiguous,dimension(:,:,:) :: extBoundary
    real(prec),pointer,contiguous,dimension(:,:,:) :: avgBoundary

  contains

    procedure,public :: Init => Init_Scalar1D_t
    procedure,public :: Free => Free_Scalar1D_t

    procedure,public :: UpdateHost => UpdateHost_Scalar1D_t
    procedure,public :: UpdateDevice => UpdateDevice_Scalar1D_t

    procedure,public :: AverageSides => AverageSides_Scalar1D_t
    procedure,public :: BoundaryInterp => BoundaryInterp_Scalar1D_t
    generic,public :: GridInterp => GridInterp_Scalar1D_t
    procedure,private :: GridInterp_Scalar1D_t
    generic,public :: Derivative => Derivative_Scalar1D_t
    procedure,private :: Derivative_Scalar1D_t
    generic,public :: WriteHDF5 => WriteHDF5_Scalar1D_t
    procedure,private :: WriteHDF5_Scalar1D_t

  endtype Scalar1D_t