marker_set Derived Type

type, public, extends(lagrangian_set) :: marker_set

A collection of IB markers


Inherits

type~~marker_set~~InheritsGraph type~marker_set marker_set type~lagrangian_set lagrangian_set type~marker_set->type~lagrangian_set type~monitor_set monitor_set type~marker_set->type~monitor_set monitors type~op_obj op_obj type~marker_set->type~op_obj op type~parser_obj parser_obj type~marker_set->type~parser_obj parser type~timer_obj timer_obj type~marker_set->type~timer_obj timer MPI_Datatype MPI_Datatype type~lagrangian_set->MPI_Datatype MPI_TYPE type~block_obj block_obj type~lagrangian_set->type~block_obj block type~lagrangian_obj lagrangian_obj type~lagrangian_set->type~lagrangian_obj p, sample type~parallel_obj parallel_obj type~lagrangian_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~monitor_set->type~parallel_obj parallel type~op_obj->type~block_obj block type~eulerian_obj_i eulerian_obj_i type~op_obj->type~eulerian_obj_i mask type~op_obj->type~parallel_obj parallel type~entry_obj entry_obj type~parser_obj->type~entry_obj entries type~timer_obj->type~parser_obj parser type~timer_obj->type~hashtbl_obj tbl type~timer_obj->type~parallel_obj parallel type~block_obj->MPI_Datatype gc_slab_r, gc_slab_i type~block_obj->type~parallel_obj parallel type~axis_obj axis_obj type~block_obj->type~axis_obj axis, axis_partition type~eulerian_obj_base eulerian_obj_base type~eulerian_obj_i->type~eulerian_obj_base type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec type~column_obj column_obj type~monitor_obj->type~column_obj col type~parallel_obj->MPI_Datatype REAL_SP, REAL_DP, REAL_WP, COMPLEX_SP, COMPLEX_DP, COMPLEX_WP, INTEGER, INT8, LOGICAL MPI_Info MPI_Info type~parallel_obj->MPI_Info mpi_info 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~eulerian_obj_base->type~block_obj block type~eulerian_obj_base->type~parallel_obj parallel type~sllist_obj->type~sllist_obj child

Inherited by

type~~marker_set~~InheritedByGraph type~marker_set marker_set type~cdifs_obj cdifs_obj type~cdifs_obj->type~marker_set IB type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~respart_set ResPart_set type~cdifs_obj->type~respart_set RP type~collision_obj->type~marker_set IB type~collision_obj->type~respart_set RP type~grans_obj grans_obj type~grans_obj->type~marker_set IB type~grans_obj->type~collision_obj collisions type~grans_obj->type~respart_set RP type~respart_set->type~marker_set ib 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
integer, public :: MPI_SIZE = 44

MPI size

type(MPI_Datatype), public :: MPI_TYPE

MPI variable type

integer, public :: R_chunk_size

Read chunk size

type(block_obj), public, pointer :: block => null()

Associated block structure

integer, public :: count = 0

Total count across all MPI ranks

integer, public :: count_ = 0

Local count for this rank

integer, public, allocatable :: count_proc(:)

of lagrangian objects per proc

procedure(kernel_1D), public, nopass, pointer :: g1ex => int_g1_triangle

1D kernel used in extrapolations

procedure(kernel_1D), public, nopass, pointer :: g1in => g1_triangle

1D kernel used in interpolations

logical, public :: is_initialized = .false.

Flag to determine whether this has been initialized

real(kind=wp), public :: l_filter

Half filter width

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

Monitors to print to stdout and files

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

Name of the Lagrangian set

type(op_obj), public, pointer :: op => null()

operators object

logical, public :: overwrite = .true.

Switch to overwrite IO files

class(lagrangian_obj), public, allocatable :: p(:)

Array of Lagrangian_obj or any extended type

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

Associated parallel structure

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

Parser for input file

character(len=str64), public :: read_file

file to read

class(lagrangian_obj), public, allocatable :: sample

Sample used in allocation of polymorphic data

integer, public :: stib = 3

Stencil size for filtering

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

Timer utility

character(len=str64), public :: write_file

file to write


Type-Bound Procedures

procedure, public :: AddPlane => marker_set_AddPlane

  • private subroutine marker_set_AddPlane(this, center, normal, width, vel, dl, tag)

    Add an IB plane

    Arguments

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

    Collection of Resolved Particles

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

    Plane center

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

    Plane normal

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

    Plane extents

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

    Plane velocity

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

    Marker spacing

    integer(kind=8), intent(in), optional :: tag

    Tag

procedure, public :: AddSphere => marker_set_AddSphere

  • private subroutine marker_set_AddSphere(this, center, radius, vel, dl, tag)

    Add an IB sphere

    Arguments

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

    Collection of Resolved Particles

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

    Sphere center

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

    Sphere radius

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

    Sphere velocity

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

    Marker spacing

    integer(kind=8), intent(in), optional :: tag

    Tag

procedure, public :: ApplyPeriodicity => lagrangian_set_ApplyPeriodicity

procedure, public :: CoM => marker_set_CoM

  • private function marker_set_CoM(this) result(CoM)

    Find the center of mass

    Arguments

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

    Set of ib markers

    Return Value real(kind=wp), (3)

    Position of center of mass

