jackpolynomials-1.4.7.0: Jack, zonal, Schur, and other symmetric polynomials
Copyright(c) Stéphane Laurent 2024
LicenseGPL-3
Maintainerlaurent_step@outlook.fr
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Algebra.SymmetricPolynomials

Description

A Jack polynomial can have a very long expression in the canonical basis. A considerably shorter expression is obtained by writing the polynomial as a linear combination of the monomial symmetric polynomials instead, which is always possible since Jack polynomials are symmetric. This is the initial motivation of this module. But now it contains much more stuff dealing with symmetric polynomials.

Synopsis

Checking symmetry

isSymmetricSpray :: (C a, Eq a) => Spray a -> Bool Source #

Checks whether a spray defines a symmetric polynomial.

>>> -- note that the sum of two symmetric polynomials is not symmetric
>>> -- if they have different numbers of variables:
>>> spray = schurPol' 4 [2, 2] ^+^ schurPol' 3 [2, 1]
>>> isSymmetricSpray spray

Classical symmetric polynomials

msPolynomial Source #

Arguments

:: (C a, Eq a) 
=> Int

number of variables

-> Partition

integer partition

-> Spray a 

Monomial symmetric polynomial

>>> putStrLn $ prettySpray' (msPolynomial 3 [2, 1])
(1) x1^2.x2 + (1) x1^2.x3 + (1) x1.x2^2 + (1) x1.x3^2 + (1) x2^2.x3 + (1) x2.x3^2

psPolynomial Source #

Arguments

:: (C a, Eq a) 
=> Int

number of variables

-> Partition

integer partition

-> Spray a 

Power sum polynomial

>>> putStrLn $ prettyQSpray (psPolynomial 3 [2, 1])
x^3 + x^2.y + x^2.z + x.y^2 + x.z^2 + y^3 + y^2.z + y.z^2 + z^3

cshPolynomial Source #

Arguments

:: (C a, Eq a) 
=> Int

number of variables

-> Partition

integer partition

-> Spray a 

Complete symmetric homogeneous polynomial

>>> putStrLn $ prettyQSpray (cshPolynomial 3 [2, 1])
x^3 + 2*x^2.y + 2*x^2.z + 2*x.y^2 + 3*x.y.z + 2*x.z^2 + y^3 + 2*y^2.z + 2*y.z^2 + z^3

esPolynomial Source #

Arguments

:: (C a, Eq a) 
=> Int

number of variables

-> Partition

integer partition

-> Spray a 

Elementary symmetric polynomial.

>>> putStrLn $ prettyQSpray (esPolynomial 3 [2, 1])
x^2.y + x^2.z + x.y^2 + 3*x.y.z + x.z^2 + y^2.z + y.z^2

Decomposition of symmetric polynomials

msCombination :: C a => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of monomial symmetric polynomials.

