eulerian_obj_base Derived Type

type, private, abstract :: eulerian_obj_base

Base structure for Rulerian data. This typically represents a field quantity.


Inherits

type~~eulerian_obj_base~~InheritsGraph type~eulerian_obj_base eulerian_obj_base type~block_obj block_obj type~eulerian_obj_base->type~block_obj block type~parallel_obj parallel_obj type~eulerian_obj_base->type~parallel_obj parallel type~block_obj->type~parallel_obj parallel MPI_Datatype MPI_Datatype type~block_obj->MPI_Datatype gc_slab_r, gc_slab_i type~axis_obj axis_obj type~block_obj->type~axis_obj axis, axis_partition type~hdf5_obj hdf5_obj type~block_obj->type~hdf5_obj hdf5 type~parallel_obj->MPI_Datatype REAL_SP, REAL_DP, REAL_WP, COMPLEX_SP, COMPLEX_DP, COMPLEX_WP, INTEGER, INT8, LOGICAL type~communicators communicators type~parallel_obj->type~communicators comm type~patch patch type~parallel_obj->type~patch rank MPI_Comm MPI_Comm type~communicators->MPI_Comm w, g type~hdf5_obj->type~parallel_obj parallel type~hashtbl_obj hashtbl_obj type~hdf5_obj->type~hashtbl_obj tbl type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec type~sllist_obj->type~sllist_obj child

Inherited by

type~~eulerian_obj_base~~InheritedByGraph type~eulerian_obj_base eulerian_obj_base type~eulerian_obj_i eulerian_obj_i type~eulerian_obj_i->type~eulerian_obj_base type~eulerian_obj_r eulerian_obj_r type~eulerian_obj_r->type~eulerian_obj_base type~eulerian_ptr eulerian_ptr type~eulerian_ptr->type~eulerian_obj_base p type~cdifs_obj cdifs_obj type~cdifs_obj->type~eulerian_obj_i maskV type~cdifs_obj->type~eulerian_obj_r V, P, dP, ibS, ibVF, ibF, ibN, Vold, resV, rhs, divu, Vm, srcV type~eulerian_set eulerian_set type~cdifs_obj->type~eulerian_set fields type~hypre_obj hypre_obj type~cdifs_obj->type~hypre_obj hypre, VFSolver type~eulerian_set->type~eulerian_ptr field type~grans_obj grans_obj type~grans_obj->type~eulerian_obj_r ibVF, PVF, ibS, Fp, ibF, ibN, rhs type~grans_obj->type~eulerian_set fields type~grans_obj->type~hypre_obj VFSolver type~hypre_obj->type~eulerian_obj_i irow

Components

Type Visibility Attributes Name Initial
type(block_obj), public, pointer :: block => null()

Associated block structure

character(len=:), public, allocatable :: name

Variable name

type(parallel_obj), public, pointer :: parallel => null()

Associated parallel structure

integer, public :: staggering = 0

0 = cell centered; 1 = X1-face centered 2 = X2-face centered; 3 = X3-face centered


Type-Bound Procedures

procedure, public :: AddUpGhostCells => eulerian_obj_AddUpGhostCells

