combinat-0.2.10.0: Generate and manipulate various combinatorial objects.
Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Partitions.Integer

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

Documentation

Types and basic stuff

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

Instances

Instances details
Eq Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Ord Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Read Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Show Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

HasDuality Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

HasWeight Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Methods

weight :: Partition -> Int Source #

HasHeight Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Methods

height :: Partition -> Int Source #

HasWidth Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

Methods

width :: Partition -> Int Source #

HasNumberOfParts Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

CanBeEmpty Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer.Naive

DrawASCII Partition Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer

HasShape (Tableau a) Partition Source # 
Instance details

Defined in Math.Combinat.Tableaux

Methods

shape :: Tableau a -> Partition Source #

Conversion to/from lists

mkPartition :: [Int] -> Partition Source #

Sorts the input, and cuts the nonpositive elements.

toPartition :: [Int] -> Partition Source #

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

toPartitionUnsafe :: [Int] -> Partition Source #

Assumes that the input is decreasing.

isPartition :: [Int] -> Bool Source #

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

Conversion to/from exponent vectors

toExponentVector :: Partition -> [Int] Source #

Converts a partition to an exponent vector.

For example,

toExponentVector (Partition [4,4,2,2,2,1]) == [1,3,0,2]

meaning (1^1,2^3,3^0,4^2).

Union and sum

unionOfPartitions :: Partition -> Partition -> Partition Source #

This is simply the union of parts. For example

Partition [4,2,1] `unionOfPartitions` Partition [4,3,1] == Partition [4,4,3,2,1,1]

Note: This is the dual of pointwise sum, sumOfPartitions

sumOfPartitions :: Partition -> Partition -> Partition Source #

Pointwise sum of the parts. For example:

Partition [3,2,1,1] `sumOfPartitions` Partition [4,3,1] == Partition [7,5,2,1]

Note: This is the dual of unionOfPartitions

Generating partitions

partitions :: Int -> [Partition] Source #

Partitions of d.

partitions' Source #

Arguments

:: (Int, Int)

(height,width)

-> Int

d

-> [Partition] 

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

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.

Counting partitions

countPartitions :: Int -> Integer Source #

Number of partitions of n (looking up a table built using Euler's algorithm)

countPartitions' :: (Int, Int) -> Int -> Integer Source #

Number of of d, fitting into a given rectangle. Naive recursive algorithm.

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

Count all partitions fitting into a rectangle. # = \binom { h+w } { h }

countPartitionsWithKParts Source #

Arguments

:: Int

k = number of parts

-> Int

n = the integer we partition

-> Integer 

Count partitions of n into k parts.

Naive recursive algorithm.

Random partitions

randomPartition :: RandomGen g => Int -> g -> (Partition, g) Source #

Uniformly random partition of the given weight.

NOTE: This algorithm is effective for small n-s (say n up to a few hundred / one thousand it should work nicely), and the first time it is executed may be slower (as it needs to build the table of partitions counts first)

Algorithm of Nijenhuis and Wilf (1975); see

  • Knuth Vol 4A, pre-fascicle 3B, exercise 47;
  • Nijenhuis and Wilf: Combinatorial Algorithms for Computers and Calculators, chapter 10

randomPartitions Source #

Arguments

:: forall g. RandomGen g 
=> Int

number of partitions to generate

-> Int

the weight of the partitions

-> g 
-> ([Partition], g) 

Generates several uniformly random partitions of n at the same time. Should be a little bit faster then generating them individually.

Dominating / dominated partitions

dominanceCompare :: Partition -> Partition -> Maybe Ordering Source #

Dominance partial ordering as a partial ordering.

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 ]

Conjugate lexicographic ordering

newtype ConjLex Source #

Constructors

ConjLex Partition 

Instances

Instances details
Eq ConjLex Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer

Methods

(==) :: ConjLex -> ConjLex -> Bool #

(/=) :: ConjLex -> ConjLex -> Bool #

Ord ConjLex Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer

Show ConjLex Source # 
Instance details

Defined in Math.Combinat.Partitions.Integer

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.

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- and super-partitions of a given partition

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

superPartitions :: Int -> Partition -> [Partition] Source #

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

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

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)

Orphan instances

DrawASCII Partition Source # 
Instance details