psCombination :: (Eq a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of power sum polynomials. Symmetry is not checked.

psCombination' :: (Eq a, C Rational a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of power sum polynomials. Same as psCombination but with other constraints on the base ring of the spray.

psCombination'' Source #

Arguments

:: (FunctionLike b, Eq b, C b, C (BaseRing b)) 
=> Spray b

parametric spray

-> Map Partition b 

Symmetric parametric spray as a linear combination of power sum polynomials.

cshCombination :: (Eq a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of complete symmetric homogeneous polynomials. Symmetry is not checked.

cshCombination' :: (Eq a, C Rational a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of complete symmetric homogeneous polynomials. Same as cshCombination but with other constraints on the base ring of the spray.

esCombination :: (Eq a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of elementary symmetric polynomials. Symmetry is not checked.

esCombination' :: (Eq a, C Rational a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of elementary symmetric polynomials. Same as esCombination but with other constraints on the base ring of the spray.

schurCombination :: (Eq a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of Schur polynomials. Symmetry is not checked.

schurCombination' :: (Eq a, C Rational a, C a) => Spray a -> Map Partition a Source #

Symmetric polynomial as a linear combination of Schur polynomials. Same as schurCombination but with other constraints on the base ring of the spray.

jackCombination Source #

Arguments

:: (Eq a, C a) 
=> a

Jack parameter

-> Char

which Jack polynomials, J, C, P or Q

-> Spray a

spray representing a symmetric polynomial

-> Map Partition a

map representing the linear combination; a partition lambda in the keys of this map corresponds to the term coeff *^ jackPol' n lambda alpha which, where coeff is the value attached to this key and n is the number of variables of the spray

Symmetric polynomial as a linear combination of Jack polynomials with a given Jack parameter. Symmetry is not checked.

jackCombination' Source #

Arguments

:: (FunctionLike b, Eq b, C b, Eq (BaseRing b), C (BaseRing b)) 
=> BaseRing b

Jack parameter

-> Char

which Jack polynomials, J, C, P or Q

-> Spray b

parametric spray representing a symmetric polynomial

-> Map Partition b 

Symmetric parametric polynomial as a linear combination of Jack polynomials with a given Jack parameter. Symmetry is not checked. Similar to jackCombination but for a parametric spray.

jackSymbolicCombination Source #

Arguments

:: Char

which Jack polynomials, J, C, P or Q

-> QSpray

spray representing a symmetric polynomial

-> Map Partition RatioOfQSprays

map representing the linear combination; a partition lambda in the keys of this map corresponds to the term coeff *^ jackSymbolicPol' n lambda which, where coeff is the value attached to this key and n is the number of variables of the spray

Symmetric polynomial as a linear combination of Jack polynomials with symbolic parameter. Symmetry is not checked.

jackSymbolicCombination' Source #

Arguments

:: (Eq a, C a) 
=> Char

which Jack polynomials, J, C, P or Q

-> ParametricSpray a

parametric spray representing a symmetric polynomial

-> Map Partition (RatioOfSprays a)

map representing the linear combination; a partition lambda in the keys of this map corresponds to the term coeff *^ jackSymbolicPol' n lambda which, where coeff is the value attached to this key and n is the number of variables of the spray

Symmetric parametric polynomial as a linear combination of Jack polynomials with symbolic parameter. Similar to jackSymbolicCombination but for a parametric spray.

Printing symmetric polynomials

prettySymmetricNumSpray :: (Num a, Ord a, Show a, C a) => Spray a -> String Source #

Prints a symmetric spray as a linear combination of monomial symmetric polynomials

>>> putStrLn $ prettySymmetricNumSpray $ schurPol' 3 [3, 1, 1]
M[3,1,1] + M[2,2,1]

prettySymmetricQSpray :: QSpray -> String Source #

Prints a symmetric spray as a linear combination of monomial symmetric polynomials

>>> putStrLn $ prettySymmetricQSpray $ jackPol' 3 [3, 1, 1] 2 'J'
42*M[3,1,1] + 28*M[2,2,1]

prettySymmetricParametricQSpray :: [String] -> ParametricQSpray -> String Source #

Prints a symmetric parametric spray as a linear combination of monomial symmetric polynomials.

>>> putStrLn $ prettySymmetricParametricQSpray ["a"] $ jackSymbolicPol' 3 [3, 1, 1] 'J'
{ [ 4*a^2 + 10*a + 6 ] }*M[3,1,1] + { [ 8*a + 12 ] }*M[2,2,1]

prettySymmetricSimpleParametricQSpray :: [String] -> SimpleParametricQSpray -> String Source #

Prints a symmetric simple parametric spray as a linear combination of monomial symmetric polynomials.

Operators on the space of symmetric polynomials

laplaceBeltrami :: (Eq a, C a) => a -> Spray a -> Spray a Source #

Laplace-Beltrami operator on the space of homogeneous symmetric polynomials; neither symmetry and homogeneity are checked.

calogeroSutherland :: (Eq a, C a) => a -> Spray a -> Spray a Source #

Calogero-Sutherland operator on the space of homogeneous symmetric polynomials; neither symmetry and homogeneity are checked

Hall inner product of symmetric polynomials

hallInnerProduct Source #

Arguments

:: (Eq a, C a) 
=> Spray a

spray

-> Spray a

spray

-> a

parameter

-> a 

Hall inner product with Jack parameter, aka Jack scalar product. It makes sense only for symmetric sprays, and the symmetry is not checked.

hallInnerProduct' Source #

Arguments

:: (Eq a, C Rational a, C a) 
=> Spray a

spray

-> Spray a

spray

-> a

parameter

-> a 

Hall inner product with Jack parameter. Same as hallInnerProduct but with other constraints on the base ring of the sprays.

hallInnerProduct'' Source #

Arguments

:: forall a. Real a 
=> Spray a

spray

-> Spray a

spray

-> a

parameter

-> Rational 

Hall inner product with Jack parameter. Same as hallInnerProduct but with other constraints on the base ring of the sprays. It is applicable to Spray Int sprays.

hallInnerProduct''' Source #

Arguments

:: (Eq b, C b, C (BaseRing b) b) 
=> Spray b

parametric spray

-> Spray b

parametric spray

-> BaseRing b

parameter

-> b 

Hall inner product with Jack parameter for parametric sprays, because the type of the parameter in hallInnerProduct is strange. For example, a ParametricQSpray spray is a Spray RatioOfQSprays spray, and it makes more sense to compute the Hall product with a Rational parameter then to compute the Hall product with a RatioOfQSprays parameter.

>>> import Math.Algebra.Jack.SymmetricPolynomials
>>> import Math.Algebra.JackSymbolicPol
>>> import Math.Algebra.Hspray
>>> jp = jackSymbolicPol 3 [2, 1] 'P'
>>> hallInnerProduct''' jp jp 5 == hallInnerProduct jp jp (constantRatioOfSprays 5)

hallInnerProduct'''' Source #

Arguments

:: (Eq b, C b, C Rational b, C (BaseRing b) b) 
=> Spray b

parametric spray

-> Spray b

parametric spray

-> BaseRing b

parameter

-> b 

Hall inner product with Jack parameter for parametric sprays. Same as hallInnerProduct''' but with other constraints on the types. It is applicable to SimpleParametricQSpray sprays, while hallInnerProduct''' is not.

symbolicHallInnerProduct :: (Eq a, C a) => Spray a -> Spray a -> Spray a Source #

Hall inner product with symbolic Jack parameter. See README for some examples.

symbolicHallInnerProduct' :: (Eq a, C Rational (Spray a), C a) => Spray a -> Spray a -> Spray a Source #

Hall inner product with symbolic Jack parameter. Same as symbolicHallInnerProduct but with other type constraints.

symbolicHallInnerProduct'' :: forall a. Real a => Spray a -> Spray a -> QSpray Source #

Hall inner product with symbolic Jack parameter. Same as symbolicHallInnerProduct but with other type constraints. It is applicable to Spray Int sprays.

Kostka-Foulkes polynomials

kostkaFoulkesPolynomial :: (Eq a, C a) => Partition -> Partition -> Spray a Source #

Kostka-Foulkes polynomial of two given partitions. This is a univariate polynomial whose value at 1 is the Kostka number of the two partitions.

kostkaFoulkesPolynomial' :: Partition -> Partition -> QSpray Source #

Kostka-Foulkes polynomial of two given partitions. This is a univariate polynomial whose value at 1 is the Kostka number of the two partitions.

skewKostkaFoulkesPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Partition

integer partition; the equality of the weight of this partition with the weight of the skew partition is a necessary condition to get a non-zero polynomial

-> Spray a 

Skew Kostka-Foulkes polynomial. This is a univariate polynomial associated to a skew partition and a partition, and its value at 1 is the skew Kostka number associated to these partitions.

skewKostkaFoulkesPolynomial' Source #

Arguments

:: Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Partition

integer partition; the equality of the weight of this partition with the weight of the skew partition is a necessary condition to get a non-zero polynomial

-> QSpray 

Skew Kostka-Foulkes polynomial. This is a univariate polynomial associated to a skew partition and a partition, and its value at 1 is the skew Kostka number associated to these partitions.

qt-Kostka polynomials

qtKostkaPolynomials :: (Eq a, C a) => Partition -> Map Partition (Spray a) Source #

qt-Kostka polynomials, aka Kostka-Macdonald polynomials. These are bivariate polynomials usually denoted by \(K_{\lambda, \mu}(q,t)\) for two integer partitions \(\lambda\) and \(mu\), and \(q\) and \(t\) denote the variables. One obtains the Kostka-Foulkes polynomials by substituting \(q\) with \(0\). For a given partition \(\mu\), the function returns the polynomials \(K_{\lambda, \mu}(q,t)\) for all partitions \(\lambda\) of the same weight as \(\mu\).

qtKostkaPolynomials' :: Partition -> Map Partition QSpray Source #

qt-Kostka polynomials, aka Kostka-Macdonald polynomials. These are bivariate polynomials usually denoted by \(K_{\lambda, \mu}(q,t)\) for two integer partitions \(\lambda\) and \(mu\), and \(q\) and \(t\) denote the variables. One obtains the Kostka-Foulkes polynomials by substituting \(q\) with \(0\). For a given partition \(\mu\), the function returns the polynomials \(K_{\lambda, \mu}(q,t)\) for all partitions \(\lambda\) of the same weight as \(\mu\).

qtSkewKostkaPolynomials Source #

Arguments

:: (Eq a, C a) 
=> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Map Partition (Spray a) 

Skew qt-Kostka polynomials. These are bivariate polynomials usually denoted by \(K_{\lambda/\mu, \nu}(q,t)\) for two integer partitions \(\lambda\) and \(mu\) defining a skew partition, an integer partition \(\nu\), and \(q\) and \(t\) denote the variables. One obtains the skew Kostka-Foulkes polynomials by substituting \(q\) with \(0\). For given partitions \(\lambda\) and \(\mu\), the function returns the polynomials \(K_{\lambda/\mu, \nu}(q,t)\) for all partitions \(\nu\) of the same weight as the skew partition.

qtSkewKostkaPolynomials' Source #

Arguments

:: Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Map Partition QSpray 

Skew qt-Kostka polynomials. These are bivariate polynomials usually denoted by \(K_{\lambda/\mu, \nu}(q,t)\) for two integer partitions \(\lambda\) and \(mu\) defining a skew partition, an integer partition \(\nu\), and \(q\) and \(t\) denote the variables. One obtains the skew Kostka-Foulkes polynomials by substituting \(q\) with \(0\). For given partitions \(\lambda\) and \(\mu\), the function returns the polynomials \(K_{\lambda/\mu, \nu}(q,t)\) for all partitions \(\nu\) of the same weight as the skew partition.

Hall-Littlewood polynomials

hallLittlewoodPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> Char

which Hall-Littlewood polynomial, P or Q

-> SimpleParametricSpray a 

Hall-Littlewood polynomial of a given partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). When substituting \(t\) with \(0\) in the Hall-Littlewood \(P\)-polynomials, one obtains the Schur polynomials.

hallLittlewoodPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> Char

which Hall-Littlewood polynomial, P or Q

-> SimpleParametricQSpray 

Hall-Littlewood polynomial of a given partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). When substituting \(t\) with \(0\) in the Hall-Littlewood \(P\)-polynomials, one obtains the Schur polynomials.

transitionsSchurToHallLittlewood Source #

Arguments

:: Int

weight of the partitions of the Hall-Littlewood polynomials

-> Char

which Hall-Littlewood polynomials, P or Q

-> Map Partition (Map Partition (Spray Int)) 

Hall-Littlewood polynomials as linear combinations of Schur polynomials.

skewHallLittlewoodPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Char

which skew Hall-Littlewood polynomial, P or Q

-> SimpleParametricSpray a 

Skew Hall-Littlewood polynomial of a given skew partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). When substituting \(t\) with \(0\) in the skew Hall-Littlewood \(P\)-polynomials, one obtains the skew Schur polynomials.

skewHallLittlewoodPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Char

which skew Hall-Littlewood polynomial, P or Q

-> SimpleParametricQSpray 

Skew Hall-Littlewood polynomial of a given skew partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). When substituting \(t\) with \(0\) in the skew Hall-Littlewood \(P\)-polynomials, one obtains the skew Schur polynomials.

Hall polynomials

hallPolynomials Source #

Arguments

:: Partition

the integer partition \(\mu\)

-> Partition

the integer partition \(\nu\)

-> Map Partition QSpray 

Hall polynomials \(g^{\lambda}_{\mu,\nu}(t)\) for given integer partitions \(\mu\) and \(\nu\). The keys of the map returned by this function are the partitions \(\lambda\) and the value attached to a key \(\lambda\) is the Hall polynomial \(g^{\lambda}_{\mu,\nu}(t)\) (it is given as a QSpray spray but actually all its coefficients are integer). Warning: slow.

t-Schur polynomials

tSchurPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> SimpleParametricSpray a 

t-Schur polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). One obtains the Schur polynomials by substituting \(t\) with \(0\). The name "(t)-Schur polynomial" is taken from Wheeler and Zinn-Justin's paper Hall polynomials, inverse Kostka polynomials and puzzles.

tSchurPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> SimpleParametricQSpray 

t-Schur polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). One obtains the Schur polynomials by substituting \(t\) with \(0\). The name "(t)-Schur polynomial" is taken from Wheeler and Zinn-Justin's paper Hall polynomials, inverse Kostka polynomials and puzzles.

tSkewSchurPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> SimpleParametricSpray a 

Skew t-Schur polynomial of a given skew partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). One obtains the skew Schur polynomials by substituting \(t\) with \(0\).

tSkewSchurPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> SimpleParametricQSpray 

Skew t-Schur polynomial of a given skew partition. This is a multivariate symmetric polynomial whose coefficients are polynomial in a single parameter usually denoted by \(t\). One obtains the skew Schur polynomials by substituting \(t\) with \(0\).

Macdonald polynomials

macdonaldPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> Char

which Macdonald polynomial, P or Q

-> ParametricSpray a 

Macdonald polynomial. This is a symmetric multivariate polynomial depending on two parameters usually denoted by \(q\) and \(t\). Substituting \(q\) with \(0\) yields the Hall-Littlewood polynomials.

>>> macPoly = macdonaldPolynomial 3 [2, 1] 'P'
>>> putStrLn $ prettySymmetricParametricQSpray ["q", "t"] macPoly
{ [ 1 ] }*M[2,1] + { [ 2*q.t^2 - q.t - q + t^2 + t - 2 ] %//% [ q.t^2 - 1 ] }*M[1,1,1]

macdonaldPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> Char

which Macdonald polynomial, P or Q

-> ParametricQSpray 

Macdonald polynomial. This is a symmetric multivariate polynomial depending on two parameters usually denoted by \(q\) and \(t\). Substituting \(q\) with \(0\) yields the Hall-Littlewood polynomials.

skewMacdonaldPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Char

which skew Macdonald polynomial, P or Q

-> ParametricSpray a 

Skew Macdonald polynomial of a given skew partition. This is a multivariate symmetric polynomial with two parameters usually denoted by \(q\) and \(t\). Substituting \(q\) with \(0\) yields the skew Hall-Littlewood polynomials.

skewMacdonaldPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> Char

which skew Macdonald polynomial, P or Q

-> ParametricQSpray 

Skew Macdonald polynomial of a given skew partition. This is a multivariate symmetric polynomial with two parameters usually denoted by \(q\) and \(t\). Substituting \(q\) with \(0\) yields the skew Hall-Littlewood polynomials.

macdonaldJpolynomial Source #

Arguments

:: forall a. (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> SimpleParametricSpray a 

Macdonald J-polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomial in two parameters.

macdonaldJpolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> SimpleParametricQSpray 

Macdonald J-polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomial in two parameters.

skewMacdonaldJpolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> ParametricSpray a 

Skew Macdonald J-polynomial. This is a multivariate symmetric polynomial whose coefficients depend on two parameters.

skewMacdonaldJpolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> ParametricQSpray 

Skew Macdonald J-polynomial. This is a multivariate symmetric polynomial whose coefficients depend on two parameters.

modifiedMacdonaldPolynomial Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> SimpleParametricSpray a 

Modified Macdonald polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomials in two parameters.

modifiedMacdonaldPolynomial' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> SimpleParametricQSpray 

Modified Macdonald polynomial. This is a multivariate symmetric polynomial whose coefficients are polynomials in two parameters.

Flagged Schur polynomials

flaggedSchurPol Source #

Arguments

:: (Eq a, C a) 
=> Partition

integer partition

-> [Int]

lower bounds

-> [Int]

upper bounds

-> Spray a 

Flagged Schur polynomial. A flagged Schur polynomial is not symmetric in general.

flaggedSchurPol' Source #

Arguments

:: Partition

integer partition

-> [Int]

lower bounds

-> [Int]

upper bounds

-> QSpray 

Flagged Schur polynomial. A flagged Schur polynomial is not symmetric in general.

flaggedSkewSchurPol Source #

Arguments

:: (Eq a, C a) 
=> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> [Int]

lower bounds

-> [Int]

upper bounds

-> Spray a 

Flagged skew Schur polynomial. A flagged skew Schur polynomial is not symmetric in general.

flaggedSkewSchurPol' Source #

Arguments

:: Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> [Int]

lower bounds

-> [Int]

upper bounds

-> QSpray 

Flagged skew Schur polynomial. A flagged skew Schur polynomial is not symmetric in general.

Factorial Schur polynomials

factorialSchurPol Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

integer partition

-> [a]

the sequence denoted by \(y\) in the reference paper

-> Spray a 

Factorial Schur polynomial. See Kreiman's paper Products of factorial Schur functions for the definition.

factorialSchurPol' Source #

Arguments

:: Int

number of variables

-> Partition

integer partition

-> [Rational]

the sequence denoted by \(y\) in the reference paper

-> QSpray 

Factorial Schur polynomial. See Kreiman's paper Products of factorial Schur functions for the definition.

skewFactorialSchurPol Source #

Arguments

:: (Eq a, C a) 
=> Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> IntMap a

the sequence denoted by \(a\) in the reference paper

-> Spray a 

Skew factorial Schur polynomial. See Macdonald's paper Schur functions: theme and variations, 6th variation, for the definition.

skewFactorialSchurPol' Source #

Arguments

:: Int

number of variables

-> Partition

outer partition of the skew partition

-> Partition

inner partition of the skew partition

-> IntMap Rational

the sequence denoted by \(a\) in the reference paper

-> QSpray 

Skew factorial Schur polynomial. See Macdonald's paper Schur functions: theme and variations, 6th variation, for the definition.