Copyright | (c) Fabricio Olivetti 2021 - 2021 |
---|---|
License | BSD3 |
Maintainer | fabricio.olivetti@gmail.com |
Stability | experimental |
Portability | FlexibleInstances, DeriveFunctor, ScopedTypeVariables, ConstraintKinds |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Expression tree for Symbolic Regression
Synopsis
- data SRTree ix val
- = 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)
- data Function
- class OptIntPow a where
- traverseIx :: Applicative f => (ixa -> f ixb) -> SRTree ixa val -> f (SRTree ixb val)
- arity :: SRTree ix val -> Int
- getChildren :: SRTree ix val -> [SRTree ix val]
- countNodes :: SRTree ix val -> Int
- countVarNodes :: SRTree ix val -> Int
- countOccurrences :: Eq ix => SRTree ix val -> ix -> Int
- deriveBy :: (Eq ix, Eq val, Floating val, OptIntPow val) => ix -> SRTree ix val -> SRTree ix val
- deriveParamBy :: (Eq ix, Eq val, Floating val, OptIntPow val) => ix -> SRTree ix val -> SRTree ix val
- simplify :: (Eq ix, Eq val, Floating val, OptIntPow val) => SRTree ix val -> SRTree ix val
- derivative :: (Eq ix, Eq val, Floating val) => Function -> SRTree ix val -> SRTree ix val
- evalFun :: Floating val => Function -> val -> val
- inverseFunc :: Function -> Function
- evalTree :: (Floating val, OptIntPow val) => SRTree ix val -> Reader (ix -> Maybe val) (Maybe val)
- evalTreeMap :: (Floating v1, OptIntPow v1, Floating v2, OptIntPow v2) => (v1 -> v2) -> SRTree ix v1 -> Reader (ix -> Maybe v2) (Maybe v2)
- evalTreeWithMap :: (Ord ix, Floating val, OptIntPow val) => SRTree ix val -> Map ix val -> Maybe val
- evalTreeWithVector :: (Floating val, OptIntPow val) => SRTree Int val -> Vector val -> Maybe val
- relabelOccurrences :: forall ix val. Ord ix => SRTree ix val -> SRTree (ix, Int) val
- relabelParams :: Num ix => SRTree ix val -> SRTree ix val
Documentation
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.
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
Bifunctor SRTree Source # | |
Foldable (SRTree ix) Source # | |
Defined in Data.SRTree.Internal 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] # 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 # | |
Traversable (SRTree ix) Source # | |
Applicative (SRTree ix) Source # | |
Functor (SRTree ix) Source # | |
(Eq ix, Eq val, Floating val) => Floating (SRTree ix val) Source # | |
Defined in Data.SRTree.Internal 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 # | |
(Eq ix, Eq val, Num val) => Num (SRTree ix val) Source # | |
Defined in Data.SRTree.Internal (+) :: 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 # | |
(Show ix, Show val) => Show (SRTree ix val) Source # | |
(Eq ix, Eq val) => Eq (SRTree ix val) Source # | |
(Ord ix, Ord val) => Ord (SRTree ix val) Source # | |
Defined in Data.SRTree.Internal 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 # | |
(Eq ix, Eq val, Num val, OptIntPow val) => OptIntPow (SRTree ix val) Source # | |
Functions that can be applied to a subtree.
Instances
Enum Function Source # | |
Read Function Source # | |
Show Function Source # | |
Eq Function Source # | |
Ord Function Source # | |
Defined in Data.SRTree.Internal |
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.
traverseIx :: Applicative f => (ixa -> f ixb) -> SRTree ixa val -> f (SRTree ixb val) Source #
Same as traverse
but for the first type parameter.
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.
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
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.