immersed_boundaries_markers Module

Implementation of immersed boundaries following the Volume-Filtering Immersed Boundary (VFIB) Method. This module defines two objects: - marker_obj: this represents an element of the immersed boundary tessellation. Notably, it contains information on the surface area, normal vector, centroid position, centroid velocity, and force applied on the centroid of the tessellation element. Note that the actual shape of the element (e.g. triangular, rectangular, or other) is not stored and not needed in the VFIB method. - marker_set: this represents a collectation of tessellation elements (i.e., marker_obj) of an immersed boundary. This object offers additional methods to compute the surface density field, normal fields, IB forcing field, and I/O. There are also methods to build pre-defined basic geometries (Sphere, Plane, Cylinder) that can be used to form more complex ones.



Uses

  • module~~immersed_boundaries_markers~~UsesGraph module~immersed_boundaries_markers immersed_boundaries_markers iso_fortran_env iso_fortran_env module~immersed_boundaries_markers->iso_fortran_env module~leapbc leapBC module~immersed_boundaries_markers->module~leapbc module~leapblock leapBlock module~immersed_boundaries_markers->module~leapblock module~leapdiffop leapDiffOp module~immersed_boundaries_markers->module~leapdiffop module~leapeulerian leapEulerian module~immersed_boundaries_markers->module~leapeulerian module~leaphypre leapHypre module~immersed_boundaries_markers->module~leaphypre module~leapio leapIO module~immersed_boundaries_markers->module~leapio module~leapkinds leapKinds module~immersed_boundaries_markers->module~leapkinds module~leaplagrangian leapLagrangian module~immersed_boundaries_markers->module~leaplagrangian module~leapmonitor leapMonitor module~immersed_boundaries_markers->module~leapmonitor module~leapparallel leapParallel module~immersed_boundaries_markers->module~leapparallel module~leapparser leapParser module~immersed_boundaries_markers->module~leapparser module~leaptimer leapTimer module~immersed_boundaries_markers->module~leaptimer module~leapbc->iso_fortran_env module~leapbc->module~leapblock module~leapbc->module~leapeulerian module~leapbc->module~leapio module~leapbc->module~leapkinds module~leapbc->module~leapparallel module~leaputils leapUtils module~leapbc->module~leaputils mpi_f08 mpi_f08 module~leapbc->mpi_f08 module~leapblock->iso_fortran_env module~leapblock->module~leapkinds module~leapblock->module~leapparallel module~leapio_hdf5 leapIO_hdf5 module~leapblock->module~leapio_hdf5 module~leapblock->mpi_f08 module~leapdiffop->module~leapbc module~leapdiffop->module~leapblock module~leapdiffop->module~leapeulerian module~leapdiffop->module~leapkinds module~leapdiffop->module~leapparallel module~leapeulerian->iso_fortran_env module~leapeulerian->module~leapblock module~leapeulerian->module~leapio module~leapeulerian->module~leapkinds module~leapeulerian->module~leapparallel module~leapeulerian->module~leaputils module~leapeulerian->mpi_f08 module~leaphypre->module~leapblock module~leaphypre->module~leapeulerian module~leaphypre->module~leapkinds module~leaphypre->module~leapparallel iso_c_binding iso_c_binding module~leaphypre->iso_c_binding module~leaphypre->mpi_f08 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~leaplagrangian->module~leapblock module~leaplagrangian->module~leapio module~leaplagrangian->module~leapkinds module~leaplagrangian->module~leapparallel module~leapfilters leapfilters module~leaplagrangian->module~leapfilters module~leaplagrangian->module~leaputils module~leaplagrangian->mpi_f08 module~leapmonitor->iso_fortran_env module~leapmonitor->module~leapkinds module~leapmonitor->module~leapparallel module~leapmonitor->module~leaputils module~leapparallel->iso_fortran_env module~leapparallel->module~leapkinds module~leapparallel->mpi_f08 module~leapparser->iso_fortran_env module~leapparser->module~leapkinds module~leapcli leapCli module~leapparser->module~leapcli module~leaptimer->module~leapkinds module~leaptimer->module~leapparallel module~leaptimer->module~leapparser module~leaptimer->module~leaputils module~leapcli->module~leapkinds module~leapfilters->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 module~leaputils->module~leapkinds

