Copyright | (c) Fabricio Olivetti 2021 - 2024 |
---|---|
License | BSD3 |
Maintainer | fabricio.olivetti@gmail.com |
Stability | experimental |
Portability | ConstraintKinds |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Functions to generate random trees and nodes.
Synopsis
- class HasVars p
- class HasVals p
- class HasFuns p
- type HasEverything p = (HasVars p, HasVals p, HasExps p, HasFuns p)
- data FullParams = P [Int] (Double, Double) (Int, Int) [Function]
- type RndTree p = ReaderT p (StateT StdGen IO) (Fix SRTree)
- randomVar :: HasVars p => RndTree p
- randomConst :: HasVals p => RndTree p
- randomPow :: HasExps p => RndTree p
- randomFunction :: HasFuns p => RndTree p
- randomNode :: HasEverything p => RndTree p
- randomNonTerminal :: HasEverything p => RndTree p
- randomTree :: HasEverything p => Int -> RndTree p
- randomTreeBalanced :: HasEverything p => Int -> RndTree p
Documentation
_vars
Instances
HasVars FullParams Source # | |
Defined in Data.SRTree.Random _vars :: FullParams -> [Int] |
_range
Instances
HasVals FullParams Source # | |
Defined in Data.SRTree.Random _range :: FullParams -> (Double, Double) |
_funs
Instances
HasFuns FullParams Source # | |
Defined in Data.SRTree.Random _funs :: FullParams -> [Function] |
type HasEverything p = (HasVars p, HasVals p, HasExps p, HasFuns p) Source #
Constraint synonym for all properties.
data FullParams Source #
A structure with every property
Instances
HasFuns FullParams Source # | |
Defined in Data.SRTree.Random _funs :: FullParams -> [Function] | |
HasVals FullParams Source # | |
Defined in Data.SRTree.Random _range :: FullParams -> (Double, Double) | |
HasVars FullParams Source # | |
Defined in Data.SRTree.Random _vars :: FullParams -> [Int] |
type RndTree p = ReaderT p (StateT StdGen IO) (Fix SRTree) Source #
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
.
randomVar :: HasVars p => RndTree p Source #
Returns a random variable, the parameter p
must have the HasVars
property
randomConst :: HasVals p => RndTree p Source #
Returns a random constant, the parameter p
must have the HasConst
property
randomPow :: HasExps p => RndTree p Source #
Returns a random integer power node, the parameter p
must have the HasExps
property
randomFunction :: HasFuns p => RndTree p Source #
Returns a random function, the parameter p
must have the HasFuns
property
randomNode :: HasEverything p => RndTree p Source #
Returns a random node, the parameter p
must have every property.
randomNonTerminal :: HasEverything p => RndTree p Source #
Returns a random non-terminal node, the parameter p
must have every property.
randomTree :: HasEverything p => Int -> RndTree p Source #
Returns a random tree with a limited budget, the parameter p
must have every property.
>>>
let treeGen = runReaderT (randomTree 12) (P [0,1] (-10, 10) (2, 3) [Log, Exp])
>>>
tree <- evalStateT treeGen (mkStdGen 52)
>>>
showExpr tree
"(-2.7631152121655838 / Exp((x0 / ((x0 * -7.681722660704317) - Log(3.378309080134594)))))"
randomTreeBalanced :: HasEverything p => Int -> RndTree p Source #
Returns a random tree with a approximately a number n
of nodes, the parameter p
must have every property.
>>>
let treeGen = runReaderT (randomTreeBalanced 10) (P [0,1] (-10, 10) (2, 3) [Log, Exp])
>>>
tree <- evalStateT treeGen (mkStdGen 42)
>>>
showExpr tree
"Exp(Log((((7.784360517385774 * x0) - (3.6412224491658223 ^ x1)) ^ ((x0 ^ -4.09764995657091) + Log(-7.710216839988497)))))"