Permutations. See: Donald E. Knuth: The Art of Computer Programming, vol 4, pre-fascicle 2B.
- data Permutation
- data DisjointCycles
- fromPermutation :: Permutation -> [Int]
- permutationArray :: Permutation -> Array Int Int
- toPermutationUnsafe :: [Int] -> Permutation
- isPermutation :: [Int] -> Bool
- toPermutation :: [Int] -> Permutation
- permutationSize :: Permutation -> Int
- fromDisjointCycles :: DisjointCycles -> [[Int]]
- disjointCyclesUnsafe :: [[Int]] -> DisjointCycles
- permutationToDisjointCycles :: Permutation -> DisjointCycles
- disjointCyclesToPermutation :: Int -> DisjointCycles -> Permutation
- isEvenPermutation :: Permutation -> Bool
- isOddPermutation :: Permutation -> Bool
- signOfPermutation :: Num a => Permutation -> a
- isCyclicPermutation :: Permutation -> Bool
- permute :: Permutation -> Array Int a -> Array Int a
- permuteList :: Permutation -> [a] -> [a]
- multiply :: Permutation -> Permutation -> Permutation
- inverse :: Permutation -> Permutation
- permutations :: Int -> [Permutation]
- _permutations :: Int -> [[Int]]
- permutationsNaive :: Int -> [Permutation]
- _permutationsNaive :: Int -> [[Int]]
- countPermutations :: Int -> Integer
- randomPermutation :: RandomGen g => Int -> g -> (Permutation, g)
- _randomPermutation :: RandomGen g => Int -> g -> ([Int], g)
- randomCyclicPermutation :: RandomGen g => Int -> g -> (Permutation, g)
- _randomCyclicPermutation :: RandomGen g => Int -> g -> ([Int], g)
- randomPermutationDurstenfeld :: RandomGen g => Int -> g -> (Permutation, g)
- randomCyclicPermutationSattolo :: RandomGen g => Int -> g -> (Permutation, g)
- permuteMultiset :: (Eq a, Ord a) => [a] -> [[a]]
- countPermuteMultiset :: (Eq a, Ord a) => [a] -> Integer
- fasc2B_algorithm_L :: (Eq a, Ord a) => [a] -> [[a]]
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]]
.
fromPermutation :: Permutation -> [Int]Source
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
fromDisjointCycles :: DisjointCycles -> [[Int]]Source
disjointCyclesUnsafe :: [[Int]] -> DisjointCyclesSource
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
permutations :: Int -> [Permutation]Source
A synonym for permutationsNaive
_permutations :: Int -> [[Int]]Source
permutationsNaive :: Int -> [Permutation]Source
Permutations of [1..n]
in lexicographic order, naive algorithm.
_permutationsNaive :: Int -> [[Int]]Source
countPermutations :: Int -> IntegerSource
# = n!
Random permutations
randomPermutation :: RandomGen g => Int -> g -> (Permutation, g)Source
A synonym for randomPermutationDurstenfeld
.
_randomPermutation :: RandomGen g => Int -> g -> ([Int], g)Source
randomCyclicPermutation :: RandomGen g => Int -> g -> (Permutation, g)Source
A synonym for randomCyclicPermutationSattolo
.
_randomCyclicPermutation :: 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.