lagrangian_set Derived Type

type, public, abstract :: lagrangian_set

Base structure for a collection of Lagrangian objects.


Inherits

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

Inherited by

type~~lagrangian_set~~InheritedByGraph type~lagrangian_set lagrangian_set type~marker_set marker_set type~marker_set->type~lagrangian_set type~particle_set particle_set type~particle_set->type~lagrangian_set type~respart_set ResPart_set type~respart_set->type~lagrangian_set type~respart_set->type~marker_set ib type~cdifs_obj cdifs_obj type~cdifs_obj->type~marker_set IB type~cdifs_obj->type~respart_set RP type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~collision_obj->type~marker_set IB type~collision_obj->type~particle_set PP type~collision_obj->type~respart_set RP type~grans_obj grans_obj type~grans_obj->type~marker_set IB type~grans_obj->type~particle_set PP type~grans_obj->type~respart_set RP type~grans_obj->type~collision_obj collisions 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 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

logical, public :: is_initialized = .false.

Flag to determine whether this has been initialized

real(kind=wp), public :: l_filter

Half filter width

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

Name of the Lagrangian set

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

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

character(len=str64), public :: write_file

File to write

integer, private :: MPI_SIZE = 44

MPI size

type(MPI_Datatype), private :: MPI_TYPE

MPI variable type


Type-Bound Procedures

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

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 :: 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 :: 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(lagrangian_read), public, deferred :: Read

  • impure subroutine lagrangian_read(this, iter, time, step) Prototype

    (Deferred) Reads lagrangian objects from file in parallel.

    Arguments

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

    A set of Lagrangian objects

    integer, intent(out) :: iter

    Iteration at write

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

    Time at write

    integer, intent(in), optional :: step

    Optional step

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 :: 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 => lagrangian_set_SetFilterSize

  • private impure subroutine lagrangian_set_SetFilterSize(this, l_filter)

    Adjusts the filter half size. Note that the block needs to contain enough ghost cells to be able to represent a filter kernel centered on the edge of the domain. Otherwise, an error will be returnned. The larger the filter size, the more ghost cells are required.

    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(lagrangian_SetMPIDataTypeParams), public, deferred :: SetMPIDataTypeParams

  • impure subroutine lagrangian_SetMPIDataTypeParams(this, types, lengths, displacement) Prototype

    (Deferred) Sets up parameters used to create the MPI derived type.

    Arguments

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

    Set of Lagrangian objects

    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(lagrangian_SetObjectType), public, deferred :: SetObjectType

  • pure subroutine lagrangian_SetObjectType(this) Prototype

    (Deferred) Sets the type of the polymorphic sample.

    Arguments

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

    A set of Lagrangian objects

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

  • private pure subroutine lagrangian_set_SetReadFileName(this, name)

    Sets the base name of file to read.

    Arguments

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

    A set of Lagrangian objects

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

    Name of file

procedure, public :: SetWriteFileName => lagrangian_set_SetWriteFileName

  • private pure subroutine lagrangian_set_SetWriteFileName(this, name)

    Sets the base name of file to write.

    Arguments

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

    A set of Lagrangian objects

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

    Name of file

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(lagrangian_write), public, deferred :: Write

  • impure subroutine lagrangian_write(this, iter, time) Prototype

    (Deferred) Writes Lagrangian objects to file in parallel.

    Arguments

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

    A set of Lagrangian objects

    integer, intent(in) :: iter

    Iteration at write

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

    Time at write

procedure, public :: lagrangian_set_Final

  • private impure subroutine lagrangian_set_Final(this)

    Finalizes the structure and frees memory.

    Arguments

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

    A set of Lagrangian objects

procedure, public :: lagrangian_set_Init

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

    Initialize lagrangian objects related IO.

    Arguments

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

    A set of Lagrangian objects

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

    Variable name

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

    A block object

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

    Parallel structure to link with

