marker_obj Derived Type

type, public, extends(lagrangian_obj) :: marker_obj

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


Inherits

type~~marker_obj~~InheritsGraph type~marker_obj marker_obj type~lagrangian_obj lagrangian_obj type~marker_obj->type~lagrangian_obj

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

  • 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

procedure, public :: Interpolate => lagrangian_obj_Interpolate

  • 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)

procedure, public :: Locate => lagrangian_obj_Locate

  • 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

procedure, public :: assign => marker_obj_assign

  • 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

generic, public :: assignment(=) => assign

Source Code

  type, extends (lagrangian_obj) :: marker_obj
    !> An extended Lagrangian object that represents an element from the IB
    ! tesselation.
    integer  :: s                                                              !! A tag
    integer  :: t                                                              !! Another tag
    real(wp) :: SA                                                             !! Sufrace area
    real(wp) :: n(3)                                                           !! normal at the marker
    real(wp) :: v(3)                                                           !! marker velocity
    real(wp) :: f(3)                                                           !! marker forcing
    real(wp) :: pold(3)                                                        !! Old position
    real(wp) :: vold(3)                                                        !! Old velocity
    contains
      procedure :: assign              => marker_obj_assign
  end type marker_obj