combinat-0.2.7.2: Generate and manipulate 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

This returns True if the input is non-increasing sequence of positive integers (possibly empty); False otherwise.

height :: Partition -> Int Source

The first element of the sequence.

width :: Partition -> Int Source

The length of the sequence (that is, the number of parts).

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.

data Pair Source

Constructors

Pair !Int !Int 

_dualPartitionNaive :: [Int] -> [Int] Source

A simpler, but bit slower (about twice?) implementation of dual partition

diffSequence :: [Int] -> [Int] Source

From a sequence [a1,a2,..,an] computes the sequence of differences [a1-a2,a2-a3,...,an-0]

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

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

Automorphisms

countAutomorphisms :: Partition -> Integer Source

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

Generating partitions

partitions :: Int -> [Partition] Source

Partitions of d.

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

Partitions of d, as lists

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)

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

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

allPartitions' Source

Arguments

:: (Int, Int)

(height,width)

-> [Partition] 

All integer partitions fitting into a given rectangle.

allPartitionsGrouped' Source

Arguments

:: (Int, Int)

(height,width)

-> [[Partition]] 

All integer partitions fitting into a given rectangle, grouped by weight.

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

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

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

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

dominatedPartitions :: Partition -> [Partition] Source

Lists all partitions of the same weight as lambda and also dominated by lambda (that is, all partial sums are less or equal):

dominatedPartitions lam == [ mu | mu <- partitions (weight lam), lam `dominates` mu ]

dominatingPartitions :: Partition -> [Partition] Source

Lists all partitions of the sime weight as mu and also dominating mu (that is, all partial sums are greater or equal):

dominatingPartitions mu == [ lam | lam <- partitions (weight mu), lam `dominates` mu ]

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 

Partitions with only odd/distinct parts

partitionsWithOddParts :: Int -> [Partition] Source

Partitions of n with only odd parts

partitionsWithDistinctParts :: Int -> [Partition] Source

Partitions of n with distinct parts.

Note:

length (partitionsWithDistinctParts d) == length (partitionsWithOddParts d)

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

The Pieri rule

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

The Pieri rule computes s[lambda]*h[n] as a sum of s[mu]-s (each with coefficient 1).

See for example http://en.wikipedia.org/wiki/Pieri's_formula

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

The dual Pieri rule computes s[lambda]*e[n] as a sum of s[mu]-s (each with coefficient 1)

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)