combinat-0.2.9.0: Generate and manipulate various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Tableaux.GelfandTsetlin

Contents

Description

Gelfand-Tsetlin patterns and Kostka numbers.

Gelfand-Tsetlin patterns (or tableaux) are triangular arrays like

[ 3 ]
[ 3 , 2 ]
[ 3 , 1 , 0 ]
[ 2 , 0 , 0 , 0 ]

with both rows and columns non-increasing non-negative integers. Note: these are in bijection with the semi-standard Young tableaux.

If we add the further restriction that the top diagonal reads lambda, and the diagonal sums are partial sums of mu, where lambda and mu are two partitions (in this case lambda=[3,2] and mu=[2,1,1,1]), then the number of the resulting patterns or tableaux is the Kostka number K(lambda,mu). Actually mu doesn't even need to the be non-increasing.

Synopsis

Kostka numbers

kostkaNumber :: Partition -> Partition -> Int Source #

Kostka numbers (via counting Gelfand-Tsetlin patterns). See for example http://en.wikipedia.org/wiki/Kostka_number

K(lambda,mu)==0 unless lambda dominates mu:

[ mu | mu <- partitions (weight lam) , kostkaNumber lam mu > 0 ] == dominatedPartitions lam

kostkaNumberReferenceNaive :: Partition -> Partition -> Int Source #

Very naive (and slow) implementation of Kostka numbers, for reference.

kostkaNumbersWithGivenLambda :: forall coeff. Num coeff => Partition -> Map Partition coeff Source #

Lists all (positive) Kostka numbers K(lambda,mu) with the given lambda:

kostkaNumbersWithGivenLambda lambda == Map.fromList [ (mu , kostkaNumber lambda mu) | mu <- dominatedPartitions lambda ]

It's much faster than computing the individual Kostka numbers, but not as fast as it could be.

kostkaNumbersWithGivenMu :: Partition -> Map Partition Int Source #

Lists all (positive) Kostka numbers K(lambda,mu) with the given mu:

kostkaNumbersWithGivenMu mu == Map.fromList [ (lambda , kostkaNumber lambda mu) | lambda <- dominatingPartitions mu ]

This function uses the iterated Pieri rule, and is relatively fast.

Gelfand-Tsetlin patterns

type GT = [[Int]] Source #

A Gelfand-Tstetlin tableau

kostkaGelfandTsetlinPatterns' :: Partition -> [Int] -> [GT] Source #

Generates all Kostka-Gelfand-Tsetlin tableau, that is, triangular arrays like

[ 3 ]
[ 3 , 2 ]
[ 3 , 1 , 0 ]
[ 2 , 0 , 0 , 0 ]

with both rows and column non-increasing such that the top diagonal read lambda (in this case lambda=[3,2]) and the diagonal sums are partial sums of mu (in this case mu=[2,1,1,1])

The number of such GT tableaux is the Kostka number K(lambda,mu).

countKostkaGelfandTsetlinPatterns :: Partition -> Partition -> Int Source #

This returns the corresponding Kostka number:

countKostkaGelfandTsetlinPatterns lambda mu == length (kostkaGelfandTsetlinPatterns lambda mu)

The iterated Pieri rule

iteratedPieriRule :: Num coeff => [Int] -> Map Partition coeff Source #

Computes the Schur expansion of h[n1]*h[n2]*h[n3]*...*h[nk] via iterating the Pieri rule. Note: the coefficients are actually the Kostka numbers; the following is true:

Map.toList (iteratedPieriRule (fromPartition mu))  ==  [ (lam, kostkaNumber lam mu) | lam <- dominatingPartitions mu ]

This should be faster than individually computing all these Kostka numbers.

iteratedPieriRule' :: Num coeff => Partition -> [Int] -> Map Partition coeff Source #

Iterating the Pieri rule, we can compute the Schur expansion of h[lambda]*h[n1]*h[n2]*h[n3]*...*h[nk]

iteratedPieriRule'' :: Num coeff => (Partition, coeff) -> [Int] -> Map Partition coeff Source #

iteratedDualPieriRule :: Num coeff => [Int] -> Map Partition coeff Source #

Computes the Schur expansion of e[n1]*e[n2]*e[n3]*...*e[nk] via iterating the Pieri rule. Note: the coefficients are actually the Kostka numbers; the following is true:

Map.toList (iteratedDualPieriRule (fromPartition mu))  ==  
  [ (dualPartition lam, kostkaNumber lam mu) | lam <- dominatingPartitions mu ]

This should be faster than individually computing all these Kostka numbers. It is a tiny bit slower than iteratedPieriRule.

iteratedDualPieriRule' :: Num coeff => Partition -> [Int] -> Map Partition coeff Source #

Iterating the Pieri rule, we can compute the Schur expansion of e[lambda]*e[n1]*e[n2]*e[n3]*...*e[nk]

iteratedDualPieriRule'' :: Num coeff => (Partition, coeff) -> [Int] -> Map Partition coeff Source #