combinatorial-0.1.1: Count, enumerate, rank and unrank combinatorial objects
Safe HaskellSafe-Inferred
LanguageHaskell98

Combinatorics

Description

Count and create combinatorial objects. Also see combinat package.

Synopsis

Documentation

permute :: [a] -> [[a]] Source #

Generate list of all permutations of the input list. The list is sorted lexicographically.

>>> Comb.permute "abc"
["abc","acb","bac","bca","cab","cba"]
>>> Comb.permute "aabc"
["aabc","aacb","abac","abca","acab","acba","aabc","aacb","abac","abca","acab","acba","baac","baca","baac","baca","bcaa","bcaa","caab","caba","caab","caba","cbaa","cbaa"]
QC.forAll (take 6 <$> QC.arbitrary :: QC.Gen [Int]) $ \xs -> allEqual $ map (\p -> sort (p xs)) $ Comb.permute : Comb.permuteFast : Comb.permuteShare : []

permuteFast :: [a] -> [[a]] Source #

Generate list of all permutations of the input list. It is not lexicographically sorted. It is slightly faster and consumes less memory than the lexicographical ordering permute.

permuteShare :: [a] -> [[a]] Source #

All permutations share as much suffixes as possible. The reversed permutations are sorted lexicographically.

permuteRep :: [(a, Int)] -> [[a]] Source #

>>> Comb.permuteRep [('a',2), ('b',1), ('c',1)]
["aabc","aacb","abac","abca","acab","acba","baac","baca","bcaa","caab","caba","cbaa"]
QC.forAll (genPermuteRep  7) $ \xs -> let perms = Comb.permuteRep $ Key.nub fst xs in perms == nub perms
QC.forAll (genPermuteRep 10) $ \xs -> let perms = Comb.permuteRep $ Key.nub fst xs in List.sort perms == Set.toList (Set.fromList perms)
QC.forAll (genPermuteRep 10) $ isAscending . Comb.permuteRep . Key.nub fst . sort
QC.forAll (QC.choose (0,10)) $ \n k -> Comb.choose n k == Comb.permuteRep [(False, n-k), (True, k)]

choose :: Int -> Int -> [[Bool]] Source #

>>> map (map (\b -> if b then 'x' else '.')) $ Comb.choose 5 3
["..xxx",".x.xx",".xx.x",".xxx.","x..xx","x.x.x","x.xx.","xx..x","xx.x.","xxx.."]
>>> map (map (\b -> if b then 'x' else '.')) $ Comb.choose 3 5
[]
QC.forAll (QC.choose (0,10)) $ \n k -> all (\x  ->  n == length x  &&  k == length (filter id x)) (Comb.choose n k)

variateRep :: Int -> [a] -> [[a]] Source #

Generate all choices of n elements out of the list x with repetitions. "variation" seems to be used historically, but I like it more than "k-permutation".

>>> Comb.variateRep 2 "abc"
["aa","ab","ac","ba","bb","bc","ca","cb","cc"]

variate :: Int -> [a] -> [[a]] Source #

Generate all choices of n elements out of the list x without repetitions.

>>> Comb.variate 2 "abc"
["ab","ac","ba","bc","ca","cb"]
>>> Comb.variate 2 "abcd"
["ab","ac","ad","ba","bc","bd","ca","cb","cd","da","db","dc"]
>>> Comb.variate 3 "abcd"
["abc","abd","acb","acd","adb","adc","bac","bad","bca","bcd","bda","bdc","cab","cad","cba","cbd","cda","cdb","dab","dac","dba","dbc","dca","dcb"]
QC.forAll genVariate $ \xs -> Comb.variate (length xs) xs == Comb.permute xs
\xs -> equating (take 1000) (Comb.variate (length xs) xs) (Comb.permute (xs::String))

tuples :: Int -> [a] -> [[a]] Source #

Generate all choices of n elements out of the list x respecting the order in x and without repetitions.

>>> Comb.tuples 2 "abc"
["ab","ac","bc"]
>>> Comb.tuples 2 "abcd"
["ab","ac","ad","bc","bd","cd"]
>>> Comb.tuples 3 "abcd"
["abc","abd","acd","bcd"]

partitions :: [a] -> [([a], [a])] Source #

>>> Comb.partitions "abc"
[("abc",""),("bc","a"),("ac","b"),("c","ab"),("ab","c"),("b","ac"),("a","bc"),("","abc")]
QC.forAll genVariate $ \xs -> length (Comb.partitions xs)  ==  2 ^ length xs

rectifications :: Int -> [a] -> [[a]] Source #

Number of possibilities arising in rectification of a predicate in deductive database theory. Stefan Brass, "Logische Programmierung und deduktive Datenbanken", 2007, page 7-60 This is isomorphic to the partition of n-element sets into k non-empty subsets. http://oeis.org/A048993