procedure, public :: Communicate => lagrangian_set_Communicate

  • private subroutine lagrangian_set_Communicate(this, GetOwnerRankOpt)

    Communicate lagrangian objects across MPI_rank

    Arguments

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

    Set of Lagrangian objects

    procedure(locator), optional :: GetOwnerRankOpt

    MPI Rank locator for communications

procedure, public :: ComputeSolidVolFrac => marker_set_ComputeSolidVolFrac

  • private subroutine marker_set_ComputeSolidVolFrac(this, VF, solver, MaxTol, MaxIt, RelaxType, Rel, It, intRHS)

    Compute the solid volume fraction on the mesh

    Arguments

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

    Set of ib markers

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

    Volume fraction

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

    Name of solver to be used

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

    Maximum relative tolerance

    integer, intent(in) :: MaxIt

    Maximum number of subiterations

    integer, intent(in), optional :: RelaxType

    Relaxation type

    real(kind=wp), intent(out), optional :: Rel

    Relative error at end of solve

    integer, intent(out), optional :: It

    Number of iterations performed

    real(kind=wp), intent(out), optional :: intRHS

    Magnitude of RHS

procedure, public :: CreateMPIType => lagrangian_set_CreateMPIType

procedure, public :: Filter => marker_set_Filter

  • private subroutine marker_set_Filter(this, var, field)

    Compute a filtered quantity on the eulerian grid

    Arguments

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

    Set of ib markers

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

    Variable to compute

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

    Filtered quantity

generic, public :: Finalize => lagrangian_set_Final

  • private subroutine ResPart_set_Final(this)

    Finalize the ResPart_set type. This subourtine replaces the inheritted lagrangian_final.

    Arguments

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

    Set of resolved partilces

procedure, public :: FreeMPIType => lagrangian_set_FreeMPIType

procedure, public :: GetIBForcing => marker_set_GetIBForcing2

  • private subroutine marker_set_GetIBForcing2(this, Um, Vm, Wm, rhof, SA, ibF, dt)

    Compute the IB forcing Interpolation is carried out by linear interpolation.

    Arguments

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

    Collection of Resolved Particles

    type(eulerian_obj_r), intent(in) :: Um

    Velocity in 1-dir

    type(eulerian_obj_r), intent(in) :: Vm

    Velocity in 2-dir

    type(eulerian_obj_r), intent(in) :: Wm

    Velocity in 3-dir

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

    Fluid density

    type(eulerian_obj_r), intent(in) :: SA

    Surface area

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

    IB forcing

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

    Timestep

procedure, public :: GetOwnerRankByBlock => lagrangian_set_GetOwnerRankByBlock

  • private function lagrangian_set_GetOwnerRankByBlock(this, lagobj) result(rank)

    Returns the MPI rank that should own this lagrangian object based on which block it belongs to

    Arguments

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

    A set of Lagrangian objects

    class(lagrangian_obj), intent(in) :: lagobj

    Lagrangian obj to locate

    Return Value integer

    rank that should own lagobj

procedure, public :: GetReadFileName => lagrangian_set_GetReadFileName

  • private function lagrangian_set_GetReadFileName(this) result(name)

    Return the base name of file to write

    Arguments

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

    A collection of Eulerian objects

    Return Value character(len=str64)

    Name of file

procedure, public :: GetWriteFileName => lagrangian_set_GetWriteFileName

  • private function lagrangian_set_GetWriteFileName(this) result(name)

    Return the base name of file to write

    Arguments

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

    A collection of Eulerian objects

    Return Value character(len=str64)

    Name of file

procedure, public :: Info => lagrangian_set_Info

  • private subroutine lagrangian_set_Info(this)

    Prints diagnostics information about the derived type

    Arguments

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

    Lagrangian array to dump

generic, public :: Initialize => lagrangian_set_Init

  • private subroutine ResPart_set_Init(this, name, block, parallel)

    Initialize the ResPart_set type. This subourtine replaces the inheritted lagrangian_init.

    Arguments

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

    Set of resolved partilces

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

    Name of instance

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

    A block object

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

    parallel structure from main program

procedure, public :: LoadSTL => marker_set_LoadSTL

  • private subroutine marker_set_LoadSTL(this, STL_file)

    Load markers from a binary STL. This is a serial routine.

    Arguments

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

    Set of ib markers

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

    Variable to compute

