multiset-comb-0.2.2: Combinatorial algorithms over multisets

Math.Combinatorics.Multiset

Contents

Description

Efficient combinatorial algorithms over multisets, including generating all permutations, partitions, subsets, cycles, and other combinatorial structures based on multisets. Note that an Eq or Ord instance on the elements is not required; the algorithms are careful to keep track of which things are (by construction) equal to which other things, so equality testing is not needed.

Synopsis

The Multiset type

newtype Multiset a Source

A multiset is represented as a list of (element, count) pairs. We maintain the invariants that the counts are always positive, and no element ever appears more than once.

Constructors

MS 

Fields

toCounts :: [(a, Count)]
 

Instances

emptyMS :: Multiset aSource

A multiset with no values in it.

singletonMS :: a -> Multiset aSource

Create a multiset with only a single value in it.

consMS :: (a, Count) -> Multiset a -> Multiset aSource

Add an element with multiplicity to a multiset. Precondition: the new element is distinct from all elements already in the multiset.

(+:) :: (a, Count) -> Multiset a -> Multiset aSource

A convenient shorthand for consMS.

Conversions

toList :: Multiset a -> [a]Source

Convert a multiset to a list.

fromList :: Ord a => [a] -> Multiset aSource

Efficiently convert a list to a multiset, given an Ord instance for the elements. This method is provided just for convenience. you can also use fromListEq with only an Eq instance, or construct Multisets directly using fromCounts.

fromListEq :: Eq a => [a] -> Multiset aSource

Convert a list to a multiset, given an Eq instance for the elements.

fromDistinctList :: [a] -> Multiset aSource

Make a multiset with one copy of each element from a list of distinct elements.

fromCounts :: [(a, Count)] -> Multiset aSource

Construct a Multiset from a list of (element, count) pairs. Precondition: the counts must all be positive, and there must not be any duplicate elements.

getCounts :: Multiset a -> [Count]Source

Extract just the element counts from a multiset, forgetting the elements.

size :: Multiset a -> IntSource

Compute the total size of a multiset.

Operations

disjUnion :: Multiset a -> Multiset a -> Multiset aSource

Form the disjoint union of two multisets; i.e. we assume the two multisets share no elements in common.

disjUnions :: [Multiset a] -> Multiset aSource

Form the disjoint union of a collection of multisets. We assume that the multisets all have distinct elements.

Permutations

permutations :: Multiset a -> [[a]]Source

List all the distinct permutations of the elements of a multiset.

For example, permutations (fromList "abb") == ["abb","bba","bab"], whereas Data.List.permutations "abb" == ["abb","bab","bba","bba","bab","abb"]. This function is equivalent to, but much more efficient than, nub . Data.List.permutations, and even works when the elements have no Eq instance.

Note that this is a specialized version of permutationsRLE, where each run has been expanded via replicate.

permutationsRLE :: Multiset a -> [[(a, Count)]]Source

List all the distinct permutations of the elements of a multiset, with each permutation run-length encoded. (Note that the run-length encoding is a natural byproduct of the algorithm used, not a separate postprocessing step.)

For example, permutationsRLE [(a,1), (b,2)] == [[(a,1),(b,2)],[(b,2),(a,1)],[(b,1),(a,1),(b,1)]].

(Note that although the output type is newtype-equivalent to [Multiset a], we don't call it that since the output may violate the Multiset invariant that no element should appear more than once. And indeed, morally this function does not output multisets at all.)

Partitions

type Vec = [Count]Source

Element count vector.

vPartitions :: Vec -> [Multiset Vec]Source

Generate all vector partitions, representing each partition as a multiset of vectors.

This code is a slight generalization of the code published in

Brent Yorgey. "Generating Multiset Partitions". In: The Monad.Reader, Issue 8, September 2007. http://www.haskell.org/sitewiki/images/d/dd/TMR-Issue8.pdf

See that article for a detailed discussion of the code and how it works.

partitions :: Multiset a -> [Multiset (Multiset a)]Source

Efficiently generate all distinct multiset partitions. Note that each partition is represented as a multiset of parts (each of which is a multiset) in order to properly reflect the fact that some parts may occur multiple times.

Submultisets

splits :: Multiset a -> [(Multiset a, Multiset a)]Source

Generate all splittings of a multiset into two submultisets, i.e. all size-two partitions.

kSubsets :: Count -> Multiset a -> [Multiset a]Source

Generate all size-k submultisets.

Cycles

cycles :: Multiset a -> [[a]]Source

Generate all distinct cycles, aka necklaces, with elements taken from a multiset. See J. Sawada, "A fast algorithm to generate necklaces with fixed content", J. Theor. Comput. Sci. 301 (2003) pp. 477-489.

Given the ordering on the elements of the multiset based on their position in the multiset representation (with "smaller" elements first), in map reverse (cycles m), each generated cycle is lexicographically smallest among all its cyclic shifts, and furthermore, the cycles occur in reverse lexicographic order. (It's simply more convenient/efficient to generate the cycles reversed in this way, and of course we get the same set of cycles either way.)

For example, cycles (fromList "aabbc") == ["cabba","bcaba","cbaba","bbcaa","bcbaa","cbbaa"].

Miscellaneous

sequenceMS :: Multiset [a] -> [Multiset a]Source

Take a multiset of lists, and select one element from each list in every possible combination to form a list of multisets. We assume that all the list elements are distinct.