combinat-0.2.4: Generation of various combinatorial objects.

Math.Combinat.Permutations

Contents

Description

Permutations. See: Donald E. Knuth: The Art of Computer Programming, vol 4, pre-fascicle 2B.

Synopsis

Types

data Permutation Source

Standard notation for permutations. Internally it is an array of the integers [1..n].

data DisjointCycles Source

Disjoint cycle notation for permutations. Internally it is [[Int]].

toPermutationUnsafe :: [Int] -> PermutationSource

Assumes that the input is a permutation of the numbers [1..n].

isPermutation :: [Int] -> BoolSource

Checks whether the input is a permutation of the numbers [1..n].

toPermutation :: [Int] -> PermutationSource

Checks the input.

permutationSize :: Permutation -> IntSource

Returns n, where the input is a permutation of the numbers [1..n]

Disjoint cycles

permutationToDisjointCycles :: Permutation -> DisjointCyclesSource

This is compatible with Maple's convert(perm,'disjcyc').

signOfPermutation :: Num a => Permutation -> aSource

Plus 1 or minus 1.

Permutation groups

permute :: Permutation -> Array Int a -> Array Int aSource

Action of a permutation on a set. If our permutation is encoded with the sequence [p1,p2,...,pn], then in the two-line notation we have

 ( 1  2  3  ... n  )
 ( p1 p2 p3 ... pn )

We adopt the convention that permutations act on the left (as opposed to Knuth, where they act on the right). Thus,

 permute pi1 (permute pi2 set) == permute (pi1 `multiply` pi2) set

The second argument should be an array with bounds (1,n). The function checks the array bounds.

permuteList :: Permutation -> [a] -> [a]Source

The list should be of length n.

multiply :: Permutation -> Permutation -> PermutationSource

Multiplies two permutations together. See permute for our conventions.

inverse :: Permutation -> PermutationSource

The inverse permutation

Simple permutations

permutationsNaive :: Int -> [Permutation]Source

Permutations of [1..n] in lexicographic order, naive algorithm.

Random permutations

_randomPermutation :: RandomGen g => Int -> g -> ([Int], g)Source

randomPermutationDurstenfeld :: RandomGen g => Int -> g -> (Permutation, g)Source

Generates a uniformly random permutation of [1..n]. Durstenfeld's algorithm (see http://en.wikipedia.org/wiki/Knuth_shuffle).

randomCyclicPermutationSattolo :: RandomGen g => Int -> g -> (Permutation, g)Source

Generates a uniformly random cyclic permutation of [1..n]. Sattolo's algorithm (see http://en.wikipedia.org/wiki/Knuth_shuffle).

Multisets

permuteMultiset :: (Eq a, Ord a) => [a] -> [[a]]Source

Generates all permutations of a multiset. The order is lexicographic. A synonym for fasc2B_algorithm_L

countPermuteMultiset :: (Eq a, Ord a) => [a] -> IntegerSource

# = \frac { (sum_i n_i) ! } { \prod_i (n_i !) }

fasc2B_algorithm_L :: (Eq a, Ord a) => [a] -> [[a]]Source

Generates all permutations of a multiset (based on "algorithm L" in Knuth; somewhat less efficient). The order is lexicographic.