bc_set Derived Type

type, public :: bc_set

Collection of regions


Inherits

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

Inherited by

type~~bc_set~~InheritedByGraph type~bc_set bc_set 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(block_obj), public, pointer :: block => null()

Associated block structure

integer, public :: count = 0

Total number of regions across all MPI ranks

type(hdf5_obj), public, pointer :: hdf5 => null()

HDF5 object for IO

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

Associated parallel structure

type(region_obj), public, allocatable :: region(:)

Array of regions

type(hashtbl_obj), private :: tbl

Hash table


Type-Bound Procedures

procedure, public :: Add => bc_set_Add

  • private impure subroutine bc_set_Add(this, name, xlo, xhi, normal)

    Adds a new region to bc_set.

    Arguments

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

    Boundary conditions utility

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

    Name of region

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

    Position of lower left corner

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

    Position of upper right corner

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

    Oriented normal

procedure, public :: BuildMask => bc_set_BuildMask

  • private impure subroutine bc_set_BuildMask(this, name, mask)

    Builds an integer field, where cells=0 denotes interior cells, and cells=1 denotes boundary cells for input variable.

    Arguments

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

    Boundary conditions utility

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

    Name of the variable

    type(eulerian_obj_i), intent(inout) :: mask

    Mask for this variable

procedure, public :: CheckBCExists => bc_set_CheckBCExists

  • private pure function bc_set_CheckBCExists(this, region, var) result(val)

    Checks whether there is BC for a given variable on a given region.

    Arguments

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

    Boundary conditions utility

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

    Region name

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

    Variable name

    Return Value logical

    Result

procedure, public, nopass :: CheckBounds => bc_set_CheckBounds

  • private pure function bc_set_CheckBounds(xlo, xhi) result(val)

    Makes sure bounds represent a plane.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=wp), intent(in) :: xlo(3)

    Lower left corner

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

    Upper right corner

    Return Value logical

    True, if bounds represent a plane

procedure, public :: Expand => bc_set_Expand

  • private pure subroutine bc_set_Expand(this)

    Resizes array to accomodate a new element.

    Arguments

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

    Boundary conditions utility

procedure, public :: Finalize => bc_set_Final

  • private pure subroutine bc_set_Final(this)

    Finalizes bc_set and frees memory.

    Arguments

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

    Boundary conditions utility

procedure, public :: GetBCPointer => bc_set_GetBCPointer

  • private impure subroutine bc_set_GetBCPointer(this, region, var, val)

    Fetches a pointer to the val array describing the Dirichlet or Neumann BC of a given variable on a given region.

    Arguments

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

    Boundary conditions utility

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

    Region name

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

    Variable name

    real(kind=wp), intent(inout), pointer :: val(:,:,:)

    Pointer

procedure, public :: GetBCType => bc_set_GetBCType

  • private pure function bc_set_GetBCType(this, region, var) result(val)

    Arguments

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

    Boundary conditions utility

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

    Region name

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

    Variable name

    Return Value integer

    Result

procedure, public :: GetExtents => bc_set_GetExtents

  • private pure function bc_set_GetExtents(this, name) result(extents)

    Returns the extents (lo and hi bounds) of a region.

    Arguments

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

    Boundary conditions utility

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

    Region name

    Return Value type(extent_obj)

    Result

procedure, public :: GetRegionIndex => bc_set_GetRegionIndex

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

    Returns the index of a region, or -1 if not found.

    Arguments

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

    Boundary conditions utility

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

    Region name

    Return Value integer

    Result

procedure, public :: GetSideDirByNormal => bc_set_GetSideDirByNormal

  • private impure subroutine bc_set_GetSideDirByNormal(this, normal, side, dir)

    Arguments

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

    Boundary conditions utility

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

    String denoting the normal direction

    integer, intent(out) :: side

    Side (=BC_LEFT,BC_RIGHT)

    integer, intent(out) :: dir

    Direction (=1,2,3,)

procedure, public :: GetSideDirByRegion => bc_set_GetSideDirByRegion

  • private pure subroutine bc_set_GetSideDirByRegion(this, region, side, dir)

    Arguments

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

    Boundary conditions utility

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

    Region name

    integer, intent(out) :: side

    Side (=BC_LEFT,BC_RIGHT)

    integer, intent(out) :: dir

    Direction (=1,2,3,)

procedure, public :: Info => bc_set_Info

  • private impure subroutine bc_set_Info(this)

    Prints to stdout information on bc_set, for debugging.

    Arguments

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

    Boundary conditions utility

procedure, public :: Initialize => bc_set_Init

  • private impure subroutine bc_set_Init(this, block, parallel)

    Initializes bc_set.

    Arguments

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

    Boundary conditions utility

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

    A block object

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

    Parallel structure to link with

procedure, public :: Read => bc_set_Read

  • private impure subroutine bc_set_Read(this, iter, time, name)

    Reads boundary conditions from file.

    Arguments

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

    Boundary conditions utility

    integer, intent(out) :: iter

    Iteration read from file

    real(kind=wp), intent(out) :: time

    Time read from file

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

    Name of file to write

procedure, public :: SetBC => bc_set_SetBC

  • private impure subroutine bc_set_SetBC(this, region, type, var)

    Sets boundary condition of a given type, for a given variable on a given region.

    Arguments

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

    Boundary conditions utility

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

    Region name

    integer, intent(in) :: type

    BC type

    character(len=*), intent(in), optional :: var

    Variable name

