Safe Haskell | None |
---|---|
Language | Haskell2010 |
Math.Combinat.Partitions.Set
Description
Set partitions.
Synopsis
- newtype SetPartition = SetPartition [[Int]]
- _standardizeSetPartition :: [[Int]] -> [[Int]]
- fromSetPartition :: SetPartition -> [[Int]]
- toSetPartitionUnsafe :: [[Int]] -> SetPartition
- toSetPartition :: [[Int]] -> SetPartition
- _isSetPartition :: [[Int]] -> Bool
- setPartitionShape :: SetPartition -> Partition
- setPartitions :: Int -> [SetPartition]
- setPartitionsWithKParts :: Int -> Int -> [SetPartition]
- setPartitionsNaive :: Int -> [SetPartition]
- setPartitionsWithKPartsNaive :: Int -> Int -> [SetPartition]
- countSetPartitions :: Int -> Integer
- countSetPartitionsWithKParts :: Int -> Int -> Integer
The type of set partitions
newtype SetPartition Source #
A partition of the set [1..n]
(in standard order)
Constructors
SetPartition [[Int]] |
Instances
Eq SetPartition Source # | |
Defined in Math.Combinat.Partitions.Set | |
Ord SetPartition Source # | |
Defined in Math.Combinat.Partitions.Set Methods compare :: SetPartition -> SetPartition -> Ordering # (<) :: SetPartition -> SetPartition -> Bool # (<=) :: SetPartition -> SetPartition -> Bool # (>) :: SetPartition -> SetPartition -> Bool # (>=) :: SetPartition -> SetPartition -> Bool # max :: SetPartition -> SetPartition -> SetPartition # min :: SetPartition -> SetPartition -> SetPartition # | |
Read SetPartition Source # | |
Defined in Math.Combinat.Partitions.Set Methods readsPrec :: Int -> ReadS SetPartition # readList :: ReadS [SetPartition] # | |
Show SetPartition Source # | |
Defined in Math.Combinat.Partitions.Set Methods showsPrec :: Int -> SetPartition -> ShowS # show :: SetPartition -> String # showList :: [SetPartition] -> ShowS # | |
HasNumberOfParts SetPartition Source # | |
Defined in Math.Combinat.Partitions.Set Methods numberOfParts :: SetPartition -> Int Source # |
_standardizeSetPartition :: [[Int]] -> [[Int]] Source #
fromSetPartition :: SetPartition -> [[Int]] Source #
toSetPartitionUnsafe :: [[Int]] -> SetPartition Source #
toSetPartition :: [[Int]] -> SetPartition Source #
_isSetPartition :: [[Int]] -> Bool Source #
Forgetting the set structure
setPartitionShape :: SetPartition -> Partition Source #
The "shape" of a set partition is the partition we get when we forget the set structure, keeping only the cardinalities.
Generating set partitions
setPartitions :: Int -> [SetPartition] Source #
Synonym for setPartitionsNaive
setPartitionsWithKParts Source #
Arguments
:: Int |
|
-> Int |
|
-> [SetPartition] |
Synonym for setPartitionsWithKPartsNaive
sort (setPartitionsWithKParts k n) == sort [ p | p <- setPartitions n , numberOfParts p == k ]
setPartitionsNaive :: Int -> [SetPartition] Source #
List all set partitions of [1..n]
, naive algorithm
setPartitionsWithKPartsNaive Source #
Arguments
:: Int |
|
-> Int |
|
-> [SetPartition] |
Set partitions of the set [1..n]
into k
parts
countSetPartitions :: Int -> Integer Source #
Set partitions are counted by the Bell numbers