generic-random-0.1.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Data.Random.Generics.Internal.Oracle

Contents

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

count :: Int

Number of registered types

points :: Int

Number of iterations of the pointing operator

index :: HashMap TypeRep (Either Aliased Ix)

Map from types to indices

xedni :: HashMap Ix SomeData'

Inverse map from indices to types

xedni' :: HashMap Aliased (Ix, Alias m)

Inverse map to aliases

types :: HashMap C [(Integer, Constr, [C'])]

Structure of types and their pointings (up to points, initially 0)

Primitive types and empty types are mapped to an empty constructor list, and can be distinguished using dataTypeRep on the SomeData associated to it by xedni.

The integer is a multiplicity which can be > 1 for pointings.

lTerm :: HashMap Ix (Nat, Integer)

Leading term a * x ^ u of the generating functions C_i[k](x) in the form (u, a).

Order u
Smallest size of objects of a given type.
Leading coefficient a
number of objects of smallest size.
degree :: HashMap Ix Int

Degrees of the generating functions, when applicable: greatest size of objects of a given type.

Instances

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 

type C' = (Maybe Aliased, C) Source

type Ix = Int Source

data Nat Source

Constructors

Zero 
Succ 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 :: (Functor m, Data a) => DataDef m -> Generators m -> proxy a -> Int -> m a Source

getSmallGenerator :: (Functor m, Data a) => DataDef m -> SmallGenerators m -> proxy a -> m a Source

General helper functions

frequencyWith :: (Show r, Ord r, Num r, Monad m) => (r -> m r) -> [(r, m a)] -> m a Source

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

partitions :: Int -> Int -> [[Int]] Source

partitions k n: lists of non-negative integers of length n with sum less than or equal to k.

multinomial :: Int -> [Int] -> Integer Source

Multinomial coefficient.

multinomial n ps == factorial n `div` product [factorial p | p <- ps]

binomial :: Int -> Int -> Integer Source

Binomial coefficient.

binomial n k == factorial n `div` (factorial k * factorial (n-k))