boltzmann-samplers-0.1.0.0: Uniform random generators

Safe HaskellNone
LanguageHaskell2010

Boltzmann.Data.Oracle

Contents

Description

Internal module

Synopsis

Documentation

data DataDef m Source #

We build a dictionary which reifies type information in order to create a Boltzmann generator.

We denote by n (or count) the number of types in the dictionary.

Every type has an index 0 <= i < n; the variable X i represents its generating function C_i(x), and X (i + k*n) the GF of its k-th "pointing" C_i[k](x); we have

  C_i[0](x) = C_i(x)
  C_i[k+1](x) = x * C_i[k]'(x)

where C_i[k]' is the derivative of C_i[k]. See also point.

The order (or valuation) of a power series is the index of the first non-zero coefficient, called the leading coefficient.

Constructors

DataDef 

Fields

Instances

Show (DataDef m) Source # 

Methods

showsPrec :: Int -> DataDef m -> ShowS #

show :: DataDef m -> String #

showList :: [DataDef m] -> ShowS #

data C Source #

A pair C i k represents the k-th "pointing" of the type at index i, with generating function C_i[k](x).

Constructors

C Ix Int 

Instances

Eq C Source # 

Methods

(==) :: C -> C -> Bool #

(/=) :: C -> C -> Bool #

Ord C Source # 

Methods

compare :: C -> C -> Ordering #

(<) :: C -> C -> Bool #

(<=) :: C -> C -> Bool #

(>) :: C -> C -> Bool #

(>=) :: C -> C -> Bool #

max :: C -> C -> C #

min :: C -> C -> C #

Show C Source # 

Methods

showsPrec :: Int -> C -> ShowS #

show :: C -> String #

showList :: [C] -> ShowS #

Generic C Source # 

Associated Types

type Rep C :: * -> * #

Methods

from :: C -> Rep C x #

to :: Rep C x -> C #

Hashable C Source # 

Methods

hashWithSalt :: Int -> C -> Int #

hash :: C -> Int #

