Safe Haskell | None |
---|---|
Language | Haskell2010 |
Permutations.
See eg.: Donald E. Knuth: The Art of Computer Programming, vol 4, pre-fascicle 2B.
WARNING: As of version 0.2.8.0, I changed the convention of how permutations are represented internally. Also now they act on the right by default!
Synopsis
- newtype Permutation = Permutation (UArray Int Int)
- fromPermutation :: Permutation -> [Int]
- permutationArray :: Permutation -> Array Int Int
- permutationUArray :: Permutation -> UArray Int Int
- uarrayToPermutationUnsafe :: UArray Int Int -> Permutation
- isPermutation :: [Int] -> Bool
- maybePermutation :: [Int] -> Maybe Permutation
- toPermutation :: [Int] -> Permutation
- toPermutationUnsafe :: [Int] -> Permutation
- permutationSize :: Permutation -> Int
- newtype DisjointCycles = DisjointCycles [[Int]]
- fromDisjointCycles :: DisjointCycles -> [[Int]]
- disjointCyclesUnsafe :: [[Int]] -> DisjointCycles
- permutationToDisjointCycles :: Permutation -> DisjointCycles
- disjointCyclesToPermutation :: Int -> DisjointCycles -> Permutation
- numberOfCycles :: HasNumberOfCycles p => p -> Int
- concatPermutations :: Permutation -> Permutation -> Permutation
- isIdentityPermutation :: Permutation -> Bool
- isReversePermutation :: Permutation -> Bool
- isEvenPermutation :: Permutation -> Bool
- isOddPermutation :: Permutation -> Bool
- signOfPermutation :: Permutation -> Sign
- signValueOfPermutation :: Num a => Permutation -> a
- module Math.Combinat.Sign
- isCyclicPermutation :: Permutation -> Bool
- transposition :: Int -> (Int, Int) -> Permutation
- transpositions :: Int -> [(Int, Int)] -> Permutation
- adjacentTransposition :: Int -> Int -> Permutation
- adjacentTranspositions :: Int -> [Int] -> Permutation
- cycleLeft :: Int -> Permutation
- cycleRight :: Int -> Permutation
- reversePermutation :: Int -> Permutation
- inversions :: Permutation -> [(Int, Int)]
- numberOfInversions :: Permutation -> Int
- numberOfInversionsNaive :: Permutation -> Int
- numberOfInversionsMerge :: Permutation -> Int
- bubbleSort2 :: Permutation -> [(Int, Int)]
- bubbleSort :: Permutation -> [Int]
- identity :: Int -> Permutation
- inverse :: Permutation -> Permutation
- multiply :: Permutation -> Permutation -> Permutation
- multiplyMany :: [Permutation] -> Permutation
- multiplyMany' :: Int -> [Permutation] -> Permutation
- permute :: IArray arr b => Permutation -> arr Int b -> arr Int b
- permuteList :: Permutation -> [a] -> [a]
- permuteLeft :: IArray arr b => Permutation -> arr Int b -> arr Int b
- permuteRight :: IArray arr b => Permutation -> arr Int b -> arr Int b
- permuteLeftList :: forall a. Permutation -> [a] -> [a]
- permuteRightList :: forall a. Permutation -> [a] -> [a]
- sortingPermutationAsc :: Ord a => [a] -> Permutation
- sortingPermutationDesc :: Ord a => [a] -> Permutation
- asciiPermutation :: Permutation -> ASCII
- asciiDisjointCycles :: DisjointCycles -> ASCII
- twoLineNotation :: Permutation -> ASCII
- inverseTwoLineNotation :: Permutation -> ASCII
- genericTwoLineNotation :: [(Int, Int)] -> ASCII
- 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]]
The Permutation type
newtype Permutation Source #
A permutation. Internally it is an (unboxed) array of the integers [1..n]
, with
indexing range also being (1,n)
.
If this array of integers is [p1,p2,...,pn]
, then in two-line
notations, that represents the permutation
( 1 2 3 ... n ) ( p1 p2 p3 ... pn )
That is, it is the permutation sigma
whose (right) action on the set [1..n]
is
sigma(1) = p1 sigma(2) = p2 ...
(NOTE: this changed at version 0.2.8.0!)
Instances
fromPermutation :: Permutation -> [Int] Source #
permutationArray :: Permutation -> Array Int Int Source #
Note: this is slower than permutationUArray
permutationUArray :: Permutation -> UArray Int Int Source #
uarrayToPermutationUnsafe :: UArray Int Int -> Permutation Source #
Note: Indexing starts from 1.
isPermutation :: [Int] -> Bool Source #
Checks whether the input is a permutation of the numbers [1..n]
.
maybePermutation :: [Int] -> Maybe Permutation Source #
Checks whether the input is a permutation of the numbers [1..n]
.
toPermutation :: [Int] -> Permutation Source #
Checks the input.
toPermutationUnsafe :: [Int] -> Permutation Source #
Assumes that the input is a permutation of the numbers [1..n]
.
permutationSize :: Permutation -> Int Source #
Returns n
, where the input is a permutation of the numbers [1..n]
Disjoint cycles
newtype DisjointCycles Source #
Disjoint cycle notation for permutations. Internally it is [[Int]]
.
The cycles are to be understood as follows: a cycle [c1,c2,...,ck]
means
the permutation
( c1 c2 c3 ... ck ) ( c2 c3 c4 ... c1 )
DisjointCycles [[Int]] |
Instances
fromDisjointCycles :: DisjointCycles -> [[Int]] Source #
disjointCyclesUnsafe :: [[Int]] -> DisjointCycles Source #
permutationToDisjointCycles :: Permutation -> DisjointCycles Source #
Convert to disjoint cycle notation.
This is compatible with Maple's convert(perm,'disjcyc')
and also with Mathematica's PermutationCycles[perm]
Note however, that for example Mathematica uses the top row to represent a permutation, while we use the bottom row - thus even though this function looks identical, the meaning of both the input and output is different!
numberOfCycles :: HasNumberOfCycles p => p -> Int Source #
concatPermutations :: Permutation -> Permutation -> Permutation Source #
Given a permutation of n
and a permutation of m
, we return
a permutation of n+m
resulting by putting them next to each other.
This should satisfy
permuteList p1 xs ++ permuteList p2 ys == permuteList (concatPermutations p1 p2) (xs++ys)
Queries
isIdentityPermutation :: Permutation -> Bool Source #
Checks whether the permutation is the identity permutation
isReversePermutation :: Permutation -> Bool Source #
Checks whether the permutation is the reverse permutation @[n,n-1,n-2,...,2,1].
isEvenPermutation :: Permutation -> Bool Source #
isOddPermutation :: Permutation -> Bool Source #
signOfPermutation :: Permutation -> Sign Source #
signValueOfPermutation :: Num a => Permutation -> a Source #
Plus 1 or minus 1.
module Math.Combinat.Sign
Some concrete permutations
transposition :: Int -> (Int, Int) -> Permutation Source #
A transposition (swapping two elements).
transposition n (i,j)
is the permutation of size n
which swaps i
'th and j
'th elements.
transpositions :: Int -> [(Int, Int)] -> Permutation Source #
Product of transpositions.
transpositions n list == multiplyMany [ transposition n pair | pair <- list ]
adjacentTransposition :: Int -> Int -> Permutation Source #
adjacentTransposition n k
swaps the elements k
and (k+1)
.
adjacentTranspositions :: Int -> [Int] -> Permutation Source #
Product of adjacent transpositions.
adjacentTranspositions n list == multiplyMany [ adjacentTransposition n idx | idx <- list ]
cycleLeft :: Int -> Permutation Source #
The permutation which cycles a list left by one step:
permuteList (cycleLeft 5) "abcde" == "bcdea"
Or in two-line notation:
( 1 2 3 4 5 ) ( 2 3 4 5 1 )
cycleRight :: Int -> Permutation Source #
The permutation which cycles a list right by one step:
permuteList (cycleRight 5) "abcde" == "eabcd"
Or in two-line notation:
( 1 2 3 4 5 ) ( 5 1 2 3 4 )
reversePermutation :: Int -> Permutation Source #
The permutation [n,n-1,n-2,...,2,1]
. Note that it is the inverse of itself.
Inversions
inversions :: Permutation -> [(Int, Int)] Source #
An inversion of a permutation sigma
is a pair (i,j)
such that
i<j
and sigma(i) > sigma(j)
.
This functions returns the inversion of a permutation.
numberOfInversions :: Permutation -> Int Source #
Returns the number of inversions:
numberOfInversions perm = length (inversions perm)
Synonym for numberOfInversionsMerge
numberOfInversionsNaive :: Permutation -> Int Source #
Returns the number of inversions, using the definition, thus it's O(n^2)
.
numberOfInversionsMerge :: Permutation -> Int Source #
Returns the number of inversions, using the merge-sort algorithm.
This should be O(n*log(n))
bubbleSort2 :: Permutation -> [(Int, Int)] Source #
Bubble sorts breaks a permutation into the product of adjacent transpositions:
multiplyMany' n (map (transposition n) $ bubbleSort2 perm) == perm
Note that while this is not unique, the number of transpositions equals the number of inversions.
bubbleSort :: Permutation -> [Int] Source #
Another version of bubble sort. An entry i
in the return sequence means
the transposition (i,i+1)
:
multiplyMany' n (map (adjacentTransposition n) $ bubbleSort perm) == perm
Permutation groups
identity :: Int -> Permutation Source #
The identity (or trivial) permutation.
inverse :: Permutation -> Permutation Source #
The inverse permutation.
multiply :: Permutation -> Permutation -> Permutation infixr 7 Source #
multiplyMany :: [Permutation] -> Permutation Source #
Multiply together a non-empty list of permutations (the reason for requiring the list to
be non-empty is that we don't know the size of the result). See also multiplyMany'
.
multiplyMany' :: Int -> [Permutation] -> Permutation Source #
Multiply together a (possibly empty) list of permutations, all of which has size n
Action of the permutation group
permute :: IArray arr b => Permutation -> arr Int b -> arr Int b Source #
Right 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 right (as in Knuth):
permute pi2 (permute pi1 set) == permute (pi1 `multiply` pi2) set
Synonym to permuteRight
permuteList :: Permutation -> [a] -> [a] Source #
Right action on lists. Synonym to permuteListRight
permuteLeft :: IArray arr b => Permutation -> arr Int b -> arr Int b Source #
The left (opposite) action of the permutation group.
permuteLeft pi2 (permuteLeft pi1 set) == permuteLeft (pi2 `multiply` pi1) set
It is related to permuteLeft
via:
permuteLeft pi arr == permuteRight (inverse pi) arr permuteRight pi arr == permuteLeft (inverse pi) arr
permuteRight :: IArray arr b => Permutation -> arr Int b -> arr Int b Source #
The right (standard) action of permutations on sets.
permuteRight pi2 (permuteRight pi1 set) == permuteRight (pi1 `multiply` pi2) set
The second argument should be an array with bounds (1,n)
.
The function checks the array bounds.
permuteLeftList :: forall a. Permutation -> [a] -> [a] Source #
The left (opposite) action on a list. The list should be of length n
.
permuteLeftList perm set == permuteList (inverse perm) set fromPermutation (inverse perm) == permuteLeftList perm [1..n]
permuteRightList :: forall a. Permutation -> [a] -> [a] Source #
The right (standard) action on a list. The list should be of length n
.
fromPermutation perm == permuteRightList perm [1..n]
Sorting
sortingPermutationAsc :: Ord a => [a] -> Permutation Source #
Given a list of things, we return a permutation which sorts them into ascending order, that is:
permuteList (sortingPermutationAsc xs) xs == sort xs
Note: if the things are not unique, then the sorting permutations is not unique either; we just return one of them.
sortingPermutationDesc :: Ord a => [a] -> Permutation Source #
Given a list of things, we return a permutation which sorts them into descending order, that is:
permuteList (sortingPermutationDesc xs) xs == reverse (sort xs)
Note: if the things are not unique, then the sorting permutations is not unique either; we just return one of them.
ASCII drawing
asciiPermutation :: Permutation -> ASCII Source #
Synonym for twoLineNotation
twoLineNotation :: Permutation -> ASCII Source #
The standard two-line notation, moving the element indexed by the top row into the place indexed by the corresponding element in the bottom row.
inverseTwoLineNotation :: Permutation -> ASCII Source #
The inverse two-line notation, where the it's the bottom line
which is in standard order. The columns of this are a permutation
of the columns twoLineNotation
.
Remark: the top row of inverseTwoLineNotation perm
is the same
as the bottom row of twoLineNotation (inverse perm)
.
List of permutations
permutations :: Int -> [Permutation] Source #
A synonym for permutationsNaive
_permutations :: Int -> [[Int]] Source #
permutationsNaive :: Int -> [Permutation] Source #
All permutations of [1..n]
in lexicographic order, naive algorithm.
_permutationsNaive :: Int -> [[Int]] Source #
countPermutations :: Int -> Integer Source #
# = n!
Random permutations
randomPermutation :: RandomGen g => Int -> g -> (Permutation, g) Source #
A synonym for randomPermutationDurstenfeld
.
randomCyclicPermutation :: RandomGen g => Int -> g -> (Permutation, g) Source #
A synonym for randomCyclicPermutationSattolo
.
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] -> Integer Source #
# = \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.