collision_obj Derived Type

type, public :: collision_obj

A utility that handles collisions


Inherits

type~~collision_obj~~InheritsGraph type~collision_obj collision_obj type~block_obj block_obj type~collision_obj->type~block_obj cblock type~marker_set marker_set type~collision_obj->type~marker_set IB type~monitor_set monitor_set type~collision_obj->type~monitor_set monitors type~parallel_obj parallel_obj type~collision_obj->type~parallel_obj parallel type~parser_obj parser_obj type~collision_obj->type~parser_obj parser type~particle_set particle_set type~collision_obj->type~particle_set PP type~respart_set ResPart_set type~collision_obj->type~respart_set RP type~sllist_obj sllist_obj type~collision_obj->type~sllist_obj RPneighbors, PPneighbors, IBneighbors type~timer_obj timer_obj type~collision_obj->type~timer_obj timer 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~marker_set->type~monitor_set monitors type~marker_set->type~parser_obj parser type~marker_set->type~timer_obj timer type~bc_set bc_set type~marker_set->type~bc_set bcs type~lagrangian_set lagrangian_set type~marker_set->type~lagrangian_set type~op_obj op_obj type~marker_set->type~op_obj op type~monitor_set->type~parallel_obj parallel type~hashtbl_obj hashtbl_obj type~monitor_set->type~hashtbl_obj tbl type~monitor_obj monitor_obj type~monitor_set->type~monitor_obj m 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~entry_obj entry_obj type~parser_obj->type~entry_obj entries type~particle_set->type~monitor_set monitors type~particle_set->type~parser_obj parser type~particle_set->type~timer_obj timer type~particle_set->type~lagrangian_set type~particle_set->type~op_obj op type~respart_set->type~marker_set ib type~respart_set->type~monitor_set monitors type~respart_set->type~parser_obj parser type~respart_set->type~timer_obj timer type~respart_set->type~bc_set bcs type~respart_set->type~lagrangian_set type~respart_set->type~op_obj op type~sllist_obj->type~sllist_obj child type~timer_obj->type~parallel_obj parallel type~timer_obj->type~parser_obj parser type~timer_obj->type~hashtbl_obj tbl type~bc_set->type~block_obj block type~bc_set->type~parallel_obj parallel type~bc_set->type~hashtbl_obj tbl type~bc_set->type~hdf5_obj hdf5 type~region_obj region_obj type~bc_set->type~region_obj region MPI_Comm MPI_Comm type~communicators->MPI_Comm w, g type~hashtbl_obj->type~sllist_obj vec type~hdf5_obj->type~parallel_obj parallel type~hdf5_obj->type~hashtbl_obj tbl type~lagrangian_set->type~block_obj block type~lagrangian_set->type~parallel_obj parallel type~lagrangian_set->MPI_Datatype MPI_TYPE type~lagrangian_obj lagrangian_obj type~lagrangian_set->type~lagrangian_obj p, sample type~column_obj column_obj type~monitor_obj->type~column_obj col type~op_obj->type~block_obj block type~op_obj->type~parallel_obj parallel 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

Inherited by

type~~collision_obj~~InheritedByGraph type~collision_obj collision_obj type~cdifs_obj cdifs_obj type~cdifs_obj->type~collision_obj collisions type~grans_obj grans_obj type~grans_obj->type~collision_obj collisions

Components

Type Visibility Attributes Name Initial
type(marker_set), public, pointer :: IB => null()

Immersed solids (walls)

type(sllist_obj), public, allocatable :: IBneighbors(:,:,:)

Singly linked list of neighbors

integer, public, allocatable :: IBobjincell(:,:,:)

Number of objects in this list

type(particle_set), public, pointer :: PP => null()

Point particles

type(sllist_obj), public, allocatable :: PPneighbors(:,:,:)

Singly linked list of neighbors

integer, public, allocatable :: PPobjincell(:,:,:)

Number of objects in this list

type(ResPart_set), public, pointer :: RP => null()

Resolved particles

type(sllist_obj), public, allocatable :: RPneighbors(:,:,:)

Singly linked list of neighbors

integer, public, allocatable :: RPobjincell(:,:,:)

Number of objects in this list

type(block_obj), public :: cblock

Collision block

real(kind=wp), public :: edry

Dry restitution coefficient

type(monitor_set), public, pointer :: monitors => null()

Monitors to print to stdout and files

real(kind=wp), public :: muc

Coulomb friction factor

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

Parallel/MPI utility

type(parser_obj), public, pointer :: parser => null()

Parser for input file

