ResPart_set Derived Type

type, public, extends(lagrangian_set) :: ResPart_set

An extended Lagrgian set representing resolved particles


Inherits

type~~respart_set~~InheritsGraph type~respart_set ResPart_set type~bc_set bc_set type~respart_set->type~bc_set bcs type~lagrangian_set lagrangian_set type~respart_set->type~lagrangian_set type~marker_set marker_set type~respart_set->type~marker_set ib type~monitor_set monitor_set type~respart_set->type~monitor_set monitors type~op_obj op_obj type~respart_set->type~op_obj op type~parser_obj parser_obj type~respart_set->type~parser_obj parser type~timer_obj timer_obj type~respart_set->type~timer_obj timer 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 MPI_Datatype MPI_Datatype type~lagrangian_set->MPI_Datatype MPI_TYPE type~lagrangian_set->type~block_obj block type~lagrangian_obj lagrangian_obj type~lagrangian_set->type~lagrangian_obj p, sample type~lagrangian_set->type~parallel_obj parallel type~marker_set->type~bc_set bcs type~marker_set->type~lagrangian_set type~marker_set->type~monitor_set monitors type~marker_set->type~op_obj op type~marker_set->type~parser_obj parser type~marker_set->type~timer_obj timer 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~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~hdf5_obj hdf5 type~block_obj->type~parallel_obj parallel 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~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 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~~respart_set~~InheritedByGraph type~respart_set ResPart_set type~cdifs_obj cdifs_obj type~cdifs_obj->type~respart_set RP type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~collision_obj->type~respart_set RP type~grans_obj grans_obj type~grans_obj->type~respart_set RP type~grans_obj->type~collision_obj collisions

Components

Type Visibility Attributes Name Initial
real(kind=wp), public :: CPG(3) = 0.0_wp

Constant Pressure Gradient forcing

type(bc_set), public, pointer :: bcs => null()

boundary conditions object

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(:)

Nbr of lagrangian objects per proc

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

1D kernel used in extrapolations

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

1D kernel used in interpolations

real(kind=wp), public :: gravity(3) = 0.0_wp

Gravity

type(marker_set), public :: ib

Immersed boundary

logical, public :: is_initialized = .false.

Flag to determine whether this has been initialized

real(kind=wp), public :: l_filter

Half filter width

integer, public, allocatable :: lookup(:)

Lookup array

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

integer, public, allocatable :: ranks(:)

MPI ranks of the lagrangian objects

character(len=str64), public :: read_file

File to read

real(kind=wp), public :: rhof = 1.0_wp

Fluid density

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 :: AdvanceCenters => ResPart_set_AdvanceCenters

  • private pure subroutine ResPart_set_AdvanceCenters(this, dt)

    Advances centers to next timestep

    Arguments

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

    Collection of Resolved Particles

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

    Timestep

procedure, public :: AdvanceMarkers => ResPart_set_AdvanceMarkers

  • private pure subroutine ResPart_set_AdvanceMarkers(this, dt)

    Advances markers to next timestep

    Arguments

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

    Collection of Resolved Particles

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

    Timestep

procedure, public :: ApplyPeriodicity => lagrangian_set_ApplyPeriodicity

procedure, public :: Communicate => lagrangian_set_Communicate

  • private impure subroutine lagrangian_set_Communicate(this, GetOwnerRankOpt)

    Communicates lagrangian objects across MPI_rank. This subroutine relies on a rank locator procedure (GetOwnerRankOpt) to determine the rank that should own each Lagrangian object. The default rank locator is the one provided by the block object associated with this Lagrangian_set. From there, each rank will send objects that they no longer own and receive objects from other ranks that belongs to it. Note that this subroutine allocates an array (buf_send) of size (MAX NUMBER of OBJECTS to SEND) x (NUMBER OF MPI RANKS) For massively parallel simulations, this may cause out of memory issues. In those cases, care must be exercised to reduce the number of objects to be sent at any given time (e.g.: by doing communications in small batches).

    Arguments

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

    A set of Lagrangian objects

    procedure(locator), optional :: GetOwnerRankOpt

    MPI Rank locator for communications

procedure, public :: CreateMPIType => lagrangian_set_CreateMPIType

  • private impure subroutine lagrangian_set_CreateMPIType(this)

    Creates an MPI data type for parallel communication of the Lagrangian objects.

    Arguments

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

    A set of Lagrangian objects

procedure, public :: CreateMonitor => ResPart_set_CreateMonitor

  • private impure subroutine ResPart_set_CreateMonitor(this)

    Creates monitor file for Resolved Particles

    Arguments

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

    Collection of Resolved Particles

