region_obj Derived Type

type, private :: region_obj

Defines regions where boundary conditions are applied.


Inherits

type~~region_obj~~InheritsGraph type~region_obj region_obj type~bc_obj bc_obj type~region_obj->type~bc_obj BC type~block_obj block_obj type~region_obj->type~block_obj region type~hashtbl_obj hashtbl_obj type~region_obj->type~hashtbl_obj tbl 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 parallel_obj type~block_obj->type~parallel_obj parallel type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec type~hdf5_obj->type~hashtbl_obj tbl type~hdf5_obj->type~parallel_obj parallel 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 type~sllist_obj->type~sllist_obj child MPI_Comm MPI_Comm type~communicators->MPI_Comm w, g

Inherited by

type~~region_obj~~InheritedByGraph type~region_obj region_obj type~bc_set bc_set type~bc_set->type~region_obj region type~cdifs_obj cdifs_obj type~cdifs_obj->type~bc_set bcs type~marker_set marker_set type~cdifs_obj->type~marker_set IB type~respart_set ResPart_set type~cdifs_obj->type~respart_set RP type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~grans_obj grans_obj type~grans_obj->type~bc_set bcs type~grans_obj->type~marker_set IB type~grans_obj->type~respart_set RP type~grans_obj->type~collision_obj collisions type~marker_set->type~bc_set bcs type~respart_set->type~bc_set bcs type~respart_set->type~marker_set ib type~collision_obj->type~marker_set IB type~collision_obj->type~respart_set RP type~solid_obj solid_obj type~solid_obj->type~marker_set type~solid_set solid_set type~solid_set->type~solid_obj p

Components

Type Visibility Attributes Name Initial
type(bc_obj), public, allocatable :: BC(:)

Variables on this region

integer, public :: count = 0

Count of variables defined on this region

integer, public :: dir

Normal direction (=1,2,3)

integer, public :: hi(3) = -100

Grid hi bound

integer, public :: lo(3) = -100

Grid low bound

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

Name of this region

type(block_obj), public :: region

Block/grid for this region

integer, public :: side

Side (BC_LEFT or BC_RIGHT)

real(kind=wp), public :: xhi(3)

Position of upper right corner

real(kind=wp), public :: xlo(3)

Position of lower left corner

type(hashtbl_obj), private :: tbl

Hash table


Type-Bound Procedures

procedure, public :: Add => region_obj_Add

  • private pure subroutine region_obj_Add(this, name, type, extents)

    Adds a new variable to region.

    Arguments

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

    A boundary region object

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

    Region name

    integer, intent(in) :: type

    Type of boundary condition

    type(extent_obj), intent(in) :: extents

    Region extents

procedure, public :: Expand => region_obj_Expand

  • private pure subroutine region_obj_Expand(this)

    Resizes array to accomodate a new element.

    Arguments

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

    A boundary region object

procedure, public :: Finalize => region_obj_Final

  • private pure subroutine region_obj_Final(this)

    Arguments

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

    A boundary region object

procedure, public :: GetBCIndex => region_obj_GetBCIndex

  • private pure function region_obj_GetBCIndex(this, name) result(val)

    Returns index of a variable in this region, or -1 if not found.

    Arguments

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

    A boundary region object

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

    Name of region

    Return Value integer

    Result

procedure, public :: Initialize => region_obj_Init

  • private pure subroutine region_obj_Init(this, name, xlo, xhi, dir, side)

    Initializes a region

    Arguments

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

    A boundary region object

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

    Name of region

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

    Position of low left corner

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

    Position of high right corner

    integer, intent(in) :: dir

    Direction of normal

    integer, intent(in) :: side

    Side (left or right) of the cell

Source Code

  type :: region_obj
    !> Defines regions where boundary conditions are applied.
    character(len=:), allocatable :: name                                      !! Name of this region
    type(block_obj)               :: region                                    !! Block/grid for this region
    real(wp)                      :: xlo(3)                                    !! Position of lower left corner
    real(wp)                      :: xhi(3)                                    !! Position of upper right corner
    integer                       :: lo(3)=-100                                !! Grid low bound
    integer                       :: hi(3)=-100                                !! Grid hi bound
    integer                       :: dir                                       !! Normal direction (=1,2,3)
    integer                       :: side                                      !! Side (BC_LEFT or BC_RIGHT)
    integer                       :: count=0                                   !! Count of variables defined on this region
    type(bc_obj),     allocatable :: BC(:)                                     !! Variables on this region
    type(hashtbl_obj),  private   :: tbl                                       !! Hash table
    contains
       procedure :: Initialize      => region_obj_Init
       procedure :: Finalize        => region_obj_Final
       procedure :: Add             => region_obj_Add
       procedure :: Expand          => region_obj_Expand
       procedure :: GetBCIndex      => region_obj_GetBCIndex
  end type region_obj