real(kind=wp), public :: tcol

Collision time

type(timer_obj), public, pointer :: timer => null()

Timer utility

logical, public :: use_wall = .false.

Walls for collisions

real(kind=wp), public :: wall_bottom

Wall position at the high bound

integer, public :: wall_dir

Wall normal direction (0=no walls, 1=x1, 2=x2, or 3=x3).

real(kind=wp), public :: wall_top

Wall position at the low bound


Type-Bound Procedures

  • private impure subroutine collision_obj_AddImmersedBoundaries(this, IB)

    Adds an Immersed Boundary to list of collisional objects.

    Arguments

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

    Collision utility

    type(marker_set), intent(in), target :: IB

    Immersed Boundaries

  • private impure subroutine collision_obj_AddResolvedParticles(this, RP)

    Adds Resolved Particles to list of collisional objects.

    Arguments

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

    Collision utility

    type(ResPart_set), intent(in), target :: RP

    Resolved Particles

  • private impure subroutine collision_obj_AddPointParticles(this, PP)

    Adds Point Particles to list of collisional objects.

    Arguments

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

    Collision utility

    type(particle_set), intent(in), target :: PP

    Point particles

procedure, public :: ComputeCollisions => collision_obj_ComputeCollisions

procedure, public :: Finalize => collision_obj_Final

  • private impure subroutine collision_obj_Final(this)

    Finalizes object and frees memory.

    Arguments

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

procedure, public :: Initialize => collision_obj_Init

  • private impure subroutine collision_obj_Init(this, parallel)

    Initializes object.

    Arguments

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

    Collision utility

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

    Parallel structure to link with

procedure, public :: Prepare => collision_obj_Prepare

  • private impure subroutine collision_obj_Prepare(this, timer, parser, monitors)

    Prepares object for use in solvers.

    Arguments

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

    Collision utility

    type(timer_obj), intent(in), target :: timer

    Timer utility

    type(parser_obj), intent(in), target :: parser

    Parser for input file

    type(monitor_set), intent(in), target :: monitors

    Monitors to print to stdout and files

procedure, public :: Sanitize => collision_obj_Sanitize

  • private impure subroutine collision_obj_Sanitize(this)

    Frees data: removes ghost objects and frees neighbor lists.

    Arguments

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

    Collision utility

procedure, public :: SetupCollisionBlock => collision_obj_SetupCollisionBlock

  • private impure subroutine collision_obj_SetupCollisionBlock(this, ds, ngc, block)

    Initializes cblock to handle collisions. This extra block is expected to be coarser than the simulation block, but larger than the maximum object size. It is used to expedite neighbor searches.

    Read more…

    Arguments

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

    Collision utility

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

    Target grid spacing

    integer, intent(in) :: ngc

    Number of ghost cells for collision block

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

    Optional block to conform to

procedure, public :: SetupCollisionBlock2 => collision_obj_SetupCollisionBlock2

  • private impure subroutine collision_obj_SetupCollisionBlock2(this, ds, ngc, block)

    Initializes cblock to handle collisions. This extra block is expected to be coarser than the simulation block, but larger than the maximum object size. It is used to expedite neighbor searches.

    Read more…

    Arguments

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

    Collision utility

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

    Target grid spacing

    integer, intent(in) :: ngc

    Number of ghost cells for collision block

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

    Optional block to conform to

procedure, public :: UpdateGhostObjects => collision_obj_UpdateGhostObjects

  • private impure subroutine collision_obj_UpdateGhostObjects(this)

    Updates ghost objects in preparation for collisions.

    Arguments

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

    Collision utility

procedure, public :: UpdateNeighborList => collision_obj_UpdateNeighborList

  • private impure subroutine collision_obj_UpdateNeighborList(this)

    Updates neighbor lists in preparation for collisions.

    Arguments

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

    Collision utility

procedure, private :: collision_obj_AddImmersedBoundaries

  • private impure subroutine collision_obj_AddImmersedBoundaries(this, IB)

    Adds an Immersed Boundary to list of collisional objects.

    Arguments

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

    Collision utility

    type(marker_set), intent(in), target :: IB

    Immersed Boundaries

procedure, private :: collision_obj_AddPointParticles

  • private impure subroutine collision_obj_AddPointParticles(this, PP)

    Adds Point Particles to list of collisional objects.

    Arguments

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

    Collision utility

    type(particle_set), intent(in), target :: PP

    Point particles