>>> Comb.rectifications 4 "abc"
["aabc","abac","abbc","abca","abcb","abcc"]
>>> map (length . uncurry Comb.rectifications) $ do x<-[0..10]; y<-[0..x]; return (x,[1..y::Int])
[1,0,1,0,1,1,0,1,3,1,0,1,7,6,1,0,1,15,25,10,1,0,1,31,90,65,15,1,0,1,63,301,350,140,21,1,0,1,127,966,1701,1050,266,28,1,0,1,255,3025,7770,6951,2646,462,36,1,0,1,511,9330,34105,42525,22827,5880,750,45,1]
QC.forAll (QC.choose (0,7)) $ \k xs -> isAscending . Comb.rectifications k . nub . sort $ (xs::String)

setPartitions :: Int -> [a] -> [[[a]]] Source #

Their number is k^n.

pairPartitions :: [a] -> [[(a, a)]] Source #

All ways of separating a list of terms into pairs. All partitions are given in a canonical form, sorted lexicographically. The canonical form is: The list of pairs is ordered with respect to the first pair members, and the elements in each pair are ordered. The order is implied by the order in the input list.

http://oeis.org/A123023

chooseUnrank :: Integral a => a -> a -> a -> [Bool] Source #

chooseUnrank n k i == choose n k !! i
QC.forAll (QC.choose (0,10)) $ \n k -> map (Comb.chooseUnrank n k) [0 .. Comb.binomial n k - 1]  ==  Comb.choose n k
QC.forAll genChooseIndex $ \(n,k,i) -> Comb.chooseRank (Comb.chooseUnrank n k i)  ==  (n, k, i)
\bs -> uncurry3 Comb.chooseUnrank (Comb.chooseRank bs :: (Integer, Integer, Integer))  ==  bs

factorial :: Integral a => a -> a Source #

QC.forAll (take 8 <$> QC.arbitrary) $ \xs -> length (Comb.permute xs) == Comb.factorial (length (xs::String))
QC.forAll (take 6 <$> QC.arbitrary) $ \xs -> sum (map sum (Comb.permute xs)) == sum xs * Comb.factorial (length xs)

binomial :: Integral a => a -> a -> a Source #

Pascal's triangle containing the binomial coefficients.

QC.forAll (QC.choose (0,12)) $ \n k -> length (Comb.choose n k) == Comb.binomial n k
QC.forAll genBinomial $ \(n,k) -> let (q, r) = divMod (Comb.factorial n) (Comb.factorial k * Comb.factorial (n-k)) in r == 0 && Comb.binomial n k == q
QC.forAll (take 16 <$> QC.arbitrary) $ \xs k -> length (Comb.tuples k xs) == Comb.binomial (length (xs::String)) k

binomialSeq :: Integral a => a -> [a] Source #

binomialGen :: (Integral a, Fractional b) => b -> a -> b Source #

multinomial :: Integral a => [a] -> a Source #

QC.forAll (genPermuteRep 10) $ \xs -> length (Comb.permuteRep xs) == Comb.multinomial (map snd xs)
QC.forAll (QC.listOf $ QC.choose (0,300::Integer)) $ \xs -> Comb.multinomial xs == Comb.multinomial (sort xs)

factorials :: Num a => [a] Source #

equalFuncList Comb.factorial Comb.factorials 1000

binomials :: Num a => [[a]] Source #

Pascal's triangle containing the binomial coefficients. Only efficient if a prefix of all rows is required. It is not efficient for picking particular rows or even particular elements.

equalFuncList2 Comb.binomial Comb.binomials 100

catalanNumber :: Integer -> Integer Source #

catalanNumber n computes the number of binary trees with n nodes.

catalanNumbers :: Num a => [a] Source #

Compute the sequence of Catalan numbers by recurrence identity. It is catalanNumbers !! n == catalanNumber n

equalFuncList Comb.catalanNumber Comb.catalanNumbers 1000

derangementNumbers :: Num a => [a] Source #

Number of fix-point-free permutations with n elements.

http://oeis.org/A000166

equalFuncList Comb.derangementNumber Comb.derangementNumbers 1000

setPartitionNumbers :: Num a => [[a]] Source #

Number of partitions of an n element set into k non-empty subsets. Known as Stirling numbers http://oeis.org/A048993.

QC.forAll (QC.choose (0,10000)) $ \k -> QC.forAll (take 7 <$> QC.arbitrary) $ \xs -> length (Comb.setPartitions k xs) == (Comb.setPartitionNumbers !! length (xs::String) ++ repeat 0) !! k
QC.forAll (QC.choose (0,7)) $ \k xs -> length (Comb.rectifications k xs) == (Comb.setPartitionNumbers !! k ++ repeat 0) !! length (xs::String)

surjectiveMappingNumber :: Integer -> Integer -> Integer Source #

surjectiveMappingNumber n k computes the number of surjective mappings from a n element set to a k element set.

http://oeis.org/A019538

surjectiveMappingNumbers :: Num a => [[a]] Source #

equalFuncList2 Comb.surjectiveMappingNumber Comb.surjectiveMappingNumbers 20

fibonacciNumbers :: [Integer] Source #

Number of possibilities to compose a 2 x n rectangle of n bricks.

 |||   |--   --|
 |||   |--   --|
equalFuncList Comb.fibonacciNumber Comb.fibonacciNumbers 10000