srtree-0.1.2.0: 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, ConstraintKinds
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SRTree

Description

Expression tree for Symbolic Regression

Synopsis

Documentation

data SRTree ix val Source #

Tree structure to be used with Symbolic Regression algorithms. This structure is parametrized by the indexing type to retrieve the values of a variable and the type of the output value.

Constructors

Empty 
Var ix 
Const val 
Param ix 
Fun Function (SRTree ix val) 
Pow (SRTree ix val) Int 
(SRTree ix val) `Add` (SRTree ix val) 
(SRTree ix val) `Sub` (SRTree ix val) 
(SRTree ix val) `Mul` (SRTree ix val) 
(SRTree ix val) `Div` (SRTree ix val) 
(SRTree ix val) `Power` (SRTree ix val) 
(SRTree ix val) `LogBase` (SRTree ix val) 

Instances

Instances details
Bifunctor SRTree Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

bimap :: (a -> b) -> (c -> d) -> SRTree a c -> SRTree b d #

first :: (a -> b) -> SRTree a c -> SRTree b c #

second :: (b -> c) -> SRTree a b -> SRTree a c #

Foldable (SRTree ix) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

fold :: Monoid m => SRTree ix m -> m #

foldMap :: Monoid m => (a -> m) -> SRTree ix a -> m #

foldMap' :: Monoid m => (a -> m) -> SRTree ix a -> m #

foldr :: (a -> b -> b) -> b -> SRTree ix a -> b #

foldr' :: (a -> b -> b) -> b -> SRTree ix a -> b #

foldl :: (b -> a -> b) -> b -> SRTree ix a -> b #

foldl' :: (b -> a -> b) -> b -> SRTree ix a -> b #

foldr1 :: (a -> a -> a) -> SRTree ix a -> a #

foldl1 :: (a -> a -> a) -> SRTree ix a -> a #

toList :: SRTree ix a -> [a] #

null :: SRTree ix a -> Bool #

length :: SRTree ix a -> Int #

elem :: Eq a => a -> SRTree ix a -> Bool #

maximum :: Ord a => SRTree ix a -> a #

minimum :: Ord a => SRTree ix a -> a #

sum :: Num a => SRTree ix a -> a #

product :: Num a => SRTree ix a -> a #

Traversable (SRTree ix) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

traverse :: Applicative f => (a -> f b) -> SRTree ix a -> f (SRTree ix b) #

sequenceA :: Applicative f => SRTree ix (f a) -> f (SRTree ix a) #

mapM :: Monad m => (a -> m b) -> SRTree ix a -> m (SRTree ix b) #

sequence :: Monad m => SRTree ix (m a) -> m (SRTree ix a) #

Applicative (SRTree ix) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

pure :: a -> SRTree ix a #

(<*>) :: SRTree ix (a -> b) -> SRTree ix a -> SRTree ix b #

liftA2 :: (a -> b -> c) -> SRTree ix a -> SRTree ix b -> SRTree ix c #

(*>) :: SRTree ix a -> SRTree ix b -> SRTree ix b #

(<*) :: SRTree ix a -> SRTree ix b -> SRTree ix a #

Functor (SRTree ix) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

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

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

