boltzmann-samplers-0.1.0.0: Uniform random generators

Safe HaskellNone
LanguageHaskell2010

Boltzmann.Species

Description

Applicative interface to define recursive structures and derive Boltzmann samplers.

Given the recursive structure of the types, and how to combine generators, the library takes care of computing the oracles and setting the right distributions.

Synopsis

Documentation

class Embed f m where Source #

Minimal complete definition

emap, embed

Methods

emap :: (m a -> m b) -> f a -> f b Source #

embed :: m a -> f a Source #

A natural transformation between f and m?

Instances

Embed f m => Embed (Pointiful f) m Source # 

Methods

emap :: (m a -> m b) -> Pointiful f a -> Pointiful f b Source #

embed :: m a -> Pointiful f a Source #

MonadRandomLike m => Embed (Weighted m) m Source # 

Methods

emap :: (m a -> m b) -> Weighted m a -> Weighted m b Source #

embed :: m a -> Weighted m a Source #

Num r => Embed (ConstModule r) m Source # 

Methods

emap :: (m a -> m b) -> ConstModule r a -> ConstModule r b Source #

embed :: m a -> ConstModule r a Source #

class (Alternative f, Num (Scalar f)) => Module f where Source #

Applicative defines a product, Alternative defines an addition, with scalar multiplication we get a module.

This typeclass allows to directly tweak weights in the oracle by chosen factors.

Associated Types

type Scalar f :: * Source #

Methods

scalar :: Scalar f -> f () Source #

Scalar embedding.

(<.>) :: Scalar f -> f a -> f a infixr 3 Source #

Scalar multiplication.

Instances

Module f => Module (Pointiful f) Source # 

Associated Types

type Scalar (Pointiful f :: * -> *) :: * Source #

MonadRandomLike m => Module (Weighted m) Source # 

Associated Types

type Scalar (Weighted m :: * -> *) :: * Source #

Methods

scalar :: Scalar (Weighted m) -> Weighted m () Source #

(<.>) :: Scalar (Weighted m) -> Weighted m a -> Weighted m a Source #

Num r => Module (ConstModule r) Source # 

Associated Types

type Scalar (ConstModule r :: * -> *) :: * Source #

type Endo a = a -> a Source #

data System f a c Source #

Constructors

System 

Fields

Instances

Functor (System f a) Source # 

Methods

fmap :: (a -> b) -> System f a a -> System f a b #

(<$) :: a -> System f a b -> System f a a #

sys :: System f a c -> f () -> Vector (f a) -> Vector (f a) Source #

newtype ConstModule r a Source #

Constructors

ConstModule 

Fields

Instances

Functor (ConstModule r) Source # 

Methods

fmap :: (a -> b) -> ConstModule r a -> ConstModule r b #

(<$) :: a -> ConstModule r b -> ConstModule r a #

Num r => Applicative (ConstModule r) Source # 

Methods

pure :: a -> ConstModule r a #

(<*>) :: ConstModule r (a -> b) -> ConstModule r a -> ConstModule r b #

(*>) :: ConstModule r a -> ConstModule r b -> ConstModule r b #

(<*) :: ConstModule r a -> ConstModule r b -> ConstModule r a #

Num r => Alternative (ConstModule r) Source # 

Methods

empty :: ConstModule r a #

(<|>) :: ConstModule r a -> ConstModule r a -> ConstModule r a #

some :: ConstModule r a -> ConstModule r [a] #

many :: ConstModule r a -> ConstModule r [a] #

Num r => Module (ConstModule r) Source # 

Associated Types

type Scalar (ConstModule r :: * -> *) :: * Source #

Num r => Embed (ConstModule r) m Source # 

Methods

emap :: (m a -> m b) -> ConstModule r a -> ConstModule r b Source #

embed :: m a -> ConstModule r a Source #

type Scalar (ConstModule r) Source # 
type Scalar (ConstModule r) = r

solve :: forall b c. (forall a. Num a => System (ConstModule a) b c) -> Double -> Maybe (Vector Double) Source #

sizedGenerator Source #

Arguments

:: MonadRandomLike m 
=> (forall f. (Module f, Embed f m) => System (Pointiful f) b c) 
-> Int

Index of type

-> Int

Points

-> Maybe Double

Expected size (or singular sampler)

-> m b 

solveSized Source #

Arguments

:: (forall a. Num a => System (Pointiful (ConstModule a)) b c) 
-> Int

Index of type

-> Int

Points

-> Maybe Double

Expected size (or singular sampler)

-> (Double, Vector Double) 

newtype Weighted m a Source #

Constructors

Weighted [(Double, m a)] 

Instances

Functor m => Functor (Weighted m) Source # 

Methods

fmap :: (a -> b) -> Weighted m a -> Weighted m b #

(<$) :: a -> Weighted m b -> Weighted m a #

MonadRandomLike m => Applicative (Weighted m) Source # 

Methods

pure :: a -> Weighted m a #

(<*>) :: Weighted m (a -> b) -> Weighted m a -> Weighted m b #

(*>) :: Weighted m a -> Weighted m b -> Weighted m b #

(<*) :: Weighted m a -> Weighted m b -> Weighted m a #

MonadRandomLike m => Alternative (Weighted m) Source # 

Methods

empty :: Weighted m a #

(<|>) :: Weighted m a -> Weighted m a -> Weighted m a #

some :: Weighted m a -> Weighted m [a] #

many :: Weighted m a -> Weighted m [a] #

MonadRandomLike m => Module (Weighted m) Source # 

Associated Types

type Scalar (Weighted m :: * -> *) :: * Source #

Methods

scalar :: Scalar (Weighted m) -> Weighted m () Source #

(<.>) :: Scalar (Weighted m) -> Weighted m a -> Weighted m a Source #

MonadRandomLike m => Embed (Weighted m) m Source # 

Methods

emap :: (m a -> m b) -> Weighted m a -> Weighted m b Source #

embed :: m a -> Weighted m a Source #

type Scalar (Weighted m) Source # 

weighted :: Double -> m a -> Weighted m a Source #

sfix :: MonadRandomLike m => System (Weighted m) b c -> Double -> Vector Double -> (Vector (m b), c) Source #

data Pointiful f a Source #

Constructors

Pointiful [f a] 
Zero (f a) 

Instances

Functor f => Functor (Pointiful f) Source # 

Methods

fmap :: (a -> b) -> Pointiful f a -> Pointiful f b #

(<$) :: a -> Pointiful f b -> Pointiful f a #

Module f => Applicative (Pointiful f) Source # 

Methods

pure :: a -> Pointiful f a #

(<*>) :: Pointiful f (a -> b) -> Pointiful f a -> Pointiful f b #

(*>) :: Pointiful f a -> Pointiful f b -> Pointiful f b #

(<*) :: Pointiful f a -> Pointiful f b -> Pointiful f a #

Module f => Alternative (Pointiful f) Source # 

Methods

empty :: Pointiful f a #

(<|>) :: Pointiful f a -> Pointiful f a -> Pointiful f a #

some :: Pointiful f a -> Pointiful f [a] #

many :: Pointiful f a -> Pointiful f [a] #

Module f => Module (Pointiful f) Source # 

Associated Types

type Scalar (Pointiful f :: * -> *) :: * Source #

Embed f m => Embed (Pointiful f) m Source # 

Methods

emap :: (m a -> m b) -> Pointiful f a -> Pointiful f b Source #

embed :: m a -> Pointiful f a Source #

type Scalar (Pointiful f) Source # 
type Scalar (Pointiful f) = Scalar f

point :: Module f => Int -> System (Pointiful f) b c -> System f b c Source #