combinat-0.2.8.1: Generate and manipulate various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Tableaux.LittlewoodRichardson

Description

The Littlewood-Richardson rule

Synopsis

Documentation

lrCoeff :: Partition -> (Partition, Partition) -> Int Source

lrCoeff lam (mu,nu) computes the coressponding Littlewood-Richardson coefficients. This is also the coefficient of s[lambda] in the product s[mu]*s[nu]

Note: This is much slower than using lrRule or lrMult to compute several coefficients at the same time!

lrCoeff' :: SkewPartition -> Partition -> Int Source

lrCoeff (lam/nu) mu computes the coressponding Littlewood-Richardson coefficients. This is also the coefficient of s[mu] in the product s[lam/nu]

Note: This is much slower than using lrRule or lrMult to compute several coefficients at the same time!

lrMult :: Partition -> Partition -> Map Partition Int Source

Computes the expansion of the product of Schur polynomials s[mu]*s[nu] using the Littlewood-Richardson rule. Note: this is symmetric in the two arguments.

Based on the wikipedia article https://en.wikipedia.org/wiki/Littlewood-Richardson_rule

lrMult mu nu == Map.fromList list where
  lamw = weight nu + weight mu
  list = [ (lambda, coeff) 
         | lambda <- partitions lamw 
         , let coeff = lrCoeff lambda (mu,nu)
         , coeff /= 0
         ] 

lrRule :: SkewPartition -> Map Partition Int Source

lrRule computes the expansion of a skew Schur function s[lambda/mu] via the Littlewood-Richardson rule.

Adapted from John Stembridge's Maple code: http://www.math.lsa.umich.edu/~jrs/software/SFexamples/LR_rule

lrRule (mkSkewPartition (lambda,nu)) == Map.fromList list where
  muw  = weight lambda - weight nu
  list = [ (mu, coeff) 
         | mu <- partitions muw 
         , let coeff = lrCoeff lambda (mu,nu)
         , coeff /= 0
         ] 

_lrRule :: Partition -> Partition -> Map Partition Int Source

_lrRule lambda mu computes the expansion of the skew Schur function s[lambda/mu] via the Littlewood-Richardson rule.

lrRuleNaive :: SkewPartition -> Map Partition Int Source

Naive (very slow) reference implementation of the Littlewood-Richardson rule, based on the definition "count the semistandard skew tableaux whose row content is a lattice word"

lrScalar :: SkewPartition -> SkewPartition -> Int Source

lrScalar (lambda/mu) (alpha/beta) computes the scalar product of the two skew Schur functions s[lambda/mu] and s[alpha/beta] via the Littlewood-Richardson rule.

Adapted from John Stembridge Maple code: http://www.math.lsa.umich.edu/~jrs/software/SFexamples/LR_rule