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 val
- data Function
- data Op
- param :: Int -> Fix SRTree
- var :: Int -> Fix SRTree
- arity :: Fix SRTree -> Int
- getChildren :: Fix SRTree -> [Fix SRTree]
- countNodes :: Fix SRTree -> Int
- countVarNodes :: Fix SRTree -> Int
- countConsts :: Fix SRTree -> Int
- countParams :: Fix SRTree -> Int
- countOccurrences :: Int -> Fix SRTree -> Int
- deriveBy :: Bool -> Int -> Fix SRTree -> Fix SRTree
- deriveByVar :: Int -> Fix SRTree -> Fix SRTree
- deriveByParam :: Int -> Fix SRTree -> Fix SRTree
- derivative :: Floating a => Function -> a -> a
- forwardMode :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> [a]
- gradParamsFwd :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> (a, [a])
- gradParamsRev :: forall a. (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> (a, [a])
- evalFun :: Floating a => Function -> a -> a
- evalOp :: Floating a => Op -> a -> a -> a
- inverseFunc :: Function -> Function
- evalTree :: (Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> a
- relabelParams :: Fix SRTree -> Fix SRTree
- constsToParam :: Fix SRTree -> (Fix SRTree, [Double])
- floatConstsToParam :: Fix SRTree -> (Fix SRTree, [Double])
- paramsToConst :: [Double] -> Fix SRTree -> Fix SRTree
- newtype Fix f = Fix {}
Documentation
Tree structure to be used with Symbolic Regression algorithms. This structure is a fixed point of a n-ary tree.
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
Supported functions
Instances
Enum Function Source # | |
Defined in Data.SRTree.Internal succ :: Function -> Function Source # pred :: Function -> Function Source # toEnum :: Int -> Function Source # fromEnum :: Function -> Int Source # enumFrom :: Function -> [Function] Source # enumFromThen :: Function -> Function -> [Function] Source # enumFromTo :: Function -> Function -> [Function] Source # enumFromThenTo :: Function -> Function -> Function -> [Function] Source # | |
Read Function Source # | |
Show Function Source # | |
Eq Function Source # | |
Ord Function Source # | |
Defined in Data.SRTree.Internal |
Supported operators
getChildren :: Fix SRTree -> [Fix SRTree] Source #
Get the children of a node. Returns an empty list in case of a leaf node.
countOccurrences :: Int -> Fix SRTree -> Int Source #
Count the occurrences of variable indexed as ix
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 #
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
Instances
Floating (Fix SRTree) Source # | |
Defined in Data.SRTree.Internal exp :: Fix SRTree -> Fix SRTree Source # log :: Fix SRTree -> Fix SRTree Source # sqrt :: Fix SRTree -> Fix SRTree Source # (**) :: Fix SRTree -> Fix SRTree -> Fix SRTree Source # logBase :: Fix SRTree -> Fix SRTree -> Fix SRTree Source # sin :: Fix SRTree -> Fix SRTree Source # cos :: Fix SRTree -> Fix SRTree Source # tan :: Fix SRTree -> Fix SRTree Source # asin :: Fix SRTree -> Fix SRTree Source # acos :: Fix SRTree -> Fix SRTree Source # atan :: Fix SRTree -> Fix SRTree Source # sinh :: Fix SRTree -> Fix SRTree Source # cosh :: Fix SRTree -> Fix SRTree Source # tanh :: Fix SRTree -> Fix SRTree Source # asinh :: Fix SRTree -> Fix SRTree Source # acosh :: Fix SRTree -> Fix SRTree Source # atanh :: Fix SRTree -> Fix SRTree Source # log1p :: Fix SRTree -> Fix SRTree Source # expm1 :: Fix SRTree -> Fix SRTree Source # | |
Num (Fix SRTree) Source # | |
Defined in Data.SRTree.Internal | |
Fractional (Fix SRTree) Source # | |