procedure, public :: Localize => lagrangian_set_Localize

  • private subroutine lagrangian_set_Localize(this)

    Localize a Lagrangian object on the grid Returns the location of the closest collocated cell (staggering=0

    Arguments

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

    Lagrangian array to dump

procedure, public :: Prepare => marker_set_Prepare

  • private subroutine marker_set_Prepare(this, timer, parser, operators, monitors, update_time)

    Prepare marker_set for use with solvers

    Arguments

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

    Immersed boundary

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

    Timer utility

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

    Parser for input file

    type(op_obj), intent(in), target :: operators

    Operators object

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

    Monitors to print to stdout and files

    logical, intent(in), optional :: update_time

    Update time and iteration based on read file

procedure, public :: Read => marker_set_Read

  • private subroutine marker_set_Read(this, iter, time, step)

    Read marker data from file in parallel

    Arguments

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

    Set of ib markers

    integer, intent(out) :: iter

    Iteration at write

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

    Time at write

    integer, intent(in), optional :: step

    User supplied step to open

procedure, public :: Recycle => lagrangian_set_Recycle

  • private subroutine lagrangian_set_Recycle(this)

    Sorting routine: stacks active lagrangian objects at the beginning of the array then resizes

    Arguments

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

    Lagrangian array to dump

procedure, public :: Resize => lagrangian_set_Resize

  • private subroutine lagrangian_set_Resize(this, n)

    Changes the size of an array of Lagrangian objects

    Arguments

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

    Lagrangian array to dump

    integer, intent(in) :: n

    New size

procedure, public :: SetFilterKernel => lagrangian_set_SetFilterKernel

  • private subroutine lagrangian_set_SetFilterKernel(this, kernel_interp, kernel_extrap)

    Reset the filter kerrnel Default is Triangle for interpolation and extrapolation

    Arguments

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

    Set of Lagrangian objects

    integer, intent(in) :: kernel_interp

    Filter kernel for interpolations

    integer, intent(in) :: kernel_extrap

    Filter kernel for extrapolations

procedure, public :: SetFilterSize => lagrangian_set_SetFilterSize

  • private subroutine lagrangian_set_SetFilterSize(this, l_filter)

    Adjust the size of the filter

    Arguments

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

    Set of Lagrangian objects

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

    Filter size

procedure, public :: SetMPIDataTypeParams => marker_set_SetMPIDataTypeParams

  • private subroutine marker_set_SetMPIDataTypeParams(this, types, lengths, displacement)

    Set up parameters used when creating the MPI derived type Create the MPI structure

    Arguments

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

    Set of ib markers

    type(MPI_Datatype), intent(out), allocatable :: types(:)

    Array of types

    integer, intent(out), allocatable :: lengths(:)

    Array of lengths

    integer(kind=MPI_ADDRESS_KIND), intent(out), allocatable :: displacement(:)

    Array of displacements

procedure, public :: SetObjectType => marker_set_SetObjectType

  • private subroutine marker_set_SetObjectType(this)

    Set the sample type used in allocation of polymorphic variables

    Arguments

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

    Set of ib markers

procedure, public :: SetOverwrite => lagrangian_set_SetOverwrite

  • private subroutine lagrangian_set_SetOverwrite(this, overwrite)

    Set file overwritting

    Arguments

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

    A collection of Eulerian objects

    logical, intent(in) :: overwrite

    Name of file

procedure, public :: SetReadChunkSize => marker_set_SetReadChunkSize

  • private subroutine marker_set_SetReadChunkSize(this, chunk_size)

    Set the chunk size.

    Arguments

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

    Set of ib markers

    integer, intent(in) :: chunk_size

    Chunk size

procedure, public :: SetReadFileName => lagrangian_set_SetReadFileName

  • private subroutine lagrangian_set_SetReadFileName(this, name)

    Set the base name of file to read

    Arguments

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

    A collection of Eulerian objects

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

    Name of file

procedure, public :: SetWriteFileName => lagrangian_set_SetWriteFileName

  • private subroutine lagrangian_set_SetWriteFileName(this, name)

    Set the base name of file to write

    Arguments

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

    A collection of Eulerian objects

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

    Name of file

procedure, public :: UpdateCount => lagrangian_set_UpdateCount

  • private subroutine lagrangian_set_UpdateCount(this)

    Updates the total count of Lagrangian objects

    Arguments

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

    Lagrangian array to dump

procedure, public :: UpdateGhostObjects => lagrangian_set_UpdateGhostObjects

  • private subroutine lagrangian_set_UpdateGhostObjects(this, dist)

    Updates ghost objects Copies objects that lie "dist"-away from the block's boundaries to neighboring MPI-ranks and designate copies as Ghost Objects (id<0)

    Arguments

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

    Set of Lagrangian objects

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

    Distance from boundaries

procedure, public :: UpdateNormals => marker_set_UpdateNormals

procedure, public :: UpdateSDF => marker_set_UpdateSDF

  • private subroutine marker_set_UpdateSDF(this, SA)

    Updates the Surface Density Function

    Arguments

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

    Immersed boundary

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

procedure, public :: Write => marker_set_Write

  • private subroutine marker_set_Write(this, iter, time)

    Write marker data to file in parallel

    Arguments

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

    Set of ib markers

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

procedure, public :: lagrangian_set_Final => marker_set_Final

  • private subroutine marker_set_Final(this)

    Finalize the marker_set type. This subourtine replaces the inheritted lagrangian_final.

    Arguments

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

    Set of ib markers

procedure, public :: lagrangian_set_Init => marker_set_Init

  • private subroutine marker_set_Init(this, name, block, parallel)

    Initialize the marker_set type. This subourtine replaces the inheritted lagrangian_init.

    Arguments

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

    Set of ib markers

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

    Name of instance

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

    A block object

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

    parallel structure from main program