leapLagrangian Module

Module of abstract objets defining Lagrangian data structure. A lagrangian object: - is defined at mininum by an id, 3D position, and coordinates of cell in underlying grid where it's located. - objects with id>0 are considered as active objects. - objects with id=0 are considered inactive, and scheduled for removal. - ogjects with id<0 represent ghostobjects.

A lagrangian set: - represents a cloud of lagrangian objects. - manages addition and removal of lagrangian objects. - offers method for operations related to the underlying grid, such as periodicity adjustment, localization on grid, filtering. - offers methods to help with parallel (MPI) operations. - offers method for IO.

The objects defined in this subroutine are Abstract, meaning they cannot be directly instantiated. Users need to define an extension of these objects. Some procedures are deferred, meaning that users are forced to implement their version of these procedures when they do their extension.



Uses

  • module~~leaplagrangian~~UsesGraph module~leaplagrangian leapLagrangian module~leapblock leapBlock module~leaplagrangian->module~leapblock module~leapfilters leapfilters module~leaplagrangian->module~leapfilters module~leapio leapIO module~leaplagrangian->module~leapio module~leapkinds leapKinds module~leaplagrangian->module~leapkinds module~leapparallel leapParallel module~leaplagrangian->module~leapparallel module~leaputils leapUtils module~leaplagrangian->module~leaputils mpi_f08 mpi_f08 module~leaplagrangian->mpi_f08 module~leapblock->module~leapkinds module~leapblock->module~leapparallel module~leapblock->mpi_f08 iso_fortran_env iso_fortran_env module~leapblock->iso_fortran_env module~leapio_hdf5 leapIO_hdf5 module~leapblock->module~leapio_hdf5 module~leapfilters->module~leapkinds module~leapio_h5hut leapIO_h5hut module~leapio->module~leapio_h5hut module~leapio->module~leapio_hdf5 module~leapio_silo leapIO_silo module~leapio->module~leapio_silo module~leapio_xdmf leapIO_xdmf module~leapio->module~leapio_xdmf module~leapkinds->iso_fortran_env module~leapparallel->module~leapkinds module~leapparallel->mpi_f08 module~leapparallel->iso_fortran_env module~leaputils->module~leapkinds module~leapio_h5hut->module~leapkinds module~leapio_h5hut->module~leapparallel module~leapio_h5hut->module~leapio_hdf5 module~leapio_hdf5->module~leapkinds module~leapio_hdf5->module~leapparallel module~leapio_hdf5->module~leaputils hdf5 hdf5 module~leapio_hdf5->hdf5 module~leapio_silo->module~leapkinds module~leapio_silo->module~leapparallel module~leapio_silo->module~leaputils module~leapio_silo->mpi_f08 module~leapio_xdmf->module~leapkinds module~leapio_xdmf->module~leaputils

Used by

  • module~~leaplagrangian~~UsedByGraph module~leaplagrangian leapLagrangian module~immersed_boundaries_markers immersed_boundaries_markers module~immersed_boundaries_markers->module~leaplagrangian module~immersed_boundaries_solids immersed_boundaries_solids module~immersed_boundaries_solids->module~leaplagrangian module~immersed_boundaries_solids->module~immersed_boundaries_markers module~particles_point particles_point module~particles_point->module~leaplagrangian module~immersed_boundaries immersed_boundaries module~particles_point->module~immersed_boundaries module~particles_resolved particles_resolved module~particles_resolved->module~leaplagrangian module~particles_resolved->module~immersed_boundaries module~cdifs cdifs module~cdifs->module~particles_resolved module~collisions collisions module~cdifs->module~collisions module~cdifs->module~immersed_boundaries module~collisions->module~particles_point module~collisions->module~particles_resolved module~collisions->module~immersed_boundaries module~grans grans module~grans->module~particles_point module~grans->module~particles_resolved module~grans->module~collisions module~grans->module~immersed_boundaries module~immersed_boundaries->module~immersed_boundaries_markers module~immersed_boundaries->module~immersed_boundaries_solids module~cdifs_advancesolution_smod cdifs_AdvanceSolution_smod module~cdifs_advancesolution_smod->module~cdifs module~cdifs_monitor_smod cdifs_Monitor_smod module~cdifs_monitor_smod->module~cdifs module~cdifs_preparesolver_smod cdifs_PrepareSolver_smod module~cdifs_preparesolver_smod->module~cdifs module~cdifs_writeoutputdata_smod cdifs_WriteOutputData_smod module~cdifs_writeoutputdata_smod->module~cdifs module~cdifs_writerestartdata_smod cdifs_WriteRestartData_smod module~cdifs_writerestartdata_smod->module~cdifs module~grans_advancesolution_smod grans_AdvanceSolution_smod module~grans_advancesolution_smod->module~grans module~grans_module_smod grans_module_smod module~grans_module_smod->module~grans module~grans_preparesolver_smod grans_PrepareSolver_smod module~grans_preparesolver_smod->module~grans module~grans_writeoutputdata_smod grans_WriteOutputData_smod module~grans_writeoutputdata_smod->module~grans module~grans_writerestartdata_smod grans_WriteRestartData_smod module~grans_writerestartdata_smod->module~grans program~main main program~main->module~cdifs program~main->module~grans

Variables

Type Visibility Attributes Name Initial
real(kind=wp), private, parameter :: RESIZE_INCREMENT = 0.3_wp

Increment for resizing lagrangian arrays: 30% up or 30% smaller


Abstract Interfaces

