calculation_tree_class Module

Houses the calculation tree class and the relevant node class.


Used by


Interfaces

interface

  • public pure recursive module function evaluateNode(this, inputArray) result(res)

    Recursively evaluate nodes, using the inputArray variables for leaf values

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationNode), intent(in) :: this
    type(RealArray), intent(in), dimension(:) :: inputArray

    Return Value real(kind=rk), allocatable, dimension(:)

interface

  • public pure module function evaluateTree(this, inputArray) result(res)

    Call tree's root node evaluate

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationTree), intent(in) :: this
    type(RealArray), intent(in), dimension(:) :: inputArray

    Return Value real(kind=rk), allocatable, dimension(:)

interface

  • public module function flattenTree(this) result(res)

    Flatten tree into FlatTree object

    Arguments

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

    Return Value type(FlatTree)

interface

  • public module subroutine initNode(this, additiveMode, constant, leafVarIndex, unaryRealParams, unaryIntParams, unaryLogicalParams, unaryTransformTag)

    Calculation node initialization routine

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationNode), intent(inout) :: this
    logical, intent(in), optional :: additiveMode
    real(kind=rk), intent(in), optional :: constant
    integer(kind=ik), intent(in), optional :: leafVarIndex
    real(kind=rk), intent(in), optional, dimension(:) :: unaryRealParams
    integer(kind=ik), intent(in), optional, dimension(:) :: unaryIntParams
    logical, intent(in), optional, dimension(:) :: unaryLogicalParams
    character(len=*), intent(in), optional :: unaryTransformTag

interface

  • public module subroutine initTree(this, additiveMode, constant, leafVarIndex, unaryRealParams, unaryIntParams, unaryLogicalParams, unaryTransformTag)

    Calculation tree initialization routine

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationTree), intent(inout) :: this
    logical, intent(in), optional :: additiveMode
    real(kind=rk), intent(in), optional :: constant
    integer(kind=ik), intent(in), optional :: leafVarIndex
    real(kind=rk), intent(in), optional, dimension(:) :: unaryRealParams
    integer(kind=ik), intent(in), optional, dimension(:) :: unaryIntParams
    logical, intent(in), optional, dimension(:) :: unaryLogicalParams
    character(len=*), intent(in), optional :: unaryTransformTag

interface

  • public module subroutine addChild(this, additiveMode, constant, leafVarIndex, unaryRealParams, unaryIntParams, unaryLogicalParams, unaryTransformTag)

    Initialize a child node of this node with given properties

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationNode), intent(inout), target :: this
    logical, intent(in), optional :: additiveMode
    real(kind=rk), intent(in), optional :: constant
    integer(kind=ik), intent(in), optional :: leafVarIndex
    real(kind=rk), intent(in), optional, dimension(:) :: unaryRealParams
    integer(kind=ik), intent(in), optional, dimension(:) :: unaryIntParams
    logical, intent(in), optional, dimension(:) :: unaryLogicalParams
    character(len=*), intent(in), optional :: unaryTransformTag

interface

  • public module subroutine initFromFlatTree(this, fTree)

    Calculation tree initialization routine using a FlatTree object

    Arguments

    Type IntentOptional Attributes Name
    class(CalculationTree), intent(inout) :: this
    type(FlatTree), intent(in) :: fTree

interface

  • public pure recursive module subroutine destroyNode(this)

    Arguments

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

interface

  • public elemental module subroutine finalizeCalculationTree(this)

    Arguments

    Type IntentOptional Attributes Name
    type(CalculationTree), intent(inout) :: this

Derived Types

type, public ::  CalculationKernel

Kernel containing calculation node properties

Components

Type Visibility Attributes Name Initial
logical, public :: additiveMode

If true will use additive mode for reducing the results of its children. Defaults to false.

real(kind=rk), public :: constant

Constant component, defaults to 0 in additive mode and 1 in multiplicative.

integer(kind=ik), public :: leafVarIndex

Index of variable to be used a the child's result if this node is a leaf

real(kind=rk), public, allocatable, dimension(:) :: unaryRealParams

Optional real parameters of unary transformation

integer(kind=ik), public, allocatable, dimension(:) :: unaryIntParams

Optional integer parameters of unary transformation

logical, public, allocatable, dimension(:) :: unaryLogicalParams

Optional logical parameters of unary transformation

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

type, public ::  FlatTree

Flattened calculation tree for pointer-safe copying

Components

Type Visibility Attributes Name Initial
type(CalculationKernel), public, allocatable, dimension(:) :: kernels
type(IntArray), public, allocatable, dimension(:) :: children
integer(kind=ik), public, allocatable, dimension(:) :: parent

type, public, extends(Object) ::  CalculationNode

Node class for the abstract calculation left child/right sibling tree. Each node has a reference to its leftmost child, its sibling to the immediate right, and to its parent.

Read more…

Components

Type Visibility Attributes Name Initial
logical, public :: userDefined = .false.

True only if user explicitly sets it to true

type(CalculationNode), public, pointer :: leftChild => null()
type(CalculationNode), public, pointer :: rightSibling => null()
type(CalculationNode), public, pointer :: parent => null()
type(CalculationKernel), public :: kernel
procedure(realArrayFunctionGenParam), public, pointer, nopass :: unaryTransform => null()

Optional unary transformation

Type-Bound Procedures

procedure, public :: isDefined => isDefinedObject
procedure, public :: makeDefined => makeDefinedObject
procedure, public :: makeUndefined => makeUndefinedObject
procedure, public :: addChild
procedure, public :: init => initNode
procedure, public :: evaluate => evaluateNode
procedure, public :: destroy => destroyNode

type, public, extends(Object) ::  CalculationTree

Components

Type Visibility Attributes Name Initial
logical, public :: userDefined = .false.

True only if user explicitly sets it to true

type(CalculationNode), public, pointer :: root => null()

Finalizations Procedures

final :: finalizeCalculationTree

Type-Bound Procedures

procedure, public :: isDefined => isDefinedObject
procedure, public :: makeDefined => makeDefinedObject
procedure, public :: makeUndefined => makeUndefinedObject
procedure, public :: init => initTree
procedure, public :: evaluate => evaluateTree
procedure, public :: flatten => flattenTree
procedure, public :: initFromFlatTree