procedure, public :: AddUpGhostCells_x => eulerian_obj_AddUpGhostCells_x

  • private impure subroutine eulerian_obj_AddUpGhostCells_x(this)

    Adds up ghostcells in the x direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: AddUpGhostCells_y => eulerian_obj_AddUpGhostCells_y

  • private impure subroutine eulerian_obj_AddUpGhostCells_y(this)

    Adds up ghostcells in the y direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: AddUpGhostCells_z => eulerian_obj_AddUpGhostCells_z

  • private impure subroutine eulerian_obj_AddUpGhostCells_z(this)

    Adds up ghostcells in the z direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: Allocate => eulerian_obj_Allocate

  • private impure subroutine eulerian_obj_Allocate(this)

    Allocates Cell array in Eulerian object.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: Deallocate => eulerian_obj_Deallocate

  • private pure subroutine eulerian_obj_Deallocate(this)

    Deallocate Cell array in Eulerian object.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: Finalize => eulerian_obj_Final

  • private pure subroutine eulerian_obj_Final(this)

    Finalizes the Eulerian object and free memory.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: Info => eulerian_obj_Info

  • private impure subroutine eulerian_obj_Info(this)

    Prints info about this structure.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: Initialize => eulerian_obj_Init

  • private impure subroutine eulerian_obj_Init(this, name, block, parallel, stag)

    Initializes an Eulerian field.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    character(len=*), intent(in) :: name

    Name of variable

    type(block_obj), intent(in), target :: block

    A block object

    type(parallel_obj), intent(in), target :: parallel

    Parallel structure to link with

    integer, intent(in) :: stag

    Staggering

procedure, public :: Mean => eulerian_obj_Mean

  • private impure function eulerian_obj_Mean(this) result(val)

    Computes the mean of an Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    Return Value real(kind=wp)

procedure, public :: Norm2 => eulerian_obj_Norm2

  • private impure function eulerian_obj_Norm2(this) result(val)

    Computes norm2 of an Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    Return Value real(kind=wp)

procedure, public :: UpdateGhostCells => eulerian_obj_UpdateGhostCells

procedure, public :: UpdateGhostCells_x => eulerian_obj_UpdateGhostCells_x

  • private impure subroutine eulerian_obj_UpdateGhostCells_x(this)

    Updates the ghostcells in the x direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: UpdateGhostCells_y => eulerian_obj_UpdateGhostCells_y

  • private impure subroutine eulerian_obj_UpdateGhostCells_y(this)

    Updates the ghostcells in the y direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

procedure, public :: UpdateGhostCells_z => eulerian_obj_UpdateGhostCells_z

  • private impure subroutine eulerian_obj_UpdateGhostCells_z(this)

    Updates the ghostcells in the z direction with non-blocking mpi directives.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

  • private impure subroutine eulerian_obj_AssignEulerianObj(this, in)

    Performs assignment for Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    class(eulerian_obj_base), intent(in) :: in

    Object to assign

  • private impure subroutine eulerian_obj_AssignReal0D(this, in)

    Performs assignment for Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    real(kind=wp), intent(in) :: in

    Object to assign

  • private impure subroutine eulerian_obj_AssignInt0D(this, in)

    Performs assignment for Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    integer, intent(in) :: in

    Object to assign

generic, public :: operator(*) => eulerian_obj_MulReal0D, eulerian_obj_MulInt0D

  • private impure function eulerian_obj_MulReal0D(this, in) result(res)

    Performs multiplication of real Eulerian objects by real scalar.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    real(kind=wp), intent(in) :: in

    An Eulerian object

    Return Value type(eulerian_obj_r)

    Result

  • private impure function eulerian_obj_MulInt0D(this, in) result(res)

    Performs multiplication of integer Eulerian objects by integer scalar.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    integer, intent(in) :: in

    An Eulerian object

    Return Value class(eulerian_obj_base), allocatable

    Result

generic, public :: operator(+) => eulerian_obj_AddEulerianRObj, eulerian_obj_AddEulerianIObj

generic, public :: operator(-) => eulerian_obj_SubEulerianRObj, eulerian_obj_SubEulerianIObj

procedure, private :: eulerian_obj_AddEulerianIObj

procedure, private :: eulerian_obj_AddEulerianRObj

procedure, private :: eulerian_obj_AssignEulerianObj

procedure, private :: eulerian_obj_AssignInt0D

  • private impure subroutine eulerian_obj_AssignInt0D(this, in)

    Performs assignment for Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    integer, intent(in) :: in

    Object to assign

procedure, private :: eulerian_obj_AssignReal0D

  • private impure subroutine eulerian_obj_AssignReal0D(this, in)

    Performs assignment for Eulerian_obj.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(inout) :: this

    An Eulerian object

    real(kind=wp), intent(in) :: in

    Object to assign