abstract interface

  • private function kernel_1D(r) result(val)

    Arguments

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

    Distance from center

    Return Value real(kind=wp)

    Kernel value

abstract interface

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

    (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

abstract interface

  • private pure subroutine lagrangian_SetObjectType(this)

    (Deferred) Sets the type of the polymorphic sample.

    Arguments

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

    A set of Lagrangian objects

abstract interface

  • private pure subroutine lagrangian_obj_assign(this, val)

    (Deferred) Performs assignemnt of an extended type.

    Arguments

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

    A Lagrangian object

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

    Value to be assigned

abstract interface

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

    (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

abstract interface

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

    (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

abstract interface

  • private impure function locator(this, lagobj) result(rank)

    (Deferred) Returns the MPI rank that owns the lagrangian object.

    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


Derived Types

type, public, abstract ::  lagrangian_obj

Base lagrangian object. The object's ID indicates the status: active (id>0), inactive (id=0), ghostobject (id<0).

Components

Type Visibility Attributes Name Initial
integer, public :: c(3)

nearest cell

integer(kind=leapI8), public :: id

Identifying number (inactive if <0)

real(kind=wp), public :: p(3)

position

Type-Bound Procedures

procedure, public :: Extrapolate => lagrangian_obj_Extrapolate
procedure, public :: Interpolate => lagrangian_obj_Interpolate
procedure, public :: Locate => lagrangian_obj_Locate
procedure(lagrangian_obj_assign), public, deferred :: assign
generic, public :: assignment(=) => assign

type, public, abstract ::  lagrangian_set

Base structure for a collection of Lagrangian objects.

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
procedure, public :: CreateMPIType => lagrangian_set_CreateMPIType
generic, public :: Finalize => lagrangian_set_Final
procedure, public :: FreeMPIType => lagrangian_set_FreeMPIType
procedure, public :: GetOverwrite => lagrangian_set_GetOverwrite
procedure, public :: GetReadFileName => lagrangian_set_GetReadFileName
procedure, public :: GetWriteFileName => lagrangian_set_GetWriteFileName
procedure, public :: Info => lagrangian_set_Info
generic, public :: Initialize => lagrangian_set_Init
procedure, public :: Localize => lagrangian_set_Localize
procedure(lagrangian_read), public, deferred :: Read
procedure, public :: Recycle => lagrangian_set_Recycle
procedure, public :: Resize => lagrangian_set_Resize
procedure, public :: SetFilterKernel => lagrangian_set_SetFilterKernel
procedure, public :: SetFilterSize => lagrangian_set_SetFilterSize
procedure(lagrangian_SetMPIDataTypeParams), public, deferred :: SetMPIDataTypeParams
procedure(lagrangian_SetObjectType), public, deferred :: SetObjectType
procedure, public :: SetOverwrite => lagrangian_set_SetOverwrite
procedure, public :: SetReadFileName => lagrangian_set_SetReadFileName
procedure, public :: SetWriteFileName => lagrangian_set_SetWriteFileName
procedure, public :: UpdateCount => lagrangian_set_UpdateCount
procedure, public :: UpdateGhostObjects => lagrangian_set_UpdateGhostObjects
procedure(lagrangian_write), public, deferred :: Write
procedure, public :: lagrangian_set_Final
procedure, public :: lagrangian_set_Init
procedure, private :: GetOwnerRankByBlock => lagrangian_set_GetOwnerRankByBlock

Functions

private function lagrangian_obj_Interpolate(this, l_filter, slo, shi, block, g1in, f) result(inter)

Interpolates a field f defined on an Eulerian stencil to the location of a lagrangian object

Arguments

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

A Lagrangian object

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

Filter size

integer, intent(in) :: slo(3)

Stencil lower bound

integer, intent(in) :: shi(3)

Stencil higher bound

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

A block object

procedure(kernel_1D), intent(in), pointer :: g1in

Filter kernel

real(kind=wp), intent(in) :: f(slo(1):shi(1),slo(2):shi(2),slo(3):shi(3))

Quantity to interpolate

Return Value real(kind=wp)

private pure function lagrangian_obj_Locate(this, block) result(cell)

Locates a Lagrangian object on an external grid. Returns the location of the cell containing the object.

Arguments

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

A Lagrangian object

class(block_obj), intent(in) :: block

External block

Return Value integer, (3)

Result

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

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

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

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


Subroutines

private subroutine lagrangian_obj_Extrapolate(this, l_filter, slo, shi, block, int_g1ex, bump)

Gets a bump function centered on the lagrangian object.

Arguments

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

A Lagrangian object

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

Filter size

integer, intent(in) :: slo(3)

Stencil lower bound

integer, intent(in) :: shi(3)

Stencil higher bound

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

A block object

procedure(kernel_1D), intent(in), pointer :: int_g1ex

Integrated filter kernel

real(kind=wp), intent(out), allocatable :: bump(:,:,:)

The bump function

private pure subroutine lagrangian_set_ApplyPeriodicity(this)

Applies periodic boundary conditions.

Arguments

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

A set of Lagrangian objects

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

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

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

private impure subroutine lagrangian_set_FreeMPIType(this)

Frees the MPI data type.

Arguments

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

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

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

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

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

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

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

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

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

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

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

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

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

private impure subroutine lagrangian_set_UpdateGhostObjectsDir(this, dist, idir)

Updates ghost objects in the idir direction. Copies objects that lie "dist"-away from the block's boundaries in idir-direction to neighboring MPI-ranks. Copied objects get a negative ID to designate them as ghost objects

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

integer, intent(in) :: idir

Direction of communication