Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Count and create combinatorial objects.
Also see combinat
package.
Synopsis
- permute :: [a] -> [[a]]
- permuteFast :: [a] -> [[a]]
- permuteShare :: [a] -> [[a]]
- permuteRep :: [(a, Int)] -> [[a]]
- choose :: Int -> Int -> [[Bool]]
- variateRep :: Int -> [a] -> [[a]]
- variate :: Int -> [a] -> [[a]]
- tuples :: Int -> [a] -> [[a]]
- partitions :: [a] -> [([a], [a])]
- rectifications :: Int -> [a] -> [[a]]
- setPartitions :: Int -> [a] -> [[[a]]]
- chooseUnrank :: Integral a => a -> a -> a -> [Bool]
- chooseUnrankMaybe :: Int -> Int -> Int -> Maybe [Bool]
- chooseRank :: Integral a => [Bool] -> (a, a, a)
- factorial :: Integral a => a -> a
- binomial :: Integral a => a -> a -> a
- binomialSeq :: Integral a => a -> [a]
- binomialGen :: (Integral a, Fractional b) => b -> a -> b
- binomialSeqGen :: Fractional b => b -> [b]
- multinomial :: Integral a => [a] -> a
- factorials :: Num a => [a]
- binomials :: Num a => [[a]]
- catalanNumber :: Integer -> Integer
- catalanNumbers :: Num a => [a]
- derangementNumber :: Integer -> Integer
- derangementNumbers :: Num a => [a]
- setPartitionNumbers :: Num a => [[a]]
- surjectiveMappingNumber :: Integer -> Integer -> Integer
- surjectiveMappingNumbers :: Num a => [[a]]
- fibonacciNumber :: Integer -> Integer
- fibonacciNumbers :: [Integer]
Documentation
permute :: [a] -> [[a]] Source #
Generate list of all permutations of the input list. The list is sorted lexicographically.
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 #
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".
variate :: Int -> [a] -> [[a]] Source #
Generate all choices of n elements out of the list x without repetitions.
It holds
variate (length xs) xs == permute xs
tuples :: Int -> [a] -> [[a]] Source #
Generate all choices of n elements out of the list x respecting the order in x and without repetitions.
partitions :: [a] -> [([a], [a])] Source #
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
*Combinatorics> map (length . uncurry 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]
setPartitions :: Int -> [a] -> [[[a]]] Source #
Their number is k^n
.
chooseUnrank :: Integral a => a -> a -> a -> [Bool] Source #
chooseUnrank n k i == choose n k !! i
chooseRank :: Integral a => [Bool] -> (a, a, a) Source #
binomial :: Integral a => a -> a -> a Source #
Pascal's triangle containing the binomial coefficients.
binomialSeq :: Integral a => a -> [a] Source #
binomialGen :: (Integral a, Fractional b) => b -> a -> b Source #
binomialSeqGen :: Fractional b => b -> [b] Source #
multinomial :: Integral a => [a] -> a Source #
factorials :: Num a => [a] Source #
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.
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
derangementNumber :: Integer -> Integer Source #
derangementNumbers :: Num a => [a] Source #
Number of fix-point-free permutations with n
elements.
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.
surjectiveMappingNumber :: Integer -> Integer -> Integer Source #
surjectiveMappingNumber n k
computes the number of surjective mappings
from a n
element set to a k
element set.
surjectiveMappingNumbers :: Num a => [[a]] Source #
fibonacciNumber :: Integer -> Integer Source #
fibonacciNumbers :: [Integer] Source #
Number of possibilities to compose a 2 x n rectangle of n bricks.
||| |-- --| ||| |-- --|