procedure, private :: GetOwnerRankByBlock => lagrangian_set_GetOwnerRankByBlock

  • private impure 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(in) :: this

    A set of Lagrangian objects

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

    Lagrangian obj to locate

    Return Value integer

    rank that should own lagobj

Source Code

  type,abstract :: lagrangian_set
    !> Base structure for a collection of Lagrangian objects.
    character(len=:),      allocatable :: name                                 !! Name of the Lagrangian set
    class(lagrangian_obj), allocatable :: p(:)                                 !! Array of Lagrangian_obj or any extended type
    type(block_obj),       pointer     :: block         => null()              !! Associated block structure
    type(parallel_obj),    pointer     :: parallel      => null()              !! Associated parallel structure
    integer                            :: count_         = 0                   !! Local count for this rank
    integer                            :: count          = 0                   !! Total count across all MPI ranks
    character(len=str64)               :: read_file                            !! File to read
    character(len=str64)               :: write_file                           !! File to write
    logical                            :: overwrite      = .true.              !! Switch to overwrite IO files
    real(wp)                           :: l_filter                             !! Half filter width
    integer                            :: stib           = 3                   !! Stencil size for filtering
    procedure(kernel_1D),  pointer,     &
                                nopass :: g1in          => g1_triangle         !! 1D kernel used in interpolations
    procedure(kernel_1D),  pointer,     &
                                nopass :: g1ex          => int_g1_triangle     !! 1D kernel used in extrapolations
    class(lagrangian_obj), allocatable :: sample                               !! Sample used in allocation of polymorphic data
    integer,               allocatable :: count_proc(:)                        !! Nbr of lagrangian objects per proc
    type(MPI_Datatype),    private     :: MPI_TYPE                             !! MPI variable type
    integer,               private     :: MPI_SIZE        = 44                 !! MPI size
    logical                            :: is_initialized  = .false.            !! Flag to determine whether this has been initialized
    contains
      generic   :: Initialize          => lagrangian_set_Init
      generic   :: Finalize            => lagrangian_set_Final
      ! Procedures related to Lagrangian object
      procedure :: Resize              => lagrangian_set_Resize
      procedure :: Recycle             => lagrangian_set_Recycle
      procedure :: UpdateCount         => lagrangian_set_UpdateCount
      procedure :: Localize            => lagrangian_set_Localize
      procedure :: ApplyPeriodicity    => lagrangian_set_ApplyPeriodicity
      ! Procedures related to filtering
      procedure :: SetFilterKernel     => lagrangian_set_SetFilterKernel
      procedure :: SetFilterSize       => lagrangian_set_SetFilterSize
      ! Procedures related to I/O
      procedure :: SetWriteFileName    => lagrangian_set_SetWriteFileName
      procedure :: GetWriteFileName    => lagrangian_set_GetWriteFileName
      procedure :: SetReadFileName     => lagrangian_set_SetReadFileName
      procedure :: GetReadFileName     => lagrangian_set_GetReadFileName
      procedure :: SetOverwrite        => lagrangian_set_SetOverwrite
      procedure :: GetOverwrite        => lagrangian_set_GetOverwrite
      ! Procedures related to MPI communications
      procedure :: Communicate         => lagrangian_set_Communicate
      procedure :: UpdateGhostObjects  => lagrangian_set_UpdateGhostObjects
      procedure, &
       private  :: GetOwnerRankByBlock => lagrangian_set_GetOwnerRankByBlock
      procedure :: CreateMPIType       => lagrangian_set_CreateMPIType
      procedure :: FreeMPIType         => lagrangian_set_FreeMPIType
      ! Other
      procedure :: Info                => lagrangian_set_Info
      procedure :: lagrangian_set_Init
      procedure :: lagrangian_set_Final
      ! Deffered procedures
      procedure(lagrangian_SetObjectType),       deferred :: SetObjectType
      procedure(lagrangian_read),                deferred :: Read
      procedure(lagrangian_write),               deferred :: Write
      procedure(lagrangian_SetMPIDataTypeParams),deferred :: SetMPIDataTypeParams
  end type lagrangian_set