(Eq ix, Eq val, Floating val) => Floating (SRTree ix val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

pi :: SRTree ix val #

exp :: SRTree ix val -> SRTree ix val #

log :: SRTree ix val -> SRTree ix val #

sqrt :: SRTree ix val -> SRTree ix val #

(**) :: SRTree ix val -> SRTree ix val -> SRTree ix val #

logBase :: SRTree ix val -> SRTree ix val -> SRTree ix val #

sin :: SRTree ix val -> SRTree ix val #

cos :: SRTree ix val -> SRTree ix val #

tan :: SRTree ix val -> SRTree ix val #

asin :: SRTree ix val -> SRTree ix val #

acos :: SRTree ix val -> SRTree ix val #

atan :: SRTree ix val -> SRTree ix val #

sinh :: SRTree ix val -> SRTree ix val #

cosh :: SRTree ix val -> SRTree ix val #

tanh :: SRTree ix val -> SRTree ix val #

asinh :: SRTree ix val -> SRTree ix val #

acosh :: SRTree ix val -> SRTree ix val #

atanh :: SRTree ix val -> SRTree ix val #

log1p :: SRTree ix val -> SRTree ix val #

expm1 :: SRTree ix val -> SRTree ix val #

log1pexp :: SRTree ix val -> SRTree ix val #

log1mexp :: SRTree ix val -> SRTree ix val #

(Eq ix, Eq val, Num val) => Num (SRTree ix val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(+) :: SRTree ix val -> SRTree ix val -> SRTree ix val #

(-) :: SRTree ix val -> SRTree ix val -> SRTree ix val #

(*) :: SRTree ix val -> SRTree ix val -> SRTree ix val #

negate :: SRTree ix val -> SRTree ix val #

abs :: SRTree ix val -> SRTree ix val #

signum :: SRTree ix val -> SRTree ix val #

fromInteger :: Integer -> SRTree ix val #

(Eq ix, Eq val, Fractional val) => Fractional (SRTree ix val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(/) :: SRTree ix val -> SRTree ix val -> SRTree ix val #

recip :: SRTree ix val -> SRTree ix val #

fromRational :: Rational -> SRTree ix val #

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

Defined in Data.SRTree.Internal

Methods

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

show :: SRTree ix val -> String #

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

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

Defined in Data.SRTree.Internal

Methods

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

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

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

Defined in Data.SRTree.Internal

Methods

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

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

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

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

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

max :: SRTree ix val -> SRTree ix val -> SRTree ix val #

min :: SRTree ix val -> SRTree ix val -> SRTree ix val #

(Eq ix, Eq val, Num val, OptIntPow val) => OptIntPow (SRTree ix val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(^.) :: SRTree ix val -> Int -> SRTree ix val Source #

data Function Source #

Functions that can be applied to a subtree.

Constructors

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

class OptIntPow a where Source #

A class for optimized (^^) operators for specific types. This was created because the integer power operator for interval arithmetic must be aware of the dependency problem, thus the default (^) doesn't work.

Methods

(^.) :: a -> Int -> a infix 8 Source #

Instances

Instances details
OptIntPow Double Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(^.) :: Double -> Int -> Double Source #

OptIntPow Float Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(^.) :: Float -> Int -> Float Source #

(Eq ix, Eq val, Num val, OptIntPow val) => OptIntPow (SRTree ix val) Source # 
Instance details

Defined in Data.SRTree.Internal

Methods

(^.) :: SRTree ix val -> Int -> SRTree ix val Source #

traverseIx :: Applicative f => (ixa -> f ixb) -> SRTree ixa val -> f (SRTree ixb val) Source #

Same as traverse but for the first type parameter.

arity :: SRTree ix val -> Int Source #

Arity of the current node

getChildren :: SRTree ix val -> [SRTree ix val] Source #

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

countNodes :: SRTree ix val -> Int Source #

Count the number of nodes in a tree.

countVarNodes :: SRTree ix val -> Int Source #

Count the number of Var nodes

countOccurrences :: Eq ix => SRTree ix val -> ix -> Int Source #

Count the occurrences of variable indexed as ix

deriveBy :: (Eq ix, Eq val, Floating val, OptIntPow val) => ix -> SRTree ix val -> SRTree ix val Source #

Creates an SRTree representing the partial derivative of the input by the variable indexed by ix.

deriveParamBy :: (Eq ix, Eq val, Floating val, OptIntPow val) => ix -> SRTree ix val -> SRTree ix val Source #

Creates an SRTree representing the partial derivative of the input by the parameter indexed by ix.

simplify :: (Eq ix, Eq val, Floating val, OptIntPow val) => SRTree ix val -> SRTree ix val Source #

Simplifies the SRTree.

derivative :: (Eq ix, Eq val, Floating val) => Function -> SRTree ix val -> SRTree ix val Source #

Derivative of a Function

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

Evaluates a function.

inverseFunc :: Function -> Function Source #

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

evalTree :: (Floating val, OptIntPow val) => SRTree ix val -> Reader (ix -> Maybe val) (Maybe val) Source #

Evaluates a tree with the variables stored in a Reader monad.

evalTreeMap :: (Floating v1, OptIntPow v1, Floating v2, OptIntPow v2) => (v1 -> v2) -> SRTree ix v1 -> Reader (ix -> Maybe v2) (Maybe v2) Source #

Evaluates a tree with the variables stored in a Reader monad while mapping the constant values to a different type.

evalTreeWithMap :: (Ord ix, Floating val, OptIntPow val) => SRTree ix val -> Map ix val -> Maybe val Source #

Example of using evalTree with a Map.

evalTreeWithVector :: (Floating val, OptIntPow val) => SRTree Int val -> Vector val -> Maybe val Source #

Example of using evalTree with a Vector.

relabelOccurrences :: forall ix val. Ord ix => SRTree ix val -> SRTree (ix, Int) val Source #

Relabel occurences of a var into a tuple (ix, Int).

relabelParams :: Num ix => SRTree ix val -> SRTree ix val Source #

Relabel the parameters sequentially starting from 0