Used by

  • module~~immersed_boundaries_markers~~UsedByGraph module~immersed_boundaries_markers immersed_boundaries_markers module~immersed_boundaries immersed_boundaries module~immersed_boundaries->module~immersed_boundaries_markers module~immersed_boundaries_solids immersed_boundaries_solids module~immersed_boundaries->module~immersed_boundaries_solids module~immersed_boundaries_solids->module~immersed_boundaries_markers module~cdifs cdifs module~cdifs->module~immersed_boundaries module~collisions collisions module~cdifs->module~collisions module~particles_resolved particles_resolved module~cdifs->module~particles_resolved module~collisions->module~immersed_boundaries module~particles_point particles_point module~collisions->module~particles_point module~collisions->module~particles_resolved module~grans grans module~grans->module~immersed_boundaries module~grans->module~collisions module~grans->module~particles_point module~grans->module~particles_resolved module~particles_point->module~immersed_boundaries module~particles_resolved->module~immersed_boundaries 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
integer, private, parameter :: READ_CHUNK_SIZE = 100000

Default chunk size for reading


Derived Types

type, public, extends(lagrangian_obj) ::  marker_obj

An extended Lagrangian object that represents an element from the IB tesselation.

Components

Type Visibility Attributes Name Initial
real(kind=wp), public :: SA

Sufrace area

integer, public :: c(3)

nearest cell

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

marker forcing

integer(kind=leapI8), public :: id

Identifying number (inactive if <0)

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

normal at the marker

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

position

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

Old position

integer, public :: s

A tag

integer, public :: t

Another tag

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

marker velocity

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

Old velocity

Type-Bound Procedures

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

type, public, extends(lagrangian_set) ::  marker_set

A collection of elements that form the tesseleation of an IB surface.

Components

Type Visibility Attributes Name Initial
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

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

integer, private :: R_chunk_size

Read chunk size

Type-Bound Procedures

procedure, public :: AddCylinder => marker_set_AddCylinder
procedure, public :: AddPlane => marker_set_AddPlane
procedure, public :: AddSphere => marker_set_AddSphere
procedure, public :: ApplyPeriodicity => lagrangian_set_ApplyPeriodicity
procedure, public :: CoM => marker_set_CoM
procedure, public :: Communicate => lagrangian_set_Communicate
procedure, public :: ComputeSolidVolFrac => marker_set_ComputeSolidVolFrac
procedure, public :: CreateMPIType => lagrangian_set_CreateMPIType
procedure, public :: Filter => marker_set_Filter
generic, public :: Finalize => lagrangian_set_Final
procedure, public :: FreeMPIType => lagrangian_set_FreeMPIType
procedure, public :: GetIBForcing => marker_set_GetIBForcing
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 :: LoadSTL => marker_set_LoadSTL
procedure, public :: Localize => lagrangian_set_Localize
procedure, public :: Prepare => marker_set_Prepare
procedure, public :: Read => marker_set_ReadH5HUT
procedure, public :: ReadH5HUT => marker_set_ReadH5HUT
procedure, public :: ReadHDF5 => marker_set_ReadHDF5
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, public :: SetMPIDataTypeParams => marker_set_SetMPIDataTypeParams
procedure, public :: SetObjectType => marker_set_SetObjectType
procedure, public :: SetOverwrite => lagrangian_set_SetOverwrite
procedure, public :: SetReadChunkSize => marker_set_SetReadChunkSize
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, public :: UpdateNormals => marker_set_UpdateNormals
procedure, public :: UpdateSDF => marker_set_UpdateSDF
procedure, public :: Write => marker_set_WriteH5HUT
procedure, public :: WriteH5HUT => marker_set_WriteH5HUT
procedure, public :: WriteHDF5 => marker_set_WriteHDF5
procedure, public :: lagrangian_set_Final => marker_set_Final
procedure, public :: lagrangian_set_Init => marker_set_Init