type Rep C Source # 
type Rep C = D1 (MetaData "C" "Boltzmann.Data.Oracle" "boltzmann-samplers-0.1.0.0-JXp3XIEjxcQGhw29m2Mjvm" False) (C1 (MetaCons "C" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ix)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

data AC Source #

Constructors

AC Aliased Int 

Instances

Eq AC Source # 

Methods

(==) :: AC -> AC -> Bool #

(/=) :: AC -> AC -> Bool #

Ord AC Source # 

Methods

compare :: AC -> AC -> Ordering #

(<) :: AC -> AC -> Bool #

(<=) :: AC -> AC -> Bool #

(>) :: AC -> AC -> Bool #

(>=) :: AC -> AC -> Bool #

max :: AC -> AC -> AC #

min :: AC -> AC -> AC #

Show AC Source # 

Methods

showsPrec :: Int -> AC -> ShowS #

show :: AC -> String #

showList :: [AC] -> ShowS #

Generic AC Source # 

Associated Types

type Rep AC :: * -> * #

Methods

from :: AC -> Rep AC x #

to :: Rep AC x -> AC #

Hashable AC Source # 

Methods

hashWithSalt :: Int -> AC -> Int #

hash :: AC -> Int #

type Rep AC Source # 
type Rep AC = D1 (MetaData "AC" "Boltzmann.Data.Oracle" "boltzmann-samplers-0.1.0.0-JXp3XIEjxcQGhw29m2Mjvm" False) (C1 (MetaCons "AC" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Aliased)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

type C' = (Maybe Aliased, C) Source #

newtype Aliased Source #

Constructors

Aliased Int 

Instances

Eq Aliased Source # 

Methods

(==) :: Aliased -> Aliased -> Bool #

(/=) :: Aliased -> Aliased -> Bool #

Ord Aliased Source # 
Show Aliased Source # 
Generic Aliased Source # 

Associated Types

type Rep Aliased :: * -> * #

Methods

from :: Aliased -> Rep Aliased x #

to :: Rep Aliased x -> Aliased #

Hashable Aliased Source # 

Methods

hashWithSalt :: Int -> Aliased -> Int #

hash :: Aliased -> Int #

type Rep Aliased Source # 
type Rep Aliased = D1 (MetaData "Aliased" "Boltzmann.Data.Oracle" "boltzmann-samplers-0.1.0.0-JXp3XIEjxcQGhw29m2Mjvm" True) (C1 (MetaCons "Aliased" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

type Ix = Int Source #

data Nat Source #

Constructors

Zero 
Succ Nat 

Instances

Eq Nat Source # 

Methods

(==) :: Nat -> Nat -> Bool #

(/=) :: Nat -> Nat -> Bool #

Ord Nat Source # 

Methods

compare :: Nat -> Nat -> Ordering #

(<) :: Nat -> Nat -> Bool #

(<=) :: Nat -> Nat -> Bool #

(>) :: Nat -> Nat -> Bool #

(>=) :: Nat -> Nat -> Bool #

max :: Nat -> Nat -> Nat #

min :: Nat -> Nat -> Nat #

Show Nat Source # 

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

Monoid Nat Source # 

Methods

mempty :: Nat #

mappend :: Nat -> Nat -> Nat #

mconcat :: [Nat] -> Nat #

collectTypes :: Data a => [Alias m] -> proxy a -> DataDef m Source #

Find all types that may be types of subterms of a value of type a.

This will loop if there are infinitely many such types.

primOrder :: Int Source #

Primitive datatypes have C(x) = x: they are considered as having a single object (lCoef) of size 1 (order)).

type GUnfold m = forall b r. Data b => m (b -> r) -> m r Source #

The type of the first argument of gunfold.

type AMap m = HashMap Aliased (Ix, Alias m) Source #

Type of xedni'.

chaseType :: Data a => proxy a -> ((Maybe (Alias m), Ix) -> AMap m -> AMap m) -> State (DataDef m) (Either Aliased Ix, ((Nat, Integer), Maybe Int)) Source #

traverseType :: Data a => proxy a -> Ix -> State (DataDef m) (Either Aliased Ix, ((Nat, Integer), Maybe Int)) Source #

Traversal of the definition of a datatype.

traverseType' :: Data a => proxy a -> DataType -> State (DataDef m) ([(Integer, Constr, [(Maybe Aliased, C)])], ((Nat, Integer), Maybe Int)) Source #

lPlus :: (Nat, Integer) -> (Nat, Integer) -> (Nat, Integer) Source #

If (u, a) represents a power series of leading term a * x ^ u, and similarly for (u', a'), this finds the leading term of their sum.

The comparison of Nat is unrolled here for maximum laziness.

lSum :: [(Nat, Integer)] -> (Nat, Integer) Source #

Sum of a list of series.

lMul :: (Nat, Integer) -> (Nat, Integer) -> (Nat, Integer) Source #

Leading term of a product of series.

point :: DataDef m -> DataDef m Source #

Pointing operator.

Populates a DataDef with one more level of pointings. (collectTypes produces a dictionary at level 0.)

The "pointing" of a type t is a derived type whose values are essentially values of type t, with one of their constructors being "pointed". Alternatively, we may turn every constructor into variants that indicate the position of points.

  -- Original type
  data Tree = Node Tree Tree | Leaf
  -- Pointing of Tree
  data Tree'
    = Tree' Tree -- Point at the root
    | Node'0 Tree' Tree -- Point to the left
    | Node'1 Tree Tree' -- Point to the right
  -- Pointing of the pointing
  -- Notice that the "points" introduced by both applications of pointing
  -- are considered different: exchanging their positions (when different)
  -- produces a different tree.
  data Tree''
    = Tree'' Tree' -- Point 2 at the root, the inner Tree' places point 1
    | Node'0' Tree' Tree -- Point 1 at the root, point 2 to the left
    | Node'1' Tree Tree' -- Point 1 at the root, point 2 to the right
    | Node'0'0 Tree'' Tree -- Points 1 and 2 to the left
    | Node'0'1 Tree' Tree' -- Point 1 to the left, point 2 to the right
    | Node'1'0 Tree' Tree' -- Point 1 to the right, point 2 to the left
    | Node'0'1 Tree Tree'' -- Points 1 and 2 to the right

If we ignore points, some constructors are equivalent. Thus we may simply calculate their multiplicity instead of duplicating them.

Given a constructor with c arguments C x_1 ... x_c, and a sequence p_0 + p_1 + ... + p_c = k corresponding to a distribution of k points (p_0 are assigned to the constructor C itself, and for i > 0, p_i points are assigned within the i-th subterm), the multiplicity of the constructor paired with that distribution is the multinomial coefficient multinomial k [p_1, ..., p_c].

type Oracle = HashMap C Double Source #

An oracle gives the values of the generating functions at some x.

makeOracle :: DataDef m -> TypeRep -> Maybe Double -> Oracle Source #

Find the value of x such that the average size of the generator for the k-1-th pointing is equal to size, and produce the associated oracle. If the size is Nothing, find the radius of convergence.

The search evaluates the generating functions for some values of x in order to run a binary search. The evaluator is implemented using Newton's method, the convergence of which has been shown for relevant systems in Boltzmann Oracle for Combinatorial Systems, C. Pivoteau, B. Salvy, M. Soria.

phi :: Num a => DataDef m -> C -> [(Integer, constr, [C'])] -> a -> Vector a -> a Source #

Generating function definition. This defines a Phi_i[k] function associated with the k-th pointing of the type at index i, such that:

C_i[k](x)
  = Phi_i[k](x, C_0[0](x), ..., C_(n-1)[0](x),
             ..., C_0[k](x), ..., C_(n-1)[k](x))

Primitive datatypes have C(x) = x: they are considered as having a single object (lCoef) of size 1 (order)).

type Generators m = (HashMap AC (SomeData m), HashMap C (SomeData m)) Source #

Maps a key representing a type a (or one of its pointings) to a generator m a.

makeGenerators :: forall m. MonadRandomLike m => DataDef m -> Oracle -> Generators m Source #

Build all involved generators at once.

smallGenerators :: forall m. MonadRandomLike m => DataDef m -> SmallGenerators m Source #

Generators of values of minimal sizes.

Short operators

(?) :: DataDef m -> C -> Int Source #

listCs :: DataDef m -> [C] Source #

dd ? (listCs dd !! i) = i

ix :: C -> Int Source #

(?!) :: DataDef m -> Int -> C Source #

dd ? (dd ?! i) = i

getGenerator :: Data a => DataDef m -> Generators m -> proxy a -> Int -> m a Source #

getSmallGenerator :: Data a => DataDef m -> SmallGenerators m -> proxy a -> m a Source #

(#!) :: (Eq k, Hashable k) => HashMap k v -> k -> v Source #