Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Naive implementation of partitions of integers, encoded as list of Int
-s.
Integer partitions are nonincreasing sequences of positive integers.
This is an internal module, you are not supposed to import it directly.
Synopsis
- newtype Partition = Partition [Int]
- toList :: Partition -> [Int]
- fromList :: [Int] -> Partition
- fromListUnsafe :: [Int] -> Partition
- isEmptyPartition :: Partition -> Bool
- emptyPartition :: Partition
- partitionHeight :: Partition -> Int
- partitionWidth :: Partition -> Int
- heightWidth :: Partition -> (Int, Int)
- partitionWeight :: Partition -> Int
- dualPartition :: Partition -> Partition
- elements :: Partition -> [(Int, Int)]
- pattern Nil :: Partition
- pattern Cons :: Int -> Partition -> Partition
- pattern Partition_ :: [Int] -> Partition
- pattern Head :: Int -> Partition
- pattern Tail :: Partition -> Partition
- pattern Length :: Int -> Partition
- toExponentialForm :: Partition -> [(Int, Int)]
- fromExponentialForm :: [(Int, Int)] -> Partition
- diffSequence :: Partition -> [Int]
- unconsPartition :: Partition -> Maybe (Int, Partition)
- toDescList :: Partition -> [Int]
- dominates :: Partition -> Partition -> Bool
- isSubPartitionOf :: Partition -> Partition -> Bool
- isSuperPartitionOf :: Partition -> Partition -> Bool
- pieriRule :: Partition -> Int -> [Partition]
- dualPieriRule :: Partition -> Int -> [Partition]
Type and basic stuff
A partition of an integer. The additional invariant enforced here is that partitions
are monotone decreasing sequences of positive integers. The Ord
instance is lexicographical.
Instances
fromListUnsafe :: [Int] -> Partition Source #
isEmptyPartition :: Partition -> Bool Source #
partitionHeight :: Partition -> Int Source #
The first element of the sequence.
partitionWidth :: Partition -> Int Source #
The length of the sequence (that is, the number of parts).
partitionWeight :: Partition -> Int Source #
The weight of the partition (that is, the sum of the corresponding sequence).
dualPartition :: Partition -> Partition Source #
The dual (or conjugate) partition.
elements :: Partition -> [(Int, Int)] Source #
Example:
elements (toPartition [5,4,1]) == [ (1,1), (1,2), (1,3), (1,4), (1,5) , (2,1), (2,2), (2,3), (2,4) , (3,1) ]
Pattern synonyms
pattern Nil :: Partition Source #
Pattern sysnonyms allows us to use existing code with minimal modifications
pattern Partition_ :: [Int] -> Partition Source #
Simulated newtype constructor
Exponential form
toExponentialForm :: Partition -> [(Int, Int)] Source #
We convert a partition to exponential form.
(i,e)
mean (i^e)
; for example [(1,4),(2,3)]
corresponds to (1^4)(2^3) = [2,2,2,1,1,1,1]
. Another example:
toExponentialForm (Partition [5,5,3,2,2,2,2,1,1]) == [(1,2),(2,4),(3,1),(5,2)]
List-like operations
diffSequence :: Partition -> [Int] Source #
From a sequence [a1,a2,..,an]
computes the sequence of differences
[a1-a2,a2-a3,...,an-0]
toDescList :: Partition -> [Int] Source #
Dominance order
dominates :: Partition -> Partition -> Bool Source #
q `dominates` p
returns True
if q >= p
in the dominance order of partitions
(this is partial ordering on the set of partitions of n
).
Containment partial ordering
isSubPartitionOf :: Partition -> Partition -> Bool Source #
Returns True
of the first partition is a subpartition (that is, fit inside) of the second.
This includes equality
isSuperPartitionOf :: Partition -> Partition -> Bool Source #
This is provided for convenience/completeness only, as:
isSuperPartitionOf q p == isSubPartitionOf p q