Tensor3D_t Derived Type

type, public, extends(SELF_DataObj) :: Tensor3D_t


Inherits

type~~tensor3d_t~~InheritsGraph type~tensor3d_t Tensor3D_t type~self_dataobj SELF_DataObj type~tensor3d_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~~tensor3d_t~~InheritedByGraph type~tensor3d_t Tensor3D_t type~tensor3d Tensor3D type~tensor3d->type~tensor3d_t type~tensor3d~2 Tensor3D type~tensor3d~2->type~tensor3d_t type~semhex SEMHex type~semhex->type~tensor3d dxds, dsdx type~mappedvector3d_t MappedVector3D_t type~mappedvector3d_t->type~semhex geometry type~mappedscalar3d_t MappedScalar3D_t type~mappedscalar3d_t->type~semhex geometry type~dgmodel3d_t DGModel3D_t type~dgmodel3d_t->type~semhex geometry type~mappedscalar3d MappedScalar3D type~dgmodel3d_t->type~mappedscalar3d solution, source, fluxDivergence, dSdt, workSol type~mappedvector3d MappedVector3D type~dgmodel3d_t->type~mappedvector3d solutionGradient, flux type~mappedscalar3d->type~mappedscalar3d_t type~dgmodel3d DGModel3D type~dgmodel3d->type~dgmodel3d_t type~mappedvector3d->type~mappedvector3d_t type~mappedvector3d~2 MappedVector3D type~mappedvector3d~2->type~mappedvector3d_t type~mappedscalar3d~2 MappedScalar3D type~mappedscalar3d~2->type~mappedscalar3d_t type~dgmodel3d~2 DGModel3D type~dgmodel3d~2->type~dgmodel3d_t type~nulldgmodel3d_t NullDGModel3D_t type~nulldgmodel3d_t->type~dgmodel3d type~advection_diffusion_3d_t advection_diffusion_3d_t type~advection_diffusion_3d_t->type~dgmodel3d type~nulldgmodel3d NullDGModel3D type~nulldgmodel3d->type~nulldgmodel3d_t type~advection_diffusion_3d advection_diffusion_3d type~advection_diffusion_3d->type~advection_diffusion_3d_t type~nulldgmodel3d~2 NullDGModel3D type~nulldgmodel3d~2->type~nulldgmodel3d_t type~advection_diffusion_3d~2 advection_diffusion_3d type~advection_diffusion_3d~2->type~advection_diffusion_3d_t

Contents

Source Code


Components

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

generic, public :: Determinant => Determinant_Tensor3D_t

  • public subroutine Determinant_Tensor3D_t(this, det)

    Arguments

    TypeIntentOptionalAttributesName
    class(Tensor3D_t), intent(in) :: this
    real(kind=prec), intent(out) :: det(1:this%N+1,1:this%N+1,1:this%N+1,1:this%nelem,1:this%nvar)

procedure, private :: Determinant_Tensor3D_t

  • public subroutine Determinant_Tensor3D_t(this, det)

    Arguments

    TypeIntentOptionalAttributesName
    class(Tensor3D_t), intent(in) :: this
    real(kind=prec), intent(out) :: det(1:this%N+1,1:this%N+1,1:this%N+1,1:this%nelem,1:this%nvar)

procedure, public :: Free => Free_Tensor3D_t

  • public subroutine Free_Tensor3D_t(this)

    Arguments

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

procedure, public :: Init => Init_Tensor3D_t

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

    Arguments

    TypeIntentOptionalAttributesName
    class(Tensor3D_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_Tensor3D_t

procedure, public :: UpdateHost => UpdateHost_Tensor3D_t

Source Code

  type,extends(SELF_DataObj),public :: Tensor3D_t

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

  contains

    procedure,public :: Init => Init_Tensor3D_t
    procedure,public :: Free => Free_Tensor3D_t

    procedure,public :: BoundaryInterp => BoundaryInterp_Tensor3D_t

    procedure,public :: UpdateHost => UpdateHost_Tensor3D_t
    procedure,public :: UpdateDevice => UpdateDevice_Tensor3D_t

    generic,public :: Determinant => Determinant_Tensor3D_t
    procedure,private :: Determinant_Tensor3D_t

  endtype Tensor3D_t