procedure, public :: Filter => ResPart_set_Filter

  • private impure subroutine ResPart_set_Filter(this, var, field)

    Filters a quantity to the Eulerian grid

    Arguments

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

    Set of resolved particles

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

    Variable to compute

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

    Filtered quantity

generic, public :: Finalize => lagrangian_set_Final

  • private impure subroutine ResPart_set_Final(this)

    Finalizes 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 :: GetCentroidVF => ResPart_set_GetCentroidVF

  • private impure function ResPart_set_GetCentroidVF(this, ibVF) result(val)

    Computes average solid volume fraction at particle centroids

    Arguments

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

    Collection of Resolved Particles

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

    Solid volume fraction

    Return Value real(kind=wp)

    Mean solid volume fraction at particle centroids

procedure, public :: GetHydroForces => ResPart_set_GetHydroForces

  • private impure subroutine ResPart_set_GetHydroForces(this, P, U, V, W, ibVF, visc)

    Computes hydrodynamic force on particle.

    Arguments

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

    Collection of Resolved Particles

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

    Fluid pressure field

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

    Fluid velocity field in 1-dir

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

    Fluid velocity field in 2-dir

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

    Fluid velocity field in 3-dir

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

    Solid volume fraction

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

    Fluid viscosity

procedure, public :: GetIBForcing => ResPart_set_GetIBForcing

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

    Computes the IB forcing

    Arguments

    Type IntentOptional Attributes Name
    class(ResPart_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 :: GetOverwrite => lagrangian_set_GetOverwrite

  • private pure function lagrangian_set_GetOverwrite(this) result(val)

    Returns whether overwriting is true or false.

    Arguments

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

    A set of Lagrangian objects

    Return Value logical

    Overwrite value

procedure, public :: GetReadFileName => lagrangian_set_GetReadFileName

  • private pure function lagrangian_set_GetReadFileName(this) result(name)

    Returns the base name of file to read.

    Arguments

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

    A set of Lagrangian objects

    Return Value character(len=str64)

    Name of file

procedure, public :: GetSurfaceStresses => ResPart_set_GetSurfaceStresses

  • private impure subroutine ResPart_set_GetSurfaceStresses(this, P, U, V, W, ibVF, visc)

    Computes hydrodynamic stresses on markers

    Arguments

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

    Collection of Resolved Particles

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

    Fluid pressure field

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

    Fluid velocity field in 1-dir

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

    Fluid velocity field in 2-dir

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

    Fluid velocity field in 3-dir

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

    Solid volume fraction

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

    Fluid viscosity

procedure, public :: GetWriteFileName => lagrangian_set_GetWriteFileName

  • private pure function lagrangian_set_GetWriteFileName(this) result(name)

    Returns the base name of file to write.

    Arguments

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

    A set of Lagrangian objects

    Return Value character(len=str64)

    Name of file

procedure, public :: Info => lagrangian_set_Info

  • private impure subroutine lagrangian_set_Info(this)

    Prints diagnostics information about the derived type to the standard output.

    Arguments

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

    A set of Lagrangian objects

generic, public :: Initialize => lagrangian_set_Init

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

    Initializes 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 to link with

procedure, public :: Localize => lagrangian_set_Localize

  • private pure subroutine lagrangian_set_Localize(this)

    Localizes all Lagrangian object on the grid. For each Lagrangian object in the set, this subroutine finds the cell (staggering=0) where this object is located and updates its cell indices.

    Arguments

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

    A set of Lagrangian objects

procedure, public :: Prepare => ResPart_set_Prepare

  • private impure subroutine ResPart_set_Prepare(this, timer, parser, operators, bcs, monitors, update_time)

    Prepares ResPart_set for use with solvers.

    Arguments

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

    Collection of Resolved Particles

    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(bc_set), intent(in), target :: bcs

    Boundary conditions 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 => ResPart_set_ReadH5HUT

  • private impure subroutine ResPart_set_ReadH5HUT(this, iter, time, step)

    Reads ResPart data from file using H5HUT.

    Arguments

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

    Set of resolved particles

    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 :: ReadH5HUT => ResPart_set_ReadH5HUT

  • private impure subroutine ResPart_set_ReadH5HUT(this, iter, time, step)

    Reads ResPart data from file using H5HUT.

    Arguments

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

    Set of resolved particles

    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 :: ReadHDF5 => ResPart_set_ReadHDF5

  • private impure subroutine ResPart_set_ReadHDF5(this, iter, time)

    Reads ResPart data from file with HDF5.

    Arguments

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

    Set of resolved particles

    integer, intent(out) :: iter

    Iteration at write

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

    Time at write

procedure, public :: Recycle => lagrangian_set_Recycle

  • private pure subroutine lagrangian_set_Recycle(this)

    Sorting routine: stacks active lagrangian objects (i.e., who's id is >=1) at the beginning of the array then resizes. Objects with id <= 0 (such as ghost objects) are removed by this subroutine.

    Arguments

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

    A set of Lagrangian objects

procedure, public :: Regroup => ResPart_set_Regroup

  • private impure subroutine ResPart_set_Regroup(this)

    Regroup markers with their respective centroids on the same MPI block

    Arguments

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

    Set of resolved particles

procedure, public :: Resize => lagrangian_set_Resize

  • private pure subroutine lagrangian_set_Resize(this, n)

    Changes the size of an array of Lagrangian objects. To avoid excessive reallocating, the object array will be reallocated only if the new size is (1+RESIZE_INCREMENT) larger or (1-RESIZE_INCREMENT) smaller than previous size. When the size change does not justify reallocating, the excess objects at the end tail of the object array will be marked as inactive with a large negative ID.

    Arguments

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

    A set of Lagrangian objects

    integer, intent(in) :: n

    New target size

procedure, public :: SetFilterKernel => lagrangian_set_SetFilterKernel

  • private pure subroutine lagrangian_set_SetFilterKernel(this, kernel_interp, kernel_extrap)

    Sets the interpolation and extrapolation filter kernels. Default is the Triangle kernel.

    Arguments

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

    A 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 => ResPart_set_SetFilterSize

  • private impure subroutine ResPart_set_SetFilterSize(this, l_filter)

    Filters a quantity to the Eulerian grid

    Arguments

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

    Set of resolved particles

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

    Filter size

procedure, public :: SetMPIDataTypeParams => ResPart_set_SetMPIDataTypeParams

  • private impure subroutine ResPart_set_SetMPIDataTypeParams(this, types, lengths, displacement)

    Sets up parameters used when creating the MPI derived type.

    Arguments

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

    Set of resolved particles

    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 => ResPart_set_SetObjectType

  • private pure subroutine ResPart_set_SetObjectType(this)

    Sets the sample type used in allocation of polymorphic variables.

    Arguments

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

    Set of resolved particles

procedure, public :: SetOverwrite => lagrangian_set_SetOverwrite

  • private pure subroutine lagrangian_set_SetOverwrite(this, overwrite)

    Sets file overwritting.

    Arguments

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

    A set of Lagrangian objects

    logical, intent(in) :: overwrite

    Overwrite value

procedure, public :: SetReadFileName => ResPart_set_SetReadFileName

  • private pure subroutine ResPart_set_SetReadFileName(this, name)

    Sets the base name of file to read.

    Arguments

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

    Set of resolved particles

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

    Name of file

procedure, public :: SetWriteFileName => ResPart_set_SetWriteFileName

  • private pure subroutine ResPart_set_SetWriteFileName(this, name)

    Sets the base name of file to write.

    Arguments

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

    Set of resolved particles

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

    Name of file

procedure, public :: StoreOld => ResPart_set_StoreOld

  • private pure subroutine ResPart_set_StoreOld(this)

    Stores values from previous timestep

    Arguments

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

    Collection of Resolved Particles

procedure, public :: UpdateCount => lagrangian_set_UpdateCount

  • private impure subroutine lagrangian_set_UpdateCount(this)

    Updates the total count of Lagrangian objects.

    Arguments

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

    A set of Lagrangian objects

procedure, public :: UpdateGhostObjects => lagrangian_set_UpdateGhostObjects

  • private impure 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). This subroutine will also update the local count (i.e., this%count_) to (NBR of ACTIVE OBJECTS) + (NBR of GHOST OBJECTS). However, the global count (this%count) will remain unchanged (i.e., equal to the total count of active ojbects only)0

    Arguments

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

    A set of Lagrangian objects

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

    Distance from boundaries

procedure, public :: UpdateLookup => ResPart_set_UpdateLookup

  • private pure subroutine ResPart_set_UpdateLookup(this)

    Update lookup array -- The lookup array returns the local (MPI rank) index of a centroid when given the global ID of that centroid

    Arguments

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

    Set of resolved particles

procedure, public :: UpdateMonitor => ResPart_set_UpdateMonitor

procedure, public :: UpdateNormals => ResPart_set_UpdateNormals

  • private impure subroutine ResPart_set_UpdateNormals(this, ibN)

    Updates the Normals field

    Arguments

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

    Collection of Resolved Particles

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

    Normals field

procedure, public :: UpdateSDF => ResPart_set_UpdateSDF

  • private impure subroutine ResPart_set_UpdateSDF(this, SDF)

    Updates the Surface Density Function

    Arguments

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

    Collection of Resolved Particles

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

    Surface density function

procedure, public :: Write => ResPart_set_WriteH5HUT

  • private impure subroutine ResPart_set_WriteH5HUT(this, iter, time)

    Writes ResPart data to file using H5HUT.

    Arguments

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

    Set of resolved particles

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

procedure, public :: WriteH5HUT => ResPart_set_WriteH5HUT

  • private impure subroutine ResPart_set_WriteH5HUT(this, iter, time)

    Writes ResPart data to file using H5HUT.

    Arguments

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

    Set of resolved particles

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

procedure, public :: WriteHDF5 => ResPart_set_WriteHDF5

  • private impure subroutine ResPart_set_WriteHDF5(this, iter, time)

    Writes ResPart data to file using HDF5.

    Arguments

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

    Set of resolved particles

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

procedure, public :: WriteSilo => ResPart_set_WriteSILO

  • private impure subroutine ResPart_set_WriteSILO(this, iter, time, list)

    Writes data to disk in Silo format.

    Arguments

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

    Set of resolved particles

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

    character(len=str8), intent(in), optional :: list(:)

    Names of components to write

procedure, public :: lagrangian_set_Final => ResPart_set_Final

  • private impure subroutine ResPart_set_Final(this)

    Finalizes 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 :: lagrangian_set_Init => ResPart_set_Init

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

    Initializes 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 to link with

Source Code

  type, extends(lagrangian_set):: ResPart_set
    !> An extended Lagrgian set representing resolved particles
    type(marker_set)           :: ib                                           !! Immersed boundary
    integer,       allocatable :: lookup(:)                                    !! Lookup array
    integer,       allocatable :: ranks(:)                                     !! MPI ranks of the lagrangian objects
    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(op_obj),      pointer :: op        => null()                          !! operators object
    type(bc_set),      pointer :: bcs       => null()                          !! boundary conditions object
    real(wp)                   :: gravity(3) = 0.0_wp                          !! Gravity
    real(wp)                   :: CPG(3)     = 0.0_wp                          !! Constant Pressure Gradient forcing
    real(wp)                   :: rhof       = 1.0_wp                          !! Fluid density
    contains
      procedure :: lagrangian_set_Init      => ResPart_set_Init
      procedure :: lagrangian_set_Final     => ResPart_set_Final
      ! Solver subroutines
      procedure :: Prepare                  => ResPart_set_Prepare
      procedure :: StoreOld                 => ResPart_set_StoreOld
      procedure :: AdvanceCenters           => ResPart_set_AdvanceCenters
      procedure :: AdvanceMarkers           => ResPart_set_AdvanceMarkers
      procedure :: UpdateSDF                => ResPart_set_UpdateSDF
      procedure :: UpdateNormals            => ResPart_set_UpdateNormals
      procedure :: GetHydroForces           => ResPart_set_GetHydroForces
      procedure :: GetSurfaceStresses       => ResPart_set_GetSurfaceStresses
      procedure :: GetIBForcing             => ResPart_set_GetIBForcing
      procedure :: GetCentroidVF            => ResPart_set_GetCentroidVF
      procedure :: CreateMonitor            => ResPart_set_CreateMonitor
      procedure :: UpdateMonitor            => ResPart_set_UpdateMonitor
      procedure :: Filter                   => ResPart_set_Filter
      procedure :: SetFilterSize            => ResPart_set_SetFilterSize
      ! Marker-Centroid matching
      procedure :: Regroup                  => ResPart_set_Regroup
      procedure :: UpdateLookup             => ResPart_set_UpdateLookup
      ! I/O subroutines
      procedure :: SetReadFileName          => ResPart_set_SetReadFileName
      procedure :: SetWriteFileName         => ResPart_set_SetWriteFileName
      procedure :: Read                     => ResPart_set_ReadH5HUT
      procedure :: ReadH5HUT                => ResPart_set_ReadH5HUT
      procedure :: ReadHDF5                 => ResPart_set_ReadHDF5
      procedure :: Write                    => ResPart_set_WriteH5HUT
      procedure :: WriteH5HUT               => ResPart_set_WriteH5HUT
      procedure :: WriteHDF5                => ResPart_set_WriteHDF5
      procedure :: WriteSilo                => ResPart_set_WriteSilo
      ! MPI subroutines
      procedure :: SetObjectType            => ResPart_set_SetObjectType
      procedure :: SetMPIDataTypeParams     => ResPart_set_SetMPIDataTypeParams
  end type ResPart_set