Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Permutation functions.
Synopsis
- factorial :: Integral n => n -> n
- nk_permutations :: Integral a => a -> a -> a
- n_permutations :: Integral a => a -> a
- type Permutation = [Int]
- permutation :: Eq t => [t] -> [t] -> Permutation
- permutation_to_swaps :: Permutation -> [(Int, Int)]
- swaps_to_permutation :: [(Int, Int)] -> Permutation
- cycles_to_swaps :: [[Int]] -> [(Int, Int)]
- swaps_to_cycles :: [(Int, Int)] -> [[Int]]
- apply_permutation :: Permutation -> [t] -> [t]
- apply_permutation_c_zero_indexed :: [[Int]] -> [a] -> [a]
- p_inverse :: Permutation -> Permutation
- p_cycles :: Permutation -> [[Int]]
- non_invertible :: Permutation -> Bool
- from_cycles_zero_indexed :: [[Int]] -> Permutation
- from_cycles_one_indexed :: [[Int]] -> Permutation
- permutations_n :: Int -> [Permutation]
- p_size :: Permutation -> Int
- compose :: Permutation -> Permutation -> Permutation
- cycles_one_indexed :: Permutation -> [[Int]]
- permutation_mul :: Permutation -> Permutation -> Permutation
- two_line :: Permutation -> ([Int], [Int])
- one_line :: Permutation -> [Int]
- one_line_compact :: Permutation -> String
- multiplication_table :: Int -> [[Permutation]]
Documentation
nk_permutations :: Integral a => a -> a -> a Source #
Number of k element permutations of a set of n elements.
let f = nk_permutations in (f 3 2,f 3 3,f 4 3,f 4 4,f 13 3,f 12 12) == (6,6,24,24,1716,479001600)
n_permutations :: Integral a => a -> a Source #
Number of nk permutations where n ==
k.
map n_permutations [1..8] == [1,2,6,24,120,720,5040,40320] n_permutations 12 == 479001600 n_permutations 16 `div` 1000000 == 20922789
type Permutation = [Int] Source #
Permutation given as a zero-indexed list of destination indices.
permutation :: Eq t => [t] -> [t] -> Permutation Source #
Generate the permutation from p to q, ie. the permutation that, when applied to p, gives q.
p = permutation "abc" "bac" p == [1,0,2] apply_permutation p "abc" == "bac"
permutation_to_swaps :: Permutation -> [(Int, Int)] Source #
Permutation to list of swaps, ie. zip
[0..]
permutation_to_swaps [0,2,1,3] == [(0,0),(1,2),(2,1),(3,3)]
swaps_to_permutation :: [(Int, Int)] -> Permutation Source #
Inverse of permutation_to_swaps
, ie. map
snd
.
sort
cycles_to_swaps :: [[Int]] -> [(Int, Int)] Source #
List of cycles to list of swaps.
cycles_to_swaps [[0,2],[1],[3,4]] == [(0,2),(1,1),(2,0),(3,4),(4,3)]
apply_permutation :: Permutation -> [t] -> [t] Source #
Apply permutation f to p.
let p = permutation [1..4] [4,3,2,1] p == [3,2,1,0] apply_permutation p [1..4] == [4,3,2,1]
apply_permutation_c_zero_indexed :: [[Int]] -> [a] -> [a] Source #
Composition of apply_permutation
and from_cycles_zero_indexed
.
apply_permutation_c_zero_indexed [[0,3],[1,2]] [1..4] == [4,3,2,1] apply_permutation_c_zero_indexed [[0,2],[1],[3,4]] [1..5] == [3,2,1,5,4] apply_permutation_c_zero_indexed [[0,1,4],[2,3]] [1..5] == [2,5,4,3,1] apply_permutation_c_zero_indexed [[0,1,3],[2,4]] [1..5] == [2,4,5,1,3]
p_inverse :: Permutation -> Permutation Source #
p_cycles :: Permutation -> [[Int]] Source #
non_invertible :: Permutation -> Bool Source #
True if the inverse of p is p.
non_invertible [1,0,2] == True non_invertible [2,7,4,9,8,3,5,0,6,1] == False
let p = permutation [1..4] [4,3,2,1] non_invertible p == True && p_cycles p == [[0,3],[1,2]]
from_cycles_zero_indexed :: [[Int]] -> Permutation Source #
Generate a permutation from the cycles c (zero-indexed)
apply_permutation (from_cycles_zero_indexed [[0,1,2,3]]) [1..4] == [2,3,4,1]
from_cycles_one_indexed :: [[Int]] -> Permutation Source #
permutations_n :: Int -> [Permutation] Source #
Generate all permutations of size n (naive)
let r = [[1,2,3],[1,3,2],[2,1,3],[2,3,1],[3,1,2],[3,2,1]] map one_line (permutations_n 3) == r
p_size :: Permutation -> Int Source #
compose :: Permutation -> Permutation -> Permutation Source #
Composition of q then p.
let p = from_cycles_zero_indexed [[0,2],[1],[3,4]] let q = from_cycles_zero_indexed [[0,1,4],[2,3]] let r = p `compose` q apply_permutation r [1,2,3,4,5] == [2,4,5,1,3]
cycles_one_indexed :: Permutation -> [[Int]] Source #
One-indexed p_cycles
permutation_mul :: Permutation -> Permutation -> Permutation Source #
two_line :: Permutation -> ([Int], [Int]) Source #
Two line notation of p.
two_line (permutation [0,1,3] [1,0,3]) == ([1,2,3],[2,1,3])
one_line :: Permutation -> [Int] Source #
One line notation of p.
one_line (permutation [0,1,3] [1,0,3]) == [2,1,3]
let r = [[1,2,3],[1,3,2],[2,1,3],[2,3,1],[3,1,2],[3,2,1]] map one_line (permutations_n 3) == r
one_line_compact :: Permutation -> String Source #
Variant of one_line
that produces a compact string.
one_line_compact (permutation [0,1,3] [1,0,3]) == "213"
let p = permutations_n 3 unwords (map one_line_compact p) == "123 132 213 231 312 321"
multiplication_table :: Int -> [[Permutation]] Source #
Multiplication table of symmetric group n.
unlines (map (unwords . map one_line_compact) (multiplication_table 3))
==> 123 132 213 231 312 321 132 123 312 321 213 231 213 231 123 132 321 312 231 213 321 312 123 132 312 321 132 123 231 213 321 312 231 213 132 123