generic, public :: UpdateBoundary => bc_set_UpdateBoundaryScalar, bc_set_UpdateBoundaryVector

  • private impure subroutine bc_set_UpdateBoundaryScalar(this, var)

    Imposes boundary conditions for a scalar variable.

    Arguments

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

    Boundary conditions utility

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

  • private impure subroutine bc_set_UpdateBoundaryVector(this, var)

    Imposes boundary conditions for a vector field. For symmetry BC, the sign depends is 'plus' or 'minus' depending on the alignment between the vector component and the symmetry direction.

    Arguments

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

    Boundary conditions utility

    type(eulerian_obj_r), intent(inout) :: var(3)

    Eulerian variable

procedure, public :: UpdateBoundaryDirichlet => bc_set_UpdateBoundaryDirichlet

  • private impure subroutine bc_set_UpdateBoundaryDirichlet(this, region, var)

    Updates ghost cells to enforce Dirichlet BC

    Read more…

    Arguments

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

    Boundary conditions utility

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

    Region name

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

procedure, public :: UpdateBoundaryNeumann => bc_set_UpdateBoundaryNeumann

  • private impure subroutine bc_set_UpdateBoundaryNeumann(this, region, var)

    Updates ghostcells to enforce Neumann BC.

    Arguments

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

    Boundary conditions utility

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

    Region name

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

procedure, public :: UpdateBoundarySymmetryMinus => bc_set_UpdateBoundarySymmetryMinus

  • private impure subroutine bc_set_UpdateBoundarySymmetryMinus(this, region, var)

    Updates ghostcells to enforce symmetry BC. Minus version.

    Read more…

    Arguments

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

    Boundary conditions utility

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

    Region name

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

procedure, public :: UpdateBoundarySymmetryPlus => bc_set_UpdateBoundarySymmetryPlus

  • private impure subroutine bc_set_UpdateBoundarySymmetryPlus(this, region, var)

    Updates ghostcells to enforce symmetry BC. Plus version.

    Read more…

    Arguments

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

    Boundary conditions utility

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

    Region name

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

procedure, public :: UpdateExtents => bc_set_UpdateExtents

  • private pure subroutine bc_set_UpdateExtents(this, name)

    Finds the intersection between block owned by this MPI rank, and the plane defining the region.

    Arguments

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

    Boundary conditions utility

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

    Region name

procedure, public :: Write => bc_set_Write

  • private impure subroutine bc_set_Write(this, iter, time, name)

    Writes bc_set to disk using HDF5. The file structure follows this convention:

    Read more…

    Arguments

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

    Boundary conditions utility

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

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

    Name of file to write

procedure, private :: bc_set_UpdateBoundaryScalar

  • private impure subroutine bc_set_UpdateBoundaryScalar(this, var)

    Imposes boundary conditions for a scalar variable.

    Arguments

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

    Boundary conditions utility

    type(eulerian_obj_r), intent(inout) :: var

    Eulerian variable

procedure, private :: bc_set_UpdateBoundaryVector

  • private impure subroutine bc_set_UpdateBoundaryVector(this, var)

    Imposes boundary conditions for a vector field. For symmetry BC, the sign depends is 'plus' or 'minus' depending on the alignment between the vector component and the symmetry direction.

    Arguments

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

    Boundary conditions utility

    type(eulerian_obj_r), intent(inout) :: var(3)

    Eulerian variable

Source Code

  type :: bc_set
    !> Collection of regions
    type(region_obj), allocatable:: region(:)                                  !! Array of regions
    type(parallel_obj),  pointer :: parallel => null()                         !! Associated parallel structure
    type(block_obj),     pointer :: block    => null()                         !! Associated block structure
    type(hdf5_obj),      pointer :: hdf5     => null()                         !! HDF5 object for IO
    type(hashtbl_obj),   private :: tbl                                        !! Hash table
    integer                      :: count  = 0                                 !! Total number of regions across all MPI ranks
    contains
      procedure :: Initialize          => bc_set_Init
      procedure :: Finalize            => bc_set_Final
      procedure :: Add                 => bc_set_Add
      procedure :: Expand              => bc_set_Expand
      procedure :: UpdateExtents       => bc_set_UpdateExtents
      procedure :: BuildMask           => bc_set_BuildMask
      procedure :: GetRegionIndex      => bc_set_GetRegionIndex
      procedure :: GetExtents          => bc_set_GetExtents
      procedure :: SetBC               => bc_set_SetBC
      procedure :: GetSideDirByNormal  => bc_set_GetSideDirByNormal
      procedure :: GetSideDirByRegion  => bc_set_GetSideDirByRegion
      procedure :: GetBCType           => bc_set_GetBCType
      procedure :: GetBCPointer        => bc_set_GetBCPointer
      generic   :: UpdateBoundary      => bc_set_UpdateBoundaryScalar, &
                                          bc_set_UpdateBoundaryVector
      procedure :: UpdateBoundaryDirichlet &
                                       => bc_set_UpdateBoundaryDirichlet
      procedure :: UpdateBoundaryNeumann &
                                       => bc_set_UpdateBoundaryNeumann
      procedure :: UpdateBoundarySymmetryPlus  &
                                       => bc_set_UpdateBoundarySymmetryPlus
      procedure :: UpdateBoundarySymmetryMinus &
                                       => bc_set_UpdateBoundarySymmetryMinus
      procedure :: Info                => bc_set_Info
      procedure :: Write               => bc_set_Write
      procedure :: Read                => bc_set_Read
      procedure, nopass :: CheckBounds => bc_set_CheckBounds
      procedure :: CheckBCExists       => bc_set_CheckBCExists
      ! Internal/private procedures
      procedure, private :: bc_set_UpdateBoundaryScalar
      procedure, private :: bc_set_UpdateBoundaryVector
  end type bc_set