Functions

private pure function cross_product(x, y) result(z)

Returns the cross product of two vectors.

Arguments

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

Input vector

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

Input vector

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

Result

private impure function marker_set_CoM(this) result(CoM)

Finds the center of area.

Arguments

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

A collection of tessellation elements

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

Position of center of area


Subroutines

private pure subroutine marker_obj_assign(this, val)

Assignment

Arguments

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

An element from the IB tessellation

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

An element from the IB tessellation

private pure subroutine marker_set_AddCylinder(this, base, L, radius, vel, dl, tag)

Adds an IB cylinder (with open faces).

Arguments

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

A collection of tessellation elements

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

Base point for extrusion

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

Extrusion length

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

Cylinder radius

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

Cylinder translational velocity

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

Element size

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

Tag

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

Adds an IB plane.

Arguments

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

A collection of tessellation elements

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

Element size

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

Tag

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

Adds an IB sphere.

Arguments

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

A collection of tessellation elements

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

Element size

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

Tag

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

Computes the solid volume fraction on the mesh.

Arguments

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

A collection of tessellation elements

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

private impure subroutine marker_set_Filter(this, var, field)

Computes a filtered quantity on the Eulerian grid.

Arguments

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

A collection of tessellation elements

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

Variable to compute

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

Filtered quantity

private impure subroutine marker_set_Final(this)

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

Arguments

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

A collection of tessellation elements

private impure subroutine marker_set_GetIBForcing(this, Um, Vm, Wm, rhof, SDF, ibF, dt)

Computes the IB forcing Interpolation are carried out by trilinear interpolations.

Arguments

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

A collection of tessellation elements

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

Surface density function

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

IB forcing

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

Timestep

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

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

Arguments

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

A collection of tessellation elements

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

Name of this IB surface

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

A block object

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

Parallel structure to link with

private impure subroutine marker_set_LoadSTL(this, STL_file)

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

Arguments

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

A collection of tessellation elements

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

Variable to compute

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

Prepares marker_set for use with solvers.

Arguments

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

A collection of tessellation elements

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

private impure subroutine marker_set_ReadH5HUT(this, iter, time, step)

Reads marker data from file in parallel using H5HUT.

Arguments

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

A collection of tessellation elements

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

private impure subroutine marker_set_ReadHDF5(this, iter, time)

Reads marker data from file in parallel using HDF5.

Arguments

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

A collection of tessellation elements

integer, intent(out) :: iter

Iteration at write

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

Time at write

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

Sets up parameters for creating the MPI derived type. Create the MPI structure

Arguments

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

A collection of tessellation elements

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

private pure subroutine marker_set_SetObjectType(this)

Sets the sample type used in allocation of polymorphic variables.

Arguments

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

A collection of tessellation elements

private pure subroutine marker_set_SetReadChunkSize(this, chunk_size)

Sets the chunk size.

Arguments

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

A collection of tessellation elements

integer, intent(in) :: chunk_size

Chunk size

private impure subroutine marker_set_UpdateNormals(this, ibN)

Updates the Normals field.

Arguments

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

A collection of tessellation elements

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

Normals field

private impure subroutine marker_set_UpdateSDF(this, SDF)

Updates the Surface Density Function.

Arguments

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

A collection of tessellation elements

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

Surface Density Function

private impure subroutine marker_set_WriteH5HUT(this, iter, time)

Writes marker data to file in parallel using H5HUT.

Arguments

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

A collection of tessellation elements

integer, intent(in) :: iter

Iteration at write

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

Time at write

private impure subroutine marker_set_WriteHDF5(this, iter, time)

Write marker data to file in parallel using HDF5.

Arguments

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

A collection of tessellation elements

integer, intent(in) :: iter

Iteration at write

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

Time at write