srtree-1.0.0.5: A general framework to work with Symbolic Regression expression trees.
Copyright(c) Fabricio Olivetti 2021 - 2021
LicenseBSD3
Maintainerfabricio.olivetti@gmail.com
Stabilityexperimental
PortabilityFlexibleInstances, DeriveFunctor, ScopedTypeVariables
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SRTree.Internal

Description

Expression tree for Symbolic Regression

Synopsis

Documentation

data SRTree val Source #

Tree structure to be used with Symbolic Regression algorithms. This structure is a fixed point of a n-ary tree.

Constructors

Var Int

index of the variables

Param Int

index of the parameter

Const Double

constant value, can be converted to a parameter

Uni Function val

univariate function

Bin Op val val

binary operator

Instances

Instances details
Functor SRTree Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

fmap :: (a -> b) -> SRTree a -> SRTree b Source #

(<$) :: a -> SRTree b -> SRTree a Source #

Floating (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal

Num (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal

Fractional (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal

Show val => Show (SRTree val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

showsPrec :: Int -> SRTree val -> ShowS Source #

show :: SRTree val -> String Source #

showList :: [SRTree val] -> ShowS Source #

Eq val => Eq (SRTree val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(==) :: SRTree val -> SRTree val -> Bool Source #

(/=) :: SRTree val -> SRTree val -> Bool Source #

Ord val => Ord (SRTree val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

compare :: SRTree val -> SRTree val -> Ordering Source #

(<) :: SRTree val -> SRTree val -> Bool Source #

(<=) :: SRTree val -> SRTree val -> Bool Source #

(>) :: SRTree val -> SRTree val -> Bool Source #

(>=) :: SRTree val -> SRTree val -> Bool Source #

max :: SRTree val -> SRTree val -> SRTree val Source #

min :: SRTree val -> SRTree val -> SRTree val Source #

data Function Source #

Supported functions

Constructors

Id 
Abs 
Sin 
Cos 
Tan 
Sinh 
Cosh 
Tanh 
ASin 
ACos 
ATan 
ASinh 
ACosh 
ATanh 
Sqrt 
Cbrt 
Square 
Log 
Exp 

data Op Source #

Supported operators

Constructors

Add 
Sub 
Mul 
Div 
Power 

Instances

Instances details
Enum Op Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

succ :: Op -> Op Source #

pred :: Op -> Op Source #

toEnum :: Int -> Op Source #

fromEnum :: Op -> Int Source #

enumFrom :: Op -> [Op] Source #

enumFromThen :: Op -> Op -> [Op] Source #

enumFromTo :: Op -> Op -> [Op] Source #

enumFromThenTo :: Op -> Op -> Op -> [Op] Source #

Read Op Source # 
Instance details

Defined in Data.SRTree.Internal

Show Op Source # 
Instance details

Defined in Data.SRTree.Internal

Eq Op Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(==) :: Op -> Op -> Bool Source #

(/=) :: Op -> Op -> Bool Source #

Ord Op Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

compare :: Op -> Op -> Ordering Source #

(<) :: Op -> Op -> Bool Source #

(<=) :: Op -> Op -> Bool Source #

(>) :: Op -> Op -> Bool Source #

(>=) :: Op -> Op -> Bool Source #

max :: Op -> Op -> Op Source #

min :: Op -> Op -> Op Source #

param :: Int -> Fix SRTree Source #

create a tree with a single node representing a parameter

var :: Int -> Fix SRTree Source #

create a tree with a single node representing a variable

arity :: Fix SRTree -> Int Source #

Arity of the current node

getChildren :: Fix SRTree -> [Fix SRTree] Source #

Get the children of a node. Returns an empty list in case of a leaf node.

countNodes :: Fix SRTree -> Int Source #

Count the number of nodes in a tree.

countVarNodes :: Fix SRTree -> Int Source #

Count the number of Var nodes

countConsts :: Fix SRTree -> Int Source #

Count the number of const nodes

countParams :: Fix SRTree -> Int Source #

Count the number of Param nodes

countOccurrences :: Int -> Fix SRTree -> Int Source #

Count the occurrences of variable indexed as ix

deriveBy :: Bool -> Int -> Fix SRTree -> Fix SRTree Source #

Creates the symbolic partial derivative of a tree by variable dx (if p is False) or parameter dx (if p is True).

deriveByVar :: Int -> Fix SRTree -> Fix SRTree Source #

Symbolic derivative by a variable

deriveByParam :: Int -> Fix SRTree -> Fix SRTree Source #

Symbolic derivative by a parameter

derivative :: Floating a => Function -> a -> a Source #

forwardMode :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> [a] Source #

Calculates the numerical derivative of a tree using forward mode provided a vector of variable values xss, a vector of parameter values theta and a function that changes a Double value to the type of the variable values.

gradParamsFwd :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> (a, [a]) Source #

The function gradParams calculates the numerical gradient of the tree and evaluates the tree at the same time. It assumes that each parameter has a unique occurrence in the expression. This should be significantly faster than forwardMode.

gradParamsRev :: forall a. (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> (a, [a]) Source #

evalFun :: Floating a => Function -> a -> a Source #

evalOp :: Floating a => Op -> a -> a -> a Source #

inverseFunc :: Function -> Function Source #

Returns the inverse of a function. This is a partial function.

evalTree :: (Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> a Source #

Evaluates the tree given a vector of variable values, a vector of parameter values and a function that takes a Double and change to whatever type the variables have. This is useful when working with datasets of many values per variables.

relabelParams :: Fix SRTree -> Fix SRTree Source #

Relabel the parameters incrementaly starting from 0

constsToParam :: Fix SRTree -> (Fix SRTree, [Double]) Source #

Change constant values to a parameter, returning the changed tree and a list of parameter values

floatConstsToParam :: Fix SRTree -> (Fix SRTree, [Double]) Source #

Same as constsToParam but does not change constant values that can be converted to integer without loss of precision

paramsToConst :: [Double] -> Fix SRTree -> Fix SRTree Source #

Convert the parameters into constants in the tree

newtype Fix f Source #

Constructors

Fix 

Fields

Instances

Instances details
Floating (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal

Num (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal

Fractional (Fix SRTree) Source # 
Instance details

Defined in Data.SRTree.Internal