random-cycle-0.1.2.0: Uniform draws of partitions and cycle-partitions, with thinning.
Safe HaskellNone
LanguageHaskell2010

RandomCycle.List

Synopsis

Partitions

uniformPartition :: StatefulGen g m => [a] -> g -> m [[a]] Source #

Draw a random partition of the input list xs from the uniform distribution on partitions. This proceeds by randomizing the placement of each breakpoint, in other words by walking a random path in a perfect binary tree. O(n) for a vector length n.

This function preserves the order of the input list.

Examples

Expand
>>> import System.Random.Stateful
>>> pureGen = mkStdGen 0
>>> runStateGen_ pureGen $ uniformPartition [1..5::Int]
[[1,2,3],[4],[5]]
>>> runStateGen_ pureGen $ uniformPartition ([] :: [Int])
[]

uniformPartitionThin :: StatefulGen g m => Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]]) Source #

Generate a partition with a local condition r on each partition element. Construction of a partition shortcircuits to failure as soon as the local condition is false.

Since this is a rejection sampling method, the user is asked to provide a counter for the maximum number of sampling attempts in order to guarantee termination in cases where the edge predicate has probability of success close to zero.

Run time on average is O(n/p) where p is the probability all r yss == True for a uniformly generated partition yss, assuming r has run time linear in the length of its argument. This can be highly non-linear because p in general is a function of n.

Some cases can perhaps be deceptively expensive: For example, the condition r = ((>= 2) . length) leads to huge runtimes, since the number of partitions with at least one element of length 1 is exponential in n.

Examples

Expand
>>> import System.Random.Stateful
>>> maxit = 1000
>>> pureGen = mkStdGen 0
>>> r = (>= 2) . length
>>> runStateGen_ pureGen $ uniformPartitionThin maxit r [1..5::Int]
Just [[1,2],[3, 4, 5]]
>>> runStateGen_ pureGen $ uniformPartitionThin maxit (const False) ([] :: [Int])
Just []
>>> runStateGen_ pureGen $ uniformPartitionThin maxit r [1::Int]
Nothing

partitionLengths :: Word -> Int -> [Int] Source #

Primarily a testing utility, to compute directly the lengths of each partition element for a list of size n, using countTrailingZeros. Note this uses Word.

partitionFromBits :: Natural -> [a] -> [[a]] Source #

Utility to generate a list partition using the provided Natural as grouping variable, viewed as Bits. The choice of grouping variable is to improve performance since the number of partitions grows exponentially in the input list length.

This can be used to generate a list of all possible partitions of the input list as shown in the example. See partitionFromBits for other examples.

>>> import GHC.Natural
>>> allPartitions n | n < 0 = []
>>> allPartitions n = map (`partitionFromBits` [0..n-1]) [0 .. 2^(n-1) - 1]
>>> allPartitions 4
[[[0,1,2,3]],[[0],[1,2,3]],[[0],[1],[2,3]],[[0,1],[2,3]],[[0,1],[2],[3]],[[0],[1],[2],[3
]],[[0],[1,2],[3]],[[0,1,2],[3]]]

Cycles

uniformCycle :: (PrimMonad m, StatefulGen g m) => Int -> g -> m [(Int, Int)] Source #

Implements Sattolo's algorithm to sample a full cycle permutation uniformly over (n-1)! possibilities in O(n) time. The list implementation is a convenience wrapper around uniformCycle.

uniformCyclePartition :: (PrimMonad m, StatefulGen g m) => Int -> g -> m [(Int, Int)] Source #

Sample a cycle graph partition of [0.. n-1], uniformly over the n! possibilities. The list implementation is a convenience wrapper around uniformCyclePartition.

uniformCyclePartitionThin Source #

Arguments

:: (PrimMonad m, StatefulGen g m) 
=> Int

maximum number of draws to attempt

-> ((Int, Int) -> Bool)

edge-wise predicate, which all edges in the result must satisfy

-> Int

number of vertices, which will be labeled [0..n-1]

-> g 
-> m (Maybe [(Int, Int)]) 

Sample a cycle graph partition of [0.. n-1], uniformly over the set satisfying the conditions. The list implementation is a convenience wrapper around uniformCyclePartitionThin.