procedure, private :: collision_obj_AddResolvedParticles

  • private impure subroutine collision_obj_AddResolvedParticles(this, RP)

    Adds Resolved Particles to list of collisional objects.

    Arguments

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

    Collision utility

    type(ResPart_set), intent(in), target :: RP

    Resolved Particles

procedure, private :: collision_obj_ComputeCollisionsPPvIB

  • private pure subroutine collision_obj_ComputeCollisionsPPvIB(this)

    Computes collisions between Point Particles and Immersed Boundaries.

    Arguments

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

    Collision utility

procedure, private :: collision_obj_ComputeCollisionsPPvPP

procedure, private :: collision_obj_ComputeCollisionsPPvWALL

procedure, private :: collision_obj_ComputeCollisionsRPvIB

  • private pure subroutine collision_obj_ComputeCollisionsRPvIB(this)

    Computes collisions between Resolved Particles and Immersed Boundaries.

    Arguments

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

    Collision utility

procedure, private :: collision_obj_ComputeCollisionsRPvPP

procedure, private :: collision_obj_ComputeCollisionsRPvRP

procedure, private :: collision_obj_ComputeCollisionsRPvWALL

Source Code

  type :: collision_obj
    !> A utility that handles collisions
    type(parallel_obj),  pointer :: parallel  => null()                        !! Parallel/MPI utility
    type(timer_obj),     pointer :: timer     => null()                        !! Timer utility
    type(parser_obj),    pointer :: parser    => null()                        !! Parser for input file
    type(monitor_set),   pointer :: monitors  => null()                        !! Monitors to print to stdout and files
    type(particle_set),  pointer :: PP        => null()                        !! Point particles
    type(ResPart_set),   pointer :: RP        => null()                        !! Resolved particles
    type(marker_set),    pointer :: IB        => null()                        !! Immersed solids (walls)
    type(block_obj)              :: cblock                                     !! Collision block
    real(wp)                     :: tcol                                       !! Collision time
    real(wp)                     :: edry                                       !! Dry restitution coefficient
    real(wp)                     :: muc                                        !! Coulomb friction factor
    logical                      :: use_wall  = .false.                        !! Walls for collisions
    integer                      :: wall_dir                                   !! Wall normal direction (0=no walls, 1=x1, 2=x2, or 3=x3).
    real(wp)                     :: wall_top                                   !! Wall position at the low bound
    real(wp)                     :: wall_bottom                                !! Wall position at the high bound
    integer,         allocatable :: RPobjincell(:,:,:)                         !! Number of objects in this list
    type(sllist_obj),allocatable :: RPneighbors(:,:,:)                         !! Singly linked list of neighbors
    integer,         allocatable :: PPobjincell(:,:,:)                         !! Number of objects in this list
    type(sllist_obj),allocatable :: PPneighbors(:,:,:)                         !! Singly linked list of neighbors
    integer,         allocatable :: IBobjincell(:,:,:)                         !! Number of objects in this list
    type(sllist_obj),allocatable :: IBneighbors(:,:,:)                         !! Singly linked list of neighbors
    contains
      procedure :: Initialize          => collision_obj_Init
      procedure :: Finalize            => collision_obj_Final
      procedure :: Prepare             => collision_obj_Prepare
      generic   :: Add                 => collision_obj_AddImmersedBoundaries, &
                                          collision_obj_AddResolvedParticles, &
                                          collision_obj_AddPointParticles
      procedure :: SetupCollisionBlock => collision_obj_SetupCollisionBlock
      procedure :: SetupCollisionBlock2=> collision_obj_SetupCollisionBlock2
      procedure :: UpdateGhostObjects  => collision_obj_UpdateGhostObjects
      procedure :: UpdateNeighborList  => collision_obj_UpdateNeighborList
      procedure :: ComputeCollisions   => collision_obj_ComputeCollisions
      procedure :: Sanitize            => collision_obj_Sanitize
      ! Internal/private procedures
      procedure, private :: collision_obj_AddImmersedBoundaries
      procedure, private :: collision_obj_AddResolvedParticles
      procedure, private :: collision_obj_AddPointParticles
      procedure, private :: collision_obj_ComputeCollisionsRPvRP
      procedure, private :: collision_obj_ComputeCollisionsRPvIB
      procedure, private :: collision_obj_ComputeCollisionsRPvWALL
      procedure, private :: collision_obj_ComputeCollisionsPPvPP
      procedure, private :: collision_obj_ComputeCollisionsPPvIB
      procedure, private :: collision_obj_ComputeCollisionsPPvWALL
      procedure, private :: collision_obj_ComputeCollisionsRPvPP
  end type collision_obj