-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A general framework to work with Symbolic Regression expression trees. -- -- A Symbolic Regression Tree data structure to work with mathematical -- expressions with support to first order derivative and simplification; @package srtree @version 1.0.0.1 module Data.SRTree.Recursion data ListF a b NilF :: ListF a b ConsF :: a -> b -> ListF a b data NatF a ZeroF :: NatF a SuccF :: a -> NatF a data StreamF a b StreamF :: a -> b -> StreamF a b data TreeF a b LeafF :: TreeF a b NodeF :: b -> a -> b -> TreeF a b newtype Fix f Fix :: f (Fix f) -> Fix f [unfix] :: Fix f -> f (Fix f) type Algebra f a = f a -> a type CoAlgebra f a = a -> f a data Cofree f a (:<) :: a -> f (Cofree f a) -> Cofree f a data Free f a Ret :: a -> Free f a Op :: f (Free f a) -> Free f a extract :: Cofree f a -> a unOp :: Free f a -> f (Free f a) cata :: Functor f => (f a -> a) -> Fix f -> a cataM :: (Functor f, Monad m) => (forall x. f (m x) -> m (f x)) -> (f a -> m a) -> Fix f -> m a ana :: Functor f => (a -> f a) -> a -> Fix f hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b para :: Functor f => (f (Fix f, a) -> a) -> Fix f -> a mutu :: Functor f => (f (a, b) -> a) -> (f (a, b) -> b) -> (Fix f -> a, Fix f -> b) apo :: Functor f => (a -> f (Either (Fix f) a)) -> a -> Fix f accu :: Functor f => (forall x. f x -> p -> f (x, p)) -> (f a -> p -> a) -> Fix f -> p -> a histo :: Functor f => (f (Cofree f a) -> a) -> Fix f -> a futu :: Functor f => (a -> f (Free f a)) -> a -> Fix f chrono :: Functor f => (f (Cofree f b) -> b) -> (a -> f (Free f a)) -> a -> b fromList :: [a] -> Fix (ListF a) toList :: Fix (ListF a) -> [a] stream2list :: StreamF a [a] -> [a] toNat :: Int -> Fix NatF fromNat :: Fix NatF -> Int instance GHC.Base.Functor (Data.SRTree.Recursion.ListF a) instance GHC.Base.Functor Data.SRTree.Recursion.NatF instance GHC.Base.Functor (Data.SRTree.Recursion.StreamF a) instance GHC.Base.Functor (Data.SRTree.Recursion.TreeF a) -- | Expression tree for Symbolic Regression module Data.SRTree.Internal -- | Tree structure to be used with Symbolic Regression algorithms. This -- structure is a fixed point of a n-ary tree. data SRTree val -- | index of the variables Var :: Int -> SRTree val -- | index of the parameter Param :: Int -> SRTree val -- | constant value, can be converted to a parameter Const :: Double -> SRTree val -- | univariate function Uni :: Function -> val -> SRTree val -- | binary operator Bin :: Op -> val -> val -> SRTree val -- | Supported functions data Function Id :: Function Abs :: Function Sin :: Function Cos :: Function Tan :: Function Sinh :: Function Cosh :: Function Tanh :: Function ASin :: Function ACos :: Function ATan :: Function ASinh :: Function ACosh :: Function ATanh :: Function Sqrt :: Function Cbrt :: Function Square :: Function Log :: Function Exp :: Function -- | Supported operators data Op Add :: Op Sub :: Op Mul :: Op Div :: Op Power :: Op -- | create a tree with a single node representing a parameter param :: Int -> Fix SRTree -- | create a tree with a single node representing a variable var :: Int -> Fix SRTree -- | Arity of the current node arity :: Fix SRTree -> Int -- | Get the children of a node. Returns an empty list in case of a leaf -- node. getChildren :: Fix SRTree -> [Fix SRTree] -- | Count the number of nodes in a tree. countNodes :: Fix SRTree -> Int -- | Count the number of Var nodes countVarNodes :: Fix SRTree -> Int -- | Count the number of const nodes countConsts :: Fix SRTree -> Int -- | Count the number of Param nodes countParams :: Fix SRTree -> Int -- | Count the occurrences of variable indexed as ix countOccurrences :: Int -> Fix SRTree -> Int -- | Creates the symbolic partial derivative of a tree by variable -- dx (if p is False) or parameter dx -- (if p is True). deriveBy :: Bool -> Int -> Fix SRTree -> Fix SRTree -- | Symbolic derivative by a variable deriveByVar :: Int -> Fix SRTree -> Fix SRTree -- | Symbolic derivative by a parameter deriveByParam :: Int -> Fix SRTree -> Fix SRTree derivative :: Floating a => Function -> a -> a -- | 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. forwardMode :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> [a] -- | 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. gradParams :: (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 -- | Returns the inverse of a function. This is a partial function. inverseFunc :: Function -> Function -- | 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. evalTree :: (Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> a -- | Relabel the parameters incrementaly starting from 0 relabelParams :: Fix SRTree -> Fix SRTree -- | Change constant values to a parameter, returning the changed tree and -- a list of parameter values constsToParam :: Fix SRTree -> (Fix SRTree, [Double]) -- | Same as constsToParam but does not change constant values that -- can be converted to integer without loss of precision floatConstsToParam :: Fix SRTree -> (Fix SRTree, [Double]) instance GHC.Enum.Enum Data.SRTree.Internal.Op instance GHC.Classes.Ord Data.SRTree.Internal.Op instance GHC.Classes.Eq Data.SRTree.Internal.Op instance GHC.Read.Read Data.SRTree.Internal.Op instance GHC.Show.Show Data.SRTree.Internal.Op instance GHC.Enum.Enum Data.SRTree.Internal.Function instance GHC.Classes.Ord Data.SRTree.Internal.Function instance GHC.Classes.Eq Data.SRTree.Internal.Function instance GHC.Read.Read Data.SRTree.Internal.Function instance GHC.Show.Show Data.SRTree.Internal.Function instance GHC.Base.Functor Data.SRTree.Internal.SRTree instance GHC.Classes.Ord val => GHC.Classes.Ord (Data.SRTree.Internal.SRTree val) instance GHC.Classes.Eq val => GHC.Classes.Eq (Data.SRTree.Internal.SRTree val) instance GHC.Show.Show val => GHC.Show.Show (Data.SRTree.Internal.SRTree val) instance GHC.Base.Functor Data.SRTree.Internal.Tape instance GHC.Show.Show a => GHC.Show.Show (Data.SRTree.Internal.Tape a) instance GHC.Num.Num a => GHC.Num.Num (Data.SRTree.Internal.Tape a) instance GHC.Float.Floating a => GHC.Float.Floating (Data.SRTree.Internal.Tape a) instance GHC.Real.Fractional a => GHC.Real.Fractional (Data.SRTree.Internal.Tape a) instance GHC.Num.Num (Data.SRTree.Recursion.Fix Data.SRTree.Internal.SRTree) instance GHC.Real.Fractional (Data.SRTree.Recursion.Fix Data.SRTree.Internal.SRTree) instance GHC.Float.Floating (Data.SRTree.Recursion.Fix Data.SRTree.Internal.SRTree) -- | Functions to generate random trees and nodes. module Data.SRTree.Random class HasVars p class HasVals p class HasFuns p -- | Constraint synonym for all properties. type HasEverything p = (HasVars p, HasVals p, HasExps p, HasFuns p) -- | A structure with every property data FullParams P :: [Int] -> (Double, Double) -> (Int, Int) -> [Function] -> FullParams -- | RndTree is a Monad Transformer to generate random trees of type -- `SRTree ix val` given the parameters `p ix val` using the random -- number generator StdGen. type RndTree p = ReaderT p (StateT StdGen IO) (Fix SRTree) -- | Returns a random variable, the parameter p must have the -- HasVars property randomVar :: HasVars p => RndTree p -- | Returns a random constant, the parameter p must have the -- HasConst property randomConst :: HasVals p => RndTree p -- | Returns a random integer power node, the parameter p must -- have the HasExps property randomPow :: HasExps p => RndTree p -- | Returns a random function, the parameter p must have the -- HasFuns property randomFunction :: HasFuns p => RndTree p -- | Returns a random node, the parameter p must have every -- property. randomNode :: HasEverything p => RndTree p -- | Returns a random non-terminal node, the parameter p must have -- every property. randomNonTerminal :: HasEverything p => RndTree p -- | Returns a random tree with a limited budget, the parameter p -- must have every property. randomTree :: HasEverything p => Int -> RndTree p -- | Returns a random tree with a approximately a number n of -- nodes, the parameter p must have every property. randomTreeBalanced :: HasEverything p => Int -> RndTree p instance Data.SRTree.Random.HasVars Data.SRTree.Random.FullParams instance Data.SRTree.Random.HasVals Data.SRTree.Random.FullParams instance Data.SRTree.Random.HasExps Data.SRTree.Random.FullParams instance Data.SRTree.Random.HasFuns Data.SRTree.Random.FullParams -- | Conversion functions to display the expression trees in different -- formats. module Data.SRTree.Print showExpr :: Fix SRTree -> String printExpr :: Fix SRTree -> IO () -- | Displays a tree in Tikz format showTikz :: Fix SRTree -> String printTikz :: Fix SRTree -> IO () -- | Displays a tree as a numpy compatible expression. showPython :: Fix SRTree -> String printPython :: Fix SRTree -> IO () -- | Displays a tree as a sympy compatible expression. showLatex :: Fix SRTree -> String printLatex :: Fix SRTree -> IO () -- | Expression tree for Symbolic Regression module Data.SRTree -- | Tree structure to be used with Symbolic Regression algorithms. This -- structure is a fixed point of a n-ary tree. data SRTree val -- | index of the variables Var :: Int -> SRTree val -- | index of the parameter Param :: Int -> SRTree val -- | constant value, can be converted to a parameter Const :: Double -> SRTree val -- | univariate function Uni :: Function -> val -> SRTree val -- | binary operator Bin :: Op -> val -> val -> SRTree val -- | Supported functions data Function Id :: Function Abs :: Function Sin :: Function Cos :: Function Tan :: Function Sinh :: Function Cosh :: Function Tanh :: Function ASin :: Function ACos :: Function ATan :: Function ASinh :: Function ACosh :: Function ATanh :: Function Sqrt :: Function Cbrt :: Function Square :: Function Log :: Function Exp :: Function -- | Supported operators data Op Add :: Op Sub :: Op Mul :: Op Div :: Op Power :: Op -- | create a tree with a single node representing a parameter param :: Int -> Fix SRTree -- | create a tree with a single node representing a variable var :: Int -> Fix SRTree -- | Arity of the current node arity :: Fix SRTree -> Int -- | Get the children of a node. Returns an empty list in case of a leaf -- node. getChildren :: Fix SRTree -> [Fix SRTree] -- | Count the number of nodes in a tree. countNodes :: Fix SRTree -> Int -- | Count the number of Var nodes countVarNodes :: Fix SRTree -> Int -- | Count the number of const nodes countConsts :: Fix SRTree -> Int -- | Count the number of Param nodes countParams :: Fix SRTree -> Int -- | Count the occurrences of variable indexed as ix countOccurrences :: Int -> Fix SRTree -> Int -- | Creates the symbolic partial derivative of a tree by variable -- dx (if p is False) or parameter dx -- (if p is True). deriveBy :: Bool -> Int -> Fix SRTree -> Fix SRTree -- | Symbolic derivative by a variable deriveByVar :: Int -> Fix SRTree -> Fix SRTree -- | Symbolic derivative by a parameter deriveByParam :: Int -> Fix SRTree -> Fix SRTree derivative :: Floating a => Function -> a -> a -- | 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. forwardMode :: (Show a, Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> [a] -- | 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. gradParams :: (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 -- | Returns the inverse of a function. This is a partial function. inverseFunc :: Function -> Function -- | 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. evalTree :: (Num a, Floating a) => Vector a -> Vector Double -> (Double -> a) -> Fix SRTree -> a -- | Relabel the parameters incrementaly starting from 0 relabelParams :: Fix SRTree -> Fix SRTree -- | Change constant values to a parameter, returning the changed tree and -- a list of parameter values constsToParam :: Fix SRTree -> (Fix SRTree, [Double]) -- | Same as constsToParam but does not change constant values that -- can be converted to integer without loss of precision floatConstsToParam :: Fix SRTree -> (Fix SRTree, [Double])