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

Math.Combinat.Partitions.Integer.IntList

Description

Partition functions working on lists of integers.

It's not recommended to use this module directly.

Synopsis

Type and basic stuff

_mkPartition :: [Int] -> [Int] Source #

Sorts the input, and cuts the nonpositive elements.

_isPartition :: [Int] -> Bool Source #

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

_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 :: [Int] -> [(Int, Int)] Source #

Example:

_elements [5,4,1] ==
  [ (1,1), (1,2), (1,3), (1,4), (1,5)
  , (2,1), (2,2), (2,3), (2,4)
  , (3,1)
  ]

Exponential form

_toExponentialForm :: [Int] -> [(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)]

Generating partitions

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

Partitions of d, as lists

_allPartitions :: Int -> [[Int]] Source #

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

_allPartitionsGrouped :: Int -> [[[Int]]] 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

_partitions' Source #

Arguments

:: (Int, Int)

(height,width)

-> Int

d

-> [[Int]] 

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

Random partitions

_randomPartition :: RandomGen g => Int -> g -> ([Int], 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 partitionCountList 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 
-> ([[Int]], g) 

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

Dominance order

_dominates :: [Int] -> [Int] -> 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 :: [Int] -> [[Int]] 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 :: [Int] -> [[Int]] 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

-> [[Int]] 

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 -> [[Int]] Source #

Partitions of n with only odd parts

_partitionsWithDistinctParts :: Int -> [[Int]] Source #

Partitions of n with distinct parts.

Note:

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

Sub- and super-partitions of a given partition

_isSubPartitionOf :: [Int] -> [Int] -> Bool Source #

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

_isSuperPartitionOf :: [Int] -> [Int] -> Bool Source #

This is provided for convenience/completeness only, as:

isSuperPartitionOf q p == isSubPartitionOf p q

_subPartitions :: Int -> [Int] -> [[Int]] Source #

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

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

_allSubPartitions :: [Int] -> [[Int]] Source #

All sub-partitions of a given partition

_superPartitions :: Int -> [Int] -> [[Int]] Source #

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

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

The Pieri rule

_pieriRule :: [Int] -> Int -> [[Int]] 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

| We assume here that lambda is a partition (non-increasing sequence of positive integers)!

_dualPieriRule :: [Int] -> Int -> [[Int]] Source #

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