combinat-0.2.7.0: Generation of various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Partitions.Integer

Contents

Description

Partitions of integers. Integer partitions are nonincreasing sequences of positive integers.

See:

For example the partition

Partition [8,6,3,3,1]

can be represented by the (English notation) Ferrers diagram:

Synopsis

Type and basic stuff

newtype Partition Source

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.

Constructors

Partition [Int] 

mkPartition :: [Int] -> Partition Source

Sorts the input, and cuts the nonpositive elements.

toPartitionUnsafe :: [Int] -> Partition Source

Assumes that the input is decreasing.

toPartition :: [Int] -> Partition Source

Checks whether the input is an integer partition. See the note at isPartition!

isPartition :: [Int] -> Bool Source

Note: we only check that the sequence is ordered, but we do not check for negative elements. This can be useful when working with symmetric functions. It may also change in the future...

height :: Partition -> Int Source

The first element of the sequence.

width :: Partition -> Int Source

The length of the sequence.

weight :: 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)
  ]

_elements :: [Int] -> [(Int, Int)] Source

Automorphisms

countAutomorphisms :: Partition -> Integer Source

Computes the number of "automorphisms" of a given integer partition.

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).

See http://en.wikipedia.org/wiki/Dominance_order

Generating partitions

_partitions' Source

Arguments

:: (Int, Int)

(height,width)

-> Int

d

-> [[Int]] 

Integer partitions of d, fitting into a given rectangle, as lists.

partitions' Source

Arguments

:: (Int, Int)

(height,width)

-> Int

d

-> [Partition] 

Partitions of d, fitting into a given rectangle. The order is again lexicographic.

_partitions :: Int -> [[Int]] Source

Partitions of d, as lists

partitions :: Int -> [Partition] Source

Partitions of d.

allPartitions' Source

Arguments

:: (Int, Int)

(height,width)

-> [[Partition]] 

All integer partitions fitting into a given rectangle.

allPartitions :: Int -> [[Partition]] Source

All integer partitions up to a given degree (that is, all integer partitions whose sum is less or equal to d)

countAllPartitions' :: (Int, Int) -> Integer Source

# = \binom { h+w } { h }

Partitions with given number of parts

partitionsWithKParts Source

Arguments

:: Int

k = number of parts

-> Int

n = the integer we partition

-> [Partition] 

Lists partitions of n into k parts.

sort (partitionsWithKParts k n) == sort [ p | p <- partitions n , numberOfParts p == k ]

Naive recursive algorithm.

countPartitionsWithKParts Source

Arguments

:: Int

k = number of parts

-> Int

n = the integer we partition

-> Integer 

Sub-partitions of a given partition

isSubPartitionOf :: Partition -> Partition -> Bool Source

Returns True of the first partition is a subpartition (that is, fit inside) of the second. This includes equality

subPartitions :: Int -> Partition -> [Partition] Source

Sub-partitions of a given partition with the given weight:

sort (subPartitions d q) == sort [ p | p <- partitions d, isSubPartitionOf p q ]

allSubPartitions :: Partition -> [Partition] Source

All sub-partitions of a given partition

ASCII Ferrers diagrams

data PartitionConvention Source

Which orientation to draw the Ferrers diagrams. For example, the partition [5,4,1] corrsponds to:

In standard English notation:

 @@@@@
 @@@@
 @

In English notation rotated by 90 degrees counter-clockwise:

@  
@@
@@
@@
@@@

And in French notation:

 @
 @@@@
 @@@@@

Constructors

EnglishNotation

English notation

EnglishNotationCCW

English notation rotated by 90 degrees counterclockwise

FrenchNotation

French notation (mirror of English notation to the x axis)

asciiFerrersDiagram :: Partition -> ASCII Source

Synonym for asciiFerrersDiagram' EnglishNotation '@'

Try for example:

autoTabulate RowMajor (Right 8) (map asciiFerrersDiagram $ partitions 9)