procedure, private :: eulerian_obj_MulInt0D

  • private impure function eulerian_obj_MulInt0D(this, in) result(res)

    Performs multiplication of integer Eulerian objects by integer scalar.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    integer, intent(in) :: in

    An Eulerian object

    Return Value class(eulerian_obj_base), allocatable

    Result

procedure, private :: eulerian_obj_MulReal0D

  • private impure function eulerian_obj_MulReal0D(this, in) result(res)

    Performs multiplication of real Eulerian objects by real scalar.

    Arguments

    Type IntentOptional Attributes Name
    class(eulerian_obj_base), intent(in) :: this

    An Eulerian object

    real(kind=wp), intent(in) :: in

    An Eulerian object

    Return Value type(eulerian_obj_r)

    Result

procedure, private :: eulerian_obj_SubEulerianIObj

procedure, private :: eulerian_obj_SubEulerianRObj

Source Code

  type, abstract :: eulerian_obj_base
    !> Base structure for Rulerian data. This typically represents
    ! a field quantity.
    character(len=:), allocatable :: name                                      !! Variable name
    integer                       :: staggering = 0                            !! 0 = cell centered; 1 = X1-face centered
                                                                               !! 2 = X2-face centered; 3 = X3-face centered
    type(parallel_obj),   pointer :: parallel => null()                        !! Associated parallel structure
    type(block_obj),      pointer :: block    => null()                        !! Associated block structure
    contains
      procedure :: Initialize          => eulerian_obj_Init
      procedure :: Finalize            => eulerian_obj_Final
      procedure :: UpdateGhostCells    => eulerian_obj_UpdateGhostCells
      procedure :: AddUpGhostCells     => eulerian_obj_AddUpGhostCells
      procedure :: Allocate            => eulerian_obj_Allocate
      procedure :: Deallocate          => eulerian_obj_Deallocate
      procedure :: UpdateGhostCells_x  => eulerian_obj_UpdateGhostCells_x
      procedure :: UpdateGhostCells_y  => eulerian_obj_UpdateGhostCells_y
      procedure :: UpdateGhostCells_z  => eulerian_obj_UpdateGhostCells_z
      procedure :: AddUpGhostCells_x   => eulerian_obj_AddUpGhostCells_x
      procedure :: AddUpGhostCells_y   => eulerian_obj_AddUpGhostCells_y
      procedure :: AddUpGhostCells_z   => eulerian_obj_AddUpGhostCells_z
      procedure :: Info                => eulerian_obj_Info
      procedure :: Mean                => eulerian_obj_Mean
      procedure :: Norm2               => eulerian_obj_Norm2
      generic   :: assignment(=)       => eulerian_obj_AssignEulerianObj,   &
                                          eulerian_obj_AssignReal0D,        &
                                          eulerian_obj_AssignInt0D
      generic   :: operator(+)         => eulerian_obj_AddEulerianRObj,     &
                                          eulerian_obj_AddEulerianIObj
      generic   :: operator(-)         => eulerian_obj_SubEulerianRObj,     &
                                          eulerian_obj_SubEulerianIObj
      generic   :: operator(*)         => eulerian_obj_MulReal0D,           &
                                          eulerian_obj_MulInt0D
      ! Internal/private procedures
      procedure, private :: eulerian_obj_AssignEulerianObj
      procedure, private :: eulerian_obj_AssignReal0D
      procedure, private :: eulerian_obj_AssignInt0D
      procedure, private :: eulerian_obj_AddEulerianRObj
      procedure, private :: eulerian_obj_AddEulerianIObj
      procedure, private :: eulerian_obj_SubEulerianRObj
      procedure, private :: eulerian_obj_SubEulerianIObj
      procedure, private :: eulerian_obj_MulReal0D
      procedure, private :: eulerian_obj_MulInt0D
  end type eulerian_obj_base