| Copyright | Sean Burton 2015 |
|---|---|
| License | BSD3 |
| Maintainer | burton.seanr@gmail.com |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell98 |
Control.SpaceProbe
Contents
Description
An applicative combinator library for parameter optimization designed to perform well over high-dimensional and/or discontinuous search spaces, using Monte-Carlo Tree Search with several enhancements.
- data Probe t = forall s . Probe {
- _initial :: s
- _partition :: s -> Forest s
- _draw :: s -> Maybe t
- newPartition :: (s -> [s]) -> s -> Forest s
- distribution :: Floating b => (b -> a) -> Probe a
- exponential :: Floating a => a -> Probe a
- normal :: (Eq a, InvErf a) => a -> a -> Probe a
- uniform :: Floating a => a -> a -> Probe a
- intDistribution :: (Integral a, Floating b, Ord b) => (a -> b) -> a -> a -> Probe a
- exponentialInt :: (Bounded a, Integral a) => Float -> Probe a
- normalInt :: (Bounded a, Integral a) => Float -> Float -> Probe a
- uniformInt :: (Eq a, Integral a) => a -> a -> Probe a
- constants :: [a] -> Probe a
- permute :: [a] -> Probe [a]
- sizedSublist :: Int -> [a] -> Probe [a]
- sizedWithReplacement :: Int -> [a] -> Probe [a]
- sublist :: [a] -> Probe [a]
- withReplacement :: [a] -> Probe [a]
- maximize :: (t -> Float) -> Probe t -> [(t, Float)]
- minimize :: (t -> Float) -> Probe t -> [(t, Float)]
- maximizeM :: Monad m => (t -> m Float) -> Probe t -> m [(t, Float)]
- minimizeM :: Monad m => (t -> m Float) -> Probe t -> m [(t, Float)]
- maximizeIO :: (t -> IO Float) -> Probe t -> IO [(t, Float)]
- minimizeIO :: (t -> IO Float) -> Probe t -> IO [(t, Float)]
- highestYet :: [(a, Float)] -> [(a, Float)]
- lowestYet :: [(a, Float)] -> [(a, Float)]
- evaluateForusecs :: Int -> [a] -> IO [a]
Documentation
The main data structure for this module; it describes a search space and an associated exploration strategy.
This type is an instance of the following classes:
Functorwhich does the obvious thing.Applicative, which allows us to combine multiple search spaces and optimize over them simultaneously.Alternative, which allows us to optimize over the disjoint union of two search spaces.
Constructors
| forall s . Probe | |
Fields
| |
Instances
newPartition :: (s -> [s]) -> s -> Forest s Source
generate a partition function to be use in the construction of custom Probes.
Floating search spaces
distribution :: Floating b => (b -> a) -> Probe a Source
Uses inverse transform sampling to draw from a probability distribution given the associated inverse cumulative distribution function.
exponential :: Floating a => a -> Probe a Source
Sample from the exponential distribution with given mean. Useful for constants which are potentially unbounded but probably small.
normal :: (Eq a, InvErf a) => a -> a -> Probe a Source
Sample from the normal distribution with given mean and standard deviation
Integral search spaces
intDistribution :: (Integral a, Floating b, Ord b) => (a -> b) -> a -> a -> Probe a Source
Approximately sample from a probability distribution over the range [a, b). Relies on splitting the range into regions of approximately equal probability so will be less accurate for small ranges or highly unequal distributions.
normalInt :: (Bounded a, Integral a) => Float -> Float -> Probe a Source
Sample from an approximate normal distribution with given mean and standard deviation. May fail if a very large mean and/or standard deviation is given.
uniformInt :: (Eq a, Integral a) => a -> a -> Probe a Source
Sample uniformly from the interval [a, b).
Discrete search spaces
permute :: [a] -> Probe [a] Source
Samples uniformly from permutations of xs. Makes the assumption that
permutations which are lexicographically close are likely to have similar
fitness.
sizedSublist :: Int -> [a] -> Probe [a] Source
Samples sublists of xs of size k. The order of elements in xs is
irrelevant.
sizedWithReplacement :: Int -> [a] -> Probe [a] Source
Samples sublists of xs of size k with replacement.
The order of elements in xs is irrelevant.
sublist :: [a] -> Probe [a] Source
Samples progressively larger sublists of xs. More important elements
(those which are likely to affect the fitness of a sample more) should
ideally be placed closest to the start of xs.
withReplacement :: [a] -> Probe [a] Source
Samples progressively larger sublists of xs with replacement. The order
of elements in xs is irrelevant.
Optimization
maximize :: (t -> Float) -> Probe t -> [(t, Float)] Source
Fairly self-explanatory. Maximize the objective function eval over the
given Probe. Keeps lazily generating samples until it explores the whole
search space so you almost certainly want to apply some cut-off criterion.
minimize :: (t -> Float) -> Probe t -> [(t, Float)] Source
The opposite of maximize.
minimize eval = map (fmap negate) . maximize (negate . eval)
Monadic Optimization
maximizeM :: Monad m => (t -> m Float) -> Probe t -> m [(t, Float)] Source
Maximize in the given monad. The underlying bind operator must be lazy if you want to generate the result list incrementally.
Optimization in IO
maximizeIO :: (t -> IO Float) -> Probe t -> IO [(t, Float)] Source
The equivalent of maximize, but running in the IO Monad. Generates the output list lazily.
Optimization output processing
highestYet :: [(a, Float)] -> [(a, Float)] Source
Preserves only those elements (_, b) for which b is higher than for
all previous previous values in the list. Designed for use with
maximization
lowestYet :: [(a, Float)] -> [(a, Float)] Source
Preserves only those elements (_, b) for which b is lower than for all
previous values in the list. Designed for use with minimization.
lowestYet xs == map (fmap negate) . highestYet . map (fmap negate)
evaluateForusecs :: Int -> [a] -> IO [a] Source
Take the largest prefix of xs which can be evaluated within dt
microseconds.