{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Math.Algebra.SymmetricPolynomials
(
isSymmetricSpray
, msPolynomial
, psPolynomial
, cshPolynomial
, esPolynomial
, msCombination
, psCombination
, psCombination'
, cshCombination
, cshCombination'
, esCombination
, esCombination'
, schurCombination
, schurCombination'
, jackCombination
, jackSymbolicCombination
, jackSymbolicCombination'
, prettySymmetricNumSpray
, prettySymmetricQSpray
, prettySymmetricQSpray'
, prettySymmetricParametricQSpray
, prettySymmetricSimpleParametricQSpray
, laplaceBeltrami
, calogeroSutherland
, hallInnerProduct
, hallInnerProduct'
, hallInnerProduct''
, hallInnerProduct'''
, hallInnerProduct''''
, symbolicHallInnerProduct
, symbolicHallInnerProduct'
, symbolicHallInnerProduct''
, kostkaNumbers
, symbolicKostkaNumbers
, kostkaFoulkesPolynomial
, kostkaFoulkesPolynomial'
, hallLittlewoodPolynomial
, hallLittlewoodPolynomial'
, transitionsSchurToHallLittlewood
, skewHallLittlewoodPolynomial
, skewHallLittlewoodPolynomial'
, flaggedSchurPol
, flaggedSchurPol'
, flaggedSkewSchurPol
, flaggedSkewSchurPol'
, factorialSchurPol
, factorialSchurPol'
, skewFactorialSchurPol
, skewFactorialSchurPol'
) where
import Prelude hiding ( fromIntegral, fromRational )
import qualified Algebra.Additive as AlgAdd
import Algebra.Field ( fromRational )
import qualified Algebra.Field as AlgField
import qualified Algebra.Module as AlgMod
import qualified Algebra.Ring as AlgRing
import Algebra.ToInteger ( fromIntegral )
import qualified Data.Foldable as DF
import qualified Data.HashMap.Strict as HM
import Data.List (
foldl1'
, nub
)
import Data.List.Extra (
unsnoc
, allSame
)
import Data.IntMap.Strict (
IntMap
)
import qualified Data.IntMap.Strict as IM
import Data.Map.Merge.Strict (
merge
, dropMissing
, zipWithMatched
)
import Data.Map.Strict (
Map
, unionsWith
, insert
)
import qualified Data.Map.Strict as DM
import Data.Matrix (
getRow
)
import Data.Maybe ( fromJust )
import Data.Ratio ( (%) )
import Data.Sequence (
Seq
, (|>)
, index
)
import qualified Data.Sequence as S
import qualified Data.Vector as V
import Data.Tuple.Extra ( second )
import Math.Algebra.Hspray (
FunctionLike (..)
, (/^)
, Spray
, Powers (..)
, QSpray
, QSpray'
, ParametricSpray
, ParametricQSpray
, SimpleParametricSpray
, SimpleParametricQSpray
, lone
, qlone
, lone'
, fromList
, getCoefficient
, getConstantTerm
, isConstant
, (%//%)
, RatioOfSprays (..)
, RatioOfQSprays
, constantRatioOfSprays
, zeroRatioOfSprays
, unitRatioOfSprays
, prettyRatioOfQSpraysXYZ
, showNumSpray
, showQSpray
, showQSpray'
, showSpray
, prettyQSprayXYZ
, zeroSpray
, unitSpray
, productOfSprays
, sumOfSprays
, constantSpray
, allExponents
)
import Math.Algebra.Jack.Internal (
Partition
, _isPartition
, sprayToMap
, comboToSpray
, _inverseKostkaMatrix
, _kostkaNumbers
, _symbolicKostkaNumbers
, _inverseSymbolicKostkaMatrix
, _kostkaFoulkesPolynomial
, _hallLittlewoodPolynomialsInSchurBasis
, _transitionMatrixHallLittlewoodSchur
, skewHallLittlewoodP
, skewHallLittlewoodQ
, isSkewPartition
, flaggedSemiStandardYoungTableaux
, tableauWeight
, isIncreasing
, flaggedSkewTableaux
, skewTableauWeight
)
import Math.Algebra.JackPol (
schurPol
)
import Math.Combinat.Compositions ( compositions1 )
import Math.Combinat.Partitions.Integer (
fromPartition
, toPartition
, mkPartition
, partitions
, partitionWidth
)
import Math.Combinat.Partitions.Skew (
mkSkewPartition
)
import Math.Combinat.Permutations ( permuteMultiset )
import Math.Combinat.Tableaux ( semiStandardYoungTableaux )
import Math.Combinat.Tableaux.GelfandTsetlin ( kostkaNumbersWithGivenMu )
import Math.Combinat.Tableaux.Skew (
SkewTableau (..)
, semiStandardSkewTableaux
)
msPolynomialUnsafe :: (AlgRing.C a, Eq a)
=> Int
-> Partition
-> Spray a
msPolynomialUnsafe :: forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomialUnsafe Int
n Partition
lambda
= [(Partition, a)] -> Spray a
forall a. (C a, Eq a) => [(Partition, a)] -> Spray a
fromList ([(Partition, a)] -> Spray a) -> [(Partition, a)] -> Spray a
forall a b. (a -> b) -> a -> b
$ [Partition] -> [a] -> [(Partition, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
permutations [a]
coefficients
where
llambda :: Int
llambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
permutations :: [Partition]
permutations = Partition -> [Partition]
forall a. (Eq a, Ord a) => [a] -> [[a]]
permuteMultiset (Partition
lambda Partition -> Partition -> Partition
forall a. [a] -> [a] -> [a]
++ Int -> Int -> Partition
forall a. Int -> a -> [a]
replicate (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
llambda) Int
0)
coefficients :: [a]
coefficients = a -> [a]
forall a. a -> [a]
repeat a
forall a. C a => a
AlgRing.one
msPolynomial :: (AlgRing.C a, Eq a)
=> Int
-> Partition
-> Spray a
msPolynomial :: forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomial Int
n Partition
lambda
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"msPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"msPolynomial: invalid partition."
| Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise = Int -> Partition -> Spray a
forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomialUnsafe Int
n Partition
lambda
isSymmetricSpray :: (AlgRing.C a, Eq a) => Spray a -> Bool
isSymmetricSpray :: forall a. (C a, Eq a) => Spray a -> Bool
isSymmetricSpray Spray a
spray = Spray a
spray Spray a -> Spray a -> Bool
forall a. Eq a => a -> a -> Bool
== Spray a
spray'
where
assocs :: [(Partition, a)]
assocs = Spray a -> [(Partition, a)]
forall a. C a => Spray a -> [(Partition, a)]
msCombination' Spray a
spray
n :: Int
n = Spray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables Spray a
spray
spray' :: Spray a
spray' = (Spray a -> Spray a -> Spray a) -> [Spray a] -> Spray a
forall a. HasCallStack => (a -> a -> a) -> [a] -> a
foldl1' Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
(^+^)
(
((Partition, a) -> Spray a) -> [(Partition, a)] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\(Partition
lambda, a
x) -> a
BaseRing (Spray a)
x BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Int -> Partition -> Spray a
forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomial Int
n Partition
lambda) [(Partition, a)]
assocs
)
msCombination :: AlgRing.C a => Spray a -> Map Partition a
msCombination :: forall a. C a => Spray a -> Map Partition a
msCombination Spray a
spray = [(Partition, a)] -> Map Partition a
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList (Spray a -> [(Partition, a)]
forall a. C a => Spray a -> [(Partition, a)]
msCombination' Spray a
spray)
msCombination' :: AlgRing.C a => Spray a -> [(Partition, a)]
msCombination' :: forall a. C a => Spray a -> [(Partition, a)]
msCombination' Spray a
spray =
(Seq Int -> (Partition, a)) -> [Seq Int] -> [(Partition, a)]
forall a b. (a -> b) -> [a] -> [b]
map (\Seq Int
lambda -> let mu :: Partition
mu = Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList Seq Int
lambda in (Partition
mu, Partition -> Spray a -> a
forall a. C a => Partition -> Spray a -> a
getCoefficient Partition
mu Spray a
spray))
[Seq Int]
lambdas
where
decreasing :: Seq a -> Bool
decreasing Seq a
ys =
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Seq a
ys Seq a -> Int -> a
forall a. Seq a -> Int -> a
`index` Int
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= Seq a
ys Seq a -> Int -> a
forall a. Seq a -> Int -> a
`index` (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) | Int
i <- [Int
0 .. Seq a -> Int
forall a. Seq a -> Int
S.length Seq a
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2]]
lambdas :: [Seq Int]
lambdas = (Seq Int -> Bool) -> [Seq Int] -> [Seq Int]
forall a. (a -> Bool) -> [a] -> [a]
filter Seq Int -> Bool
forall {a}. Ord a => Seq a -> Bool
decreasing (Spray a -> [Seq Int]
forall a. Spray a -> [Seq Int]
allExponents Spray a
spray)
makeMSpray :: (Eq a, AlgRing.C a) => Spray a -> Spray a
makeMSpray :: forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray = [(Partition, a)] -> Spray a
forall a. (C a, Eq a) => [(Partition, a)] -> Spray a
fromList ([(Partition, a)] -> Spray a)
-> (Spray a -> [(Partition, a)]) -> Spray a -> Spray a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spray a -> [(Partition, a)]
forall a. C a => Spray a -> [(Partition, a)]
msCombination'
showSymmetricMonomials :: [Seq Int] -> [String]
showSymmetricMonomials :: [Seq Int] -> [[Char]]
showSymmetricMonomials = (Seq Int -> [Char]) -> [Seq Int] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Seq Int -> [Char]
showSymmetricMonomial
where
showSymmetricMonomial :: Seq Int -> String
showSymmetricMonomial :: Seq Int -> [Char]
showSymmetricMonomial Seq Int
lambda = Char
'M' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Partition -> [Char]
forall a. Show a => a -> [Char]
show (Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList Seq Int
lambda)
prettySymmetricNumSpray ::
(Num a, Ord a, Show a, AlgRing.C a) => Spray a -> String
prettySymmetricNumSpray :: forall a. (Num a, Ord a, Show a, C a) => Spray a -> [Char]
prettySymmetricNumSpray Spray a
spray =
([Seq Int] -> [[Char]]) -> (a -> [Char]) -> Spray a -> [Char]
forall a.
(Num a, Ord a) =>
([Seq Int] -> [[Char]]) -> (a -> [Char]) -> Spray a -> [Char]
showNumSpray [Seq Int] -> [[Char]]
showSymmetricMonomials a -> [Char]
forall a. Show a => a -> [Char]
show Spray a
mspray
where
mspray :: Spray a
mspray = Spray a -> Spray a
forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray Spray a
spray
prettySymmetricQSpray :: QSpray -> String
prettySymmetricQSpray :: QSpray -> [Char]
prettySymmetricQSpray QSpray
spray = ([Seq Int] -> [[Char]]) -> QSpray -> [Char]
showQSpray [Seq Int] -> [[Char]]
showSymmetricMonomials QSpray
mspray
where
mspray :: QSpray
mspray = QSpray -> QSpray
forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray QSpray
spray
prettySymmetricQSpray' :: QSpray' -> String
prettySymmetricQSpray' :: QSpray' -> [Char]
prettySymmetricQSpray' QSpray'
spray = ([Seq Int] -> [[Char]]) -> QSpray' -> [Char]
showQSpray' [Seq Int] -> [[Char]]
showSymmetricMonomials QSpray'
mspray
where
mspray :: QSpray'
mspray = QSpray' -> QSpray'
forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray QSpray'
spray
prettySymmetricParametricQSpray :: [String] -> ParametricQSpray -> String
prettySymmetricParametricQSpray :: [[Char]] -> ParametricQSpray -> [Char]
prettySymmetricParametricQSpray [[Char]]
letters ParametricQSpray
spray =
(RatioOfQSprays -> [Char])
-> ([Char], [Char])
-> ([Seq Int] -> [[Char]])
-> ParametricQSpray
-> [Char]
forall a.
(a -> [Char])
-> ([Char], [Char]) -> ([Seq Int] -> [[Char]]) -> Spray a -> [Char]
showSpray ([[Char]] -> RatioOfQSprays -> [Char]
prettyRatioOfQSpraysXYZ [[Char]]
letters) ([Char]
"{ ", [Char]
" }")
[Seq Int] -> [[Char]]
showSymmetricMonomials ParametricQSpray
mspray
where
mspray :: ParametricQSpray
mspray = ParametricQSpray -> ParametricQSpray
forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray ParametricQSpray
spray
prettySymmetricSimpleParametricQSpray ::
[String] -> SimpleParametricQSpray -> String
prettySymmetricSimpleParametricQSpray :: [[Char]] -> SimpleParametricQSpray -> [Char]
prettySymmetricSimpleParametricQSpray [[Char]]
letters SimpleParametricQSpray
spray =
(QSpray -> [Char])
-> ([Char], [Char])
-> ([Seq Int] -> [[Char]])
-> SimpleParametricQSpray
-> [Char]
forall a.
(a -> [Char])
-> ([Char], [Char]) -> ([Seq Int] -> [[Char]]) -> Spray a -> [Char]
showSpray ([[Char]] -> QSpray -> [Char]
prettyQSprayXYZ [[Char]]
letters) ([Char]
"(", [Char]
")")
[Seq Int] -> [[Char]]
showSymmetricMonomials SimpleParametricQSpray
mspray
where
mspray :: SimpleParametricQSpray
mspray = SimpleParametricQSpray -> SimpleParametricQSpray
forall a. (Eq a, C a) => Spray a -> Spray a
makeMSpray SimpleParametricQSpray
spray
laplaceBeltrami :: (Eq a, AlgField.C a) => a -> Spray a -> Spray a
laplaceBeltrami :: forall a. (Eq a, C a) => a -> Spray a -> Spray a
laplaceBeltrami a
alpha Spray a
spray =
if Spray a -> Bool
forall b. FunctionLike b => b -> Bool
isConstant Spray a
spray
then Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
else a
BaseRing (Spray a)
alpha' BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
spray1 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
spray2
where
alpha' :: a
alpha' = a
alpha a -> a -> a
forall a. C a => a -> a -> a
AlgField./ Integer -> a
forall a. C a => Integer -> a
AlgRing.fromInteger Integer
2
n :: Int
n = Spray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables Spray a
spray
range :: Partition
range = [Int
1 .. Int
n]
dsprays :: [Spray a]
dsprays = (Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Spray a -> Spray a
forall b. FunctionLike b => Int -> b -> b
`derivative` Spray a
spray) Partition
range
op1 :: Int -> Spray a
op1 Int
i = Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
i Int
2 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Int -> Spray a -> Spray a
forall b. FunctionLike b => Int -> b -> b
derivative Int
i ([Spray a]
dsprays [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
spray1 :: Spray a
spray1 = [Spray a] -> Spray a
forall a. C a => [a] -> a
AlgAdd.sum ((Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
op1 Partition
range)
spray2 :: Spray a
spray2 = RatioOfSprays a -> Spray a
forall a. RatioOfSprays a -> Spray a
_numerator (RatioOfSprays a -> Spray a) -> RatioOfSprays a -> Spray a
forall a b. (a -> b) -> a -> b
$ [RatioOfSprays a] -> RatioOfSprays a
forall a. C a => [a] -> a
AlgAdd.sum
[(Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
i Int
2 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ [Spray a]
dsprays [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) Spray a -> Spray a -> RatioOfSprays a
forall a. (Eq a, C a) => Spray a -> Spray a -> RatioOfSprays a
%//% (Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
i Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^-^ Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
j)
| Int
i <- Partition
range, Int
j <- Partition
range, Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
j]
calogeroSutherland :: (Eq a, AlgField.C a) => a -> Spray a -> Spray a
calogeroSutherland :: forall a. (Eq a, C a) => a -> Spray a -> Spray a
calogeroSutherland a
alpha Spray a
spray =
if Spray a -> Bool
forall b. FunctionLike b => b -> Bool
isConstant Spray a
spray
then Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
else Spray a -> Spray a
forall {a}. (C a, Eq a) => Spray a -> Spray a
halfSpray (Spray a -> Spray a) -> Spray a -> Spray a
forall a b. (a -> b) -> a -> b
$ a
BaseRing (Spray a)
alpha BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
spray1 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
spray2
where
halfSpray :: Spray a -> Spray a
halfSpray Spray a
p = Spray a
p Spray a -> a -> Spray a
forall a. (C a, Eq a) => Spray a -> a -> Spray a
/^ Integer -> a
forall a. C a => Integer -> a
AlgRing.fromInteger Integer
2
n :: Int
n = Spray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables Spray a
spray
range :: Partition
range = [Int
1 .. Int
n]
dsprays :: [Spray a]
dsprays = (Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Spray a -> Spray a
forall b. FunctionLike b => Int -> b -> b
`derivative` Spray a
spray) Partition
range
op0 :: Spray a -> Int -> Spray a
op0 Spray a
p Int
i = Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
i Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Int -> Spray a -> Spray a
forall b. FunctionLike b => Int -> b -> b
derivative Int
i Spray a
p
op1 :: Spray a -> Int -> Spray a
op1 Spray a
p Int
i = Spray a -> Int -> Spray a
forall {a}. (Eq a, C a) => Spray a -> Int -> Spray a
op0 (Spray a -> Int -> Spray a
forall {a}. (Eq a, C a) => Spray a -> Int -> Spray a
op0 Spray a
p Int
i) Int
i
spray1 :: Spray a
spray1 = [Spray a] -> Spray a
forall a. C a => [a] -> a
AlgAdd.sum ((Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (Spray a -> Int -> Spray a
forall {a}. (Eq a, C a) => Spray a -> Int -> Spray a
op1 Spray a
spray) Partition
range)
spray2 :: Spray a
spray2 = RatioOfSprays a -> Spray a
forall a. RatioOfSprays a -> Spray a
_numerator (RatioOfSprays a -> Spray a) -> RatioOfSprays a -> Spray a
forall a b. (a -> b) -> a -> b
$ [RatioOfSprays a] -> RatioOfSprays a
forall a. C a => [a] -> a
AlgAdd.sum
[let (Spray a
xi, Spray a
xj, Spray a
dxi, Spray a
dxj) =
(Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
i, Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
j, [Spray a]
dsprays [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1), [Spray a]
dsprays [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) in
(Spray a
xi Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
xj) Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ (Spray a
xi Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
dxi Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^-^ Spray a
xj Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
dxj) Spray a -> Spray a -> RatioOfSprays a
forall a. (Eq a, C a) => Spray a -> Spray a -> RatioOfSprays a
%//% (Spray a
xi Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^-^ Spray a
xj)
| Int
i <- Partition
range, Int
j <- [Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 .. Int
n]]
psPolynomial :: (AlgRing.C a, Eq a)
=> Int
-> Partition
-> Spray a
psPolynomial :: forall a. (C a, Eq a) => Int -> Partition -> Spray a
psPolynomial Int
n Partition
lambda
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"psPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"psPolynomial: invalid partition."
| Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
lambda = Spray a
forall a. C a => Spray a
unitSpray
| Int
llambda Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays [Spray a]
sprays
where
llambda :: Int
llambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
sprays :: [Spray a]
sprays = [[(Powers, a)] -> Spray a
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(Powers, a)] -> Spray a) -> [(Powers, a)] -> Spray a
forall a b. (a -> b) -> a -> b
$ [Int -> Int -> (Powers, a)
forall {b}. C b => Int -> Int -> (Powers, b)
f Int
i Int
k | Int
i <- [Int
1 .. Int
n]] | Int
k <- Partition
lambda]
f :: Int -> Int -> (Powers, b)
f Int
j Int
k = (Seq Int -> Int -> Powers
Powers Seq Int
expts Int
j, b
forall a. C a => a
AlgRing.one)
where
expts :: Seq Int
expts = Int -> Int -> Seq Int
forall a. Int -> a -> Seq a
S.replicate (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Int
0 Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
|> Int
k
eLambdaMu :: Partition -> Partition -> Rational
eLambdaMu :: Partition -> Partition -> Rational
eLambdaMu Partition
lambda Partition
mu
| Int
ellLambda Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
ellMu = Rational
0
| Bool
otherwise = if Int -> Bool
forall a. Integral a => a -> Bool
even (Int
ellLambda Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ellMu)
then [Rational] -> Rational
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Rational]
xs
else - [Rational] -> Rational
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Rational]
xs
where
ellLambda :: Int
ellLambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
ellMu :: Int
ellMu = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
mu
compos :: [Partition]
compos = Int -> Int -> [Partition]
forall a. Integral a => a -> a -> [Partition]
compositions1 Int
ellMu Int
ellLambda
lambdaPerms :: [Partition]
lambdaPerms = Partition -> [Partition]
forall a. (Eq a, Ord a) => [a] -> [[a]]
permuteMultiset Partition
lambda
sequencesOfPartitions :: [[Partition]]
sequencesOfPartitions = ([Partition] -> Bool) -> [[Partition]] -> [[Partition]]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> ([Partition] -> Bool) -> [Partition] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Partition] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null)
[Partition -> Partition -> [Partition]
partitionSequences Partition
perm Partition
compo
| Partition
perm <- [Partition]
lambdaPerms, Partition
compo <- [Partition]
compos]
xs :: [Rational]
xs = [[Partition] -> Rational
eMuNus [Partition]
nus | [Partition]
nus <- [[Partition]]
sequencesOfPartitions]
partitionSequences :: [Int] -> [Int] -> [Partition]
partitionSequences :: Partition -> Partition -> [Partition]
partitionSequences Partition
kappa Partition
compo = if Bool
test then [Partition]
nus else []
where
headOfCompo :: Partition
headOfCompo = (Partition, Int) -> Partition
forall a b. (a, b) -> a
fst ((Partition, Int) -> Partition) -> (Partition, Int) -> Partition
forall a b. (a -> b) -> a -> b
$ Maybe (Partition, Int) -> (Partition, Int)
forall a. HasCallStack => Maybe a -> a
fromJust (Partition -> Maybe (Partition, Int)
forall a. [a] -> Maybe ([a], a)
unsnoc Partition
compo)
starts :: Partition
starts = (Int -> Int -> Int) -> Int -> Partition -> Partition
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Int
0 Partition
headOfCompo
ends :: Partition
ends = (Int -> Int -> Int) -> Partition -> Partition -> Partition
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Partition
starts Partition
compo
nus :: [Partition]
nus = [
[ Partition
kappa Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
k | Int
k <- [Partition
starts Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i .. Partition
ends Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ]
| Int
i <- [Int
0 .. Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
compo Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
]
nuWeights :: Partition
nuWeights = [Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
nu | Partition
nu <- [Partition]
nus]
decreasing :: [a] -> Bool
decreasing [a]
ys =
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [[a]
ys [a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!! Int
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= [a]
ys [a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) | Int
i <- [Int
0 .. [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
ys Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2]]
test :: Bool
test = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ((Int -> Int -> Bool) -> Partition -> Partition -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
(==) Partition
mu Partition
nuWeights) Bool -> Bool -> Bool
&& (Partition -> Bool) -> [Partition] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Partition -> Bool
forall {a}. Ord a => [a] -> Bool
decreasing [Partition]
nus
eMuNus :: [Partition] -> Rational
eMuNus :: [Partition] -> Rational
eMuNus [Partition]
nus = [Rational] -> Rational
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [Rational]
toMultiply
where
w :: Int -> Partition -> Rational
w :: Int -> Partition -> Rational
w Int
k Partition
nu =
let table :: Partition
table = [Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j) | Int
i <- Partition
nu] | Int
j <- Partition -> Partition
forall a. Eq a => [a] -> [a]
nub Partition
nu] in
(Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
forall {a}. (Num a, Enum a) => a -> a
factorial (Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
nu Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
%
(Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product ((Int -> Int) -> Partition -> Partition
forall a b. (a -> b) -> [a] -> [b]
map Int -> Int
forall {a}. (Num a, Enum a) => a -> a
factorial Partition
table))
factorial :: a -> a
factorial a
n = [a] -> a
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [a
2 .. a
n]
toMultiply :: [Rational]
toMultiply = (Int -> Partition -> Rational)
-> Partition -> [Partition] -> [Rational]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Partition -> Rational
w Partition
mu [Partition]
nus
mspInPSbasis :: Partition -> Map Partition Rational
mspInPSbasis :: Partition -> Map Partition Rational
mspInPSbasis Partition
kappa = [(Partition, Rational)] -> Map Partition Rational
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList ((Rational -> Partition -> (Partition, Rational))
-> [Rational] -> [Partition] -> [(Partition, Rational)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Rational -> Partition -> (Partition, Rational)
f [Rational]
weights [Partition]
lambdas)
where
parts :: [Partition]
parts = Int -> [Partition]
partitions (Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
kappa)
([Rational]
weights, [Partition]
lambdas) = [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Rational, Partition)] -> ([Rational], [Partition]))
-> [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. (a -> b) -> a -> b
$ ((Rational, Partition) -> Bool)
-> [(Rational, Partition)] -> [(Rational, Partition)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
/= Rational
0) (Rational -> Bool)
-> ((Rational, Partition) -> Rational)
-> (Rational, Partition)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational, Partition) -> Rational
forall a b. (a, b) -> a
fst)
[let lambda :: Partition
lambda = Partition -> Partition
fromPartition Partition
part in (Partition -> Partition -> Rational
eLambdaMu Partition
kappa Partition
lambda, Partition
lambda) | Partition
part <- [Partition]
parts]
f :: Rational -> Partition -> (Partition, Rational)
f Rational
weight Partition
lambda =
(Partition
lambda, Rational
weight Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/ Int -> Rational
forall a. Real a => a -> Rational
toRational (Partition -> Int
zlambda Partition
lambda))
zlambda :: Partition -> Int
zlambda :: Partition -> Int
zlambda Partition
lambda = Int
p
where
parts :: Partition
parts = Partition -> Partition
forall a. Eq a => [a] -> [a]
nub Partition
lambda
table :: Partition
table = [Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j) | Int
k <- Partition
lambda] | Int
j <- Partition
parts]
p :: Int
p =
Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [Int -> Int
forall {a}. (Num a, Enum a) => a -> a
factorial Int
mj Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
partInt -> Int -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Int
mj | (Int
part, Int
mj) <- Partition -> Partition -> [(Int, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip Partition
parts Partition
table]
factorial :: a -> a
factorial a
n = [a] -> a
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [a
2 .. a
n]
_symmPolyCombination ::
forall a b. (Eq a, AlgRing.C a)
=> (Partition -> Map Partition b)
-> (a -> b -> a)
-> Spray a
-> Map Partition a
_symmPolyCombination :: forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination Partition -> Map Partition b
mspInSymmPolyBasis a -> b -> a
func Spray a
spray =
if a
constantTerm a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
forall a. C a => a
AlgAdd.zero
then Map Partition a
symmPolyMap
else Partition -> a -> Map Partition a -> Map Partition a
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert [] a
constantTerm Map Partition a
symmPolyMap
where
constantTerm :: a
constantTerm = Spray a -> a
forall a. C a => Spray a -> a
getConstantTerm Spray a
spray
assocs :: [(Partition, a)]
assocs = Spray a -> [(Partition, a)]
forall a. C a => Spray a -> [(Partition, a)]
msCombination' (Spray a
spray Spray a -> BaseRing (Spray a) -> Spray a
forall b. FunctionLike b => b -> BaseRing b -> b
<+ (a -> a
forall a. C a => a -> a
AlgAdd.negate a
constantTerm)) :: [(Partition, a)]
f :: (Partition, a) -> [(Partition, a)]
f :: (Partition, a) -> [(Partition, a)]
f (Partition
lambda, a
coeff) =
((Partition, b) -> (Partition, a))
-> [(Partition, b)] -> [(Partition, a)]
forall a b. (a -> b) -> [a] -> [b]
map ((b -> a) -> (Partition, b) -> (Partition, a)
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second (a -> b -> a
func a
coeff)) (Map Partition b -> [(Partition, b)]
forall k a. Map k a -> [(k, a)]
DM.toList Map Partition b
symmPolyCombo)
where
symmPolyCombo :: Map Partition b
symmPolyCombo = Partition -> Map Partition b
mspInSymmPolyBasis Partition
lambda :: Map Partition b
symmPolyMap :: Map Partition a
symmPolyMap = (a -> Bool) -> Map Partition a -> Map Partition a
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
forall a. C a => a
AlgAdd.zero)
((a -> a -> a) -> [Map Partition a] -> Map Partition a
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
unionsWith a -> a -> a
forall a. C a => a -> a -> a
(AlgAdd.+) (((Partition, a) -> Map Partition a)
-> [(Partition, a)] -> [Map Partition a]
forall a b. (a -> b) -> [a] -> [b]
map ([(Partition, a)] -> Map Partition a
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList ([(Partition, a)] -> Map Partition a)
-> ((Partition, a) -> [(Partition, a)])
-> (Partition, a)
-> Map Partition a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Partition, a) -> [(Partition, a)]
f) [(Partition, a)]
assocs))
_psCombination ::
forall a. (Eq a, AlgRing.C a) => (a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination :: forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination = (Partition -> Map Partition Rational)
-> (a -> Rational -> a) -> Spray a -> Map Partition a
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination Partition -> Map Partition Rational
mspInPSbasis
psCombination ::
forall a. (Eq a, AlgField.C a) => Spray a -> Map Partition a
psCombination :: forall a. (Eq a, C a) => Spray a -> Map Partition a
psCombination =
(a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination (\a
coef Rational
r -> a
coef a -> a -> a
forall a. C a => a -> a -> a
AlgRing.* Rational -> a
forall a. C a => Rational -> a
fromRational Rational
r)
psCombination' ::
forall a. (Eq a, AlgMod.C Rational a, AlgRing.C a)
=> Spray a -> Map Partition a
psCombination' :: forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
psCombination' = (a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination ((Rational -> a -> a) -> a -> Rational -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Rational -> a -> a
forall a v. C a v => a -> v -> v
(AlgMod.*>))
_hallInnerProduct ::
forall a b. (AlgRing.C b, AlgRing.C a)
=> (Spray b -> Map Partition b)
-> (a -> b -> b)
-> Spray b
-> Spray b
-> a
-> b
_hallInnerProduct :: forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct Spray b -> Map Partition b
psCombinationFunc a -> b -> b
multabFunc Spray b
spray1 Spray b
spray2 a
alpha =
[b] -> b
forall a. C a => [a] -> a
AlgAdd.sum ([b] -> b) -> [b] -> b
forall a b. (a -> b) -> a -> b
$ Map Partition b -> [b]
forall k a. Map k a -> [a]
DM.elems
(SimpleWhenMissing Partition b b
-> SimpleWhenMissing Partition b b
-> SimpleWhenMatched Partition b b b
-> Map Partition b
-> Map Partition b
-> Map Partition b
forall k a c b.
Ord k =>
SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
merge SimpleWhenMissing Partition b b
forall (f :: * -> *) k x y. Applicative f => WhenMissing f k x y
dropMissing SimpleWhenMissing Partition b b
forall (f :: * -> *) k x y. Applicative f => WhenMissing f k x y
dropMissing ((Partition -> b -> b -> b) -> SimpleWhenMatched Partition b b b
forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> z) -> WhenMatched f k x y z
zipWithMatched Partition -> b -> b -> b
f) Map Partition b
psCombo1 Map Partition b
psCombo2)
where
psCombo1 :: Map Partition b
psCombo1 = Spray b -> Map Partition b
psCombinationFunc Spray b
spray1 :: Map Partition b
psCombo2 :: Map Partition b
psCombo2 = Spray b -> Map Partition b
psCombinationFunc Spray b
spray2 :: Map Partition b
zlambda' :: Partition -> a
zlambda' :: Partition -> a
zlambda' Partition
lambda = Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Partition -> Int
zlambda Partition
lambda)
a -> a -> a
forall a. C a => a -> a -> a
AlgRing.* a
alpha a -> Integer -> a
forall a. C a => a -> Integer -> a
AlgRing.^ (Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda)
f :: Partition -> b -> b -> b
f :: Partition -> b -> b -> b
f Partition
lambda b
coeff1 b
coeff2 =
a -> b -> b
multabFunc (Partition -> a
zlambda' Partition
lambda) (b
coeff1 b -> b -> b
forall a. C a => a -> a -> a
AlgRing.* b
coeff2)
hallInnerProduct ::
forall a. (Eq a, AlgField.C a)
=> Spray a
-> Spray a
-> a
-> a
hallInnerProduct :: forall a. (Eq a, C a) => Spray a -> Spray a -> a -> a
hallInnerProduct = (Spray a -> Map Partition a)
-> (a -> a -> a) -> Spray a -> Spray a -> a -> a
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct Spray a -> Map Partition a
forall a. (Eq a, C a) => Spray a -> Map Partition a
psCombination a -> a -> a
forall a. C a => a -> a -> a
(AlgRing.*)
hallInnerProduct' ::
forall a. (Eq a, AlgMod.C Rational a, AlgRing.C a)
=> Spray a
-> Spray a
-> a
-> a
hallInnerProduct' :: forall a. (Eq a, C Rational a, C a) => Spray a -> Spray a -> a -> a
hallInnerProduct' = (Spray a -> Map Partition a)
-> (a -> a -> a) -> Spray a -> Spray a -> a -> a
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct Spray a -> Map Partition a
forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
psCombination' a -> a -> a
forall a. C a => a -> a -> a
(AlgRing.*)
hallInnerProduct'' ::
forall a. (Real a)
=> Spray a
-> Spray a
-> a
-> Rational
hallInnerProduct'' :: forall a. Real a => Spray a -> Spray a -> a -> Rational
hallInnerProduct'' Spray a
spray1 Spray a
spray2 a
alpha =
(QSpray -> Map Partition Rational)
-> (Rational -> Rational -> Rational)
-> QSpray
-> QSpray
-> Rational
-> Rational
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct
((Rational -> Rational -> Rational)
-> QSpray -> Map Partition Rational
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
(*)) Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
(*) QSpray
qspray1 QSpray
qspray2 (a -> Rational
forall a. Real a => a -> Rational
toRational a
alpha)
where
asQSpray :: Spray a -> QSpray
asQSpray :: Spray a -> QSpray
asQSpray = (a -> Rational) -> Spray a -> QSpray
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map a -> Rational
forall a. Real a => a -> Rational
toRational
qspray1 :: QSpray
qspray1 = Spray a -> QSpray
asQSpray Spray a
spray1
qspray2 :: QSpray
qspray2 = Spray a -> QSpray
asQSpray Spray a
spray2
hallInnerProduct''' ::
forall b. (Eq b, AlgField.C b, AlgMod.C (BaseRing b) b)
=> Spray b
-> Spray b
-> BaseRing b
-> b
hallInnerProduct''' :: forall b.
(Eq b, C b, C (BaseRing b) b) =>
Spray b -> Spray b -> BaseRing b -> b
hallInnerProduct''' = (HashMap Powers b -> Map Partition b)
-> (BaseRing b -> b -> b)
-> HashMap Powers b
-> HashMap Powers b
-> BaseRing b
-> b
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct HashMap Powers b -> Map Partition b
forall a. (Eq a, C a) => Spray a -> Map Partition a
psCombination BaseRing b -> b -> b
forall a v. C a v => a -> v -> v
(AlgMod.*>)
hallInnerProduct'''' ::
forall b. (Eq b, AlgRing.C b, AlgMod.C Rational b, AlgMod.C (BaseRing b) b)
=> Spray b
-> Spray b
-> BaseRing b
-> b
hallInnerProduct'''' :: forall b.
(Eq b, C b, C Rational b, C (BaseRing b) b) =>
Spray b -> Spray b -> BaseRing b -> b
hallInnerProduct'''' = (HashMap Powers b -> Map Partition b)
-> (BaseRing b -> b -> b)
-> HashMap Powers b
-> HashMap Powers b
-> BaseRing b
-> b
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct HashMap Powers b -> Map Partition b
forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
psCombination' BaseRing b -> b -> b
forall a v. C a v => a -> v -> v
(AlgMod.*>)
_symbolicHallInnerProduct ::
(Eq a, AlgRing.C a)
=> (Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
_symbolicHallInnerProduct :: forall a.
(Eq a, C a) =>
(Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
_symbolicHallInnerProduct Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a
func Spray a
spray1 Spray a
spray2 = Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a
func Spray (Spray a)
spray1' Spray (Spray a)
spray2' (Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
1)
where
spray1' :: Spray (Spray a)
spray1' = (a -> Spray a) -> Spray a -> Spray (Spray a)
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map a -> Spray a
forall a. (Eq a, C a) => a -> Spray a
constantSpray Spray a
spray1
spray2' :: Spray (Spray a)
spray2' = (a -> Spray a) -> Spray a -> Spray (Spray a)
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map a -> Spray a
forall a. (Eq a, C a) => a -> Spray a
constantSpray Spray a
spray2
symbolicHallInnerProduct ::
(Eq a, AlgField.C a) => Spray a -> Spray a -> Spray a
symbolicHallInnerProduct :: forall a. (Eq a, C a) => Spray a -> Spray a -> Spray a
symbolicHallInnerProduct =
(Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
forall a.
(Eq a, C a) =>
(Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
_symbolicHallInnerProduct
(
(Spray (Spray a) -> Map Partition (Spray a))
-> (Spray a -> Spray a -> Spray a)
-> Spray (Spray a)
-> Spray (Spray a)
-> Spray a
-> Spray a
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct
((Spray a -> Rational -> Spray a)
-> Spray (Spray a) -> Map Partition (Spray a)
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination (\Spray a
spray_a Rational
r -> Rational -> a
forall a. C a => Rational -> a
fromRational Rational
r BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
spray_a)) Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
(^*^)
)
symbolicHallInnerProduct' ::
(Eq a, AlgMod.C Rational (Spray a), AlgRing.C a)
=> Spray a -> Spray a -> Spray a
symbolicHallInnerProduct' :: forall a.
(Eq a, C Rational (Spray a), C a) =>
Spray a -> Spray a -> Spray a
symbolicHallInnerProduct' = (Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
forall a.
(Eq a, C a) =>
(Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a)
-> Spray a -> Spray a -> Spray a
_symbolicHallInnerProduct (Spray (Spray a) -> Spray (Spray a) -> Spray a -> Spray a
forall a. (Eq a, C Rational a, C a) => Spray a -> Spray a -> a -> a
hallInnerProduct')
symbolicHallInnerProduct'' :: forall a. Real a => Spray a -> Spray a -> QSpray
symbolicHallInnerProduct'' :: forall a. Real a => Spray a -> Spray a -> QSpray
symbolicHallInnerProduct'' Spray a
spray1 Spray a
spray2 =
(SimpleParametricQSpray -> Map Partition QSpray)
-> (QSpray -> QSpray -> QSpray)
-> SimpleParametricQSpray
-> SimpleParametricQSpray
-> QSpray
-> QSpray
forall a b.
(C b, C a) =>
(Spray b -> Map Partition b)
-> (a -> b -> b) -> Spray b -> Spray b -> a -> b
_hallInnerProduct
((QSpray -> Rational -> QSpray)
-> SimpleParametricQSpray -> Map Partition QSpray
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_psCombination (\QSpray
qspray Rational
r -> Rational
BaseRing QSpray
r BaseRing QSpray -> QSpray -> QSpray
forall b. FunctionLike b => BaseRing b -> b -> b
*^ QSpray
qspray)) QSpray -> QSpray -> QSpray
forall b. (FunctionLike b, C b) => b -> b -> b
(^*^)
SimpleParametricQSpray
qspray1' SimpleParametricQSpray
qspray2' (Int -> QSpray
qlone Int
1)
where
asQSpray :: Spray a -> QSpray
asQSpray :: Spray a -> QSpray
asQSpray = (a -> Rational) -> Spray a -> QSpray
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map a -> Rational
forall a. Real a => a -> Rational
toRational
qspray1' :: SimpleParametricQSpray
qspray1' = (Rational -> QSpray) -> QSpray -> SimpleParametricQSpray
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map Rational -> QSpray
forall a. (Eq a, C a) => a -> Spray a
constantSpray (Spray a -> QSpray
asQSpray Spray a
spray1)
qspray2' :: SimpleParametricQSpray
qspray2' = (Rational -> QSpray) -> QSpray -> SimpleParametricQSpray
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map Rational -> QSpray
forall a. (Eq a, C a) => a -> Spray a
constantSpray (Spray a -> QSpray
asQSpray Spray a
spray2)
cshPolynomial :: (AlgRing.C a, Eq a)
=> Int
-> Partition
-> Spray a
cshPolynomial :: forall a. (C a, Eq a) => Int -> Partition -> Spray a
cshPolynomial Int
n Partition
lambda
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"cshPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"cshPolynomial: invalid partition."
| Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
lambda = Spray a
forall a. C a => Spray a
unitSpray
| Int
llambda Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ((Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
forall {a}. (C a, Eq a) => Int -> Spray a
cshPolynomialK Partition
lambda)
where
llambda :: Int
llambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
cshPolynomialK :: Int -> Spray a
cshPolynomialK Int
k = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
msSprays
where
parts :: [Partition]
parts = Int -> [Partition]
partitions Int
k
msSprays :: [Spray a]
msSprays =
[Int -> Partition -> Spray a
forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomialUnsafe Int
n (Partition -> Partition
fromPartition Partition
part)
| Partition
part <- [Partition]
parts, Partition -> Int
partitionWidth Partition
part Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n]
pspInCSHbasis :: Partition -> Map Partition Rational
pspInCSHbasis :: Partition -> Map Partition Rational
pspInCSHbasis Partition
mu = [(Partition, Rational)] -> Map Partition Rational
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList ((Rational -> Partition -> (Partition, Rational))
-> [Rational] -> [Partition] -> [(Partition, Rational)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Rational -> Partition -> (Partition, Rational)
forall {b} {a}. b -> a -> (a, b)
f [Rational]
weights [Partition]
lambdas)
where
parts :: [Partition]
parts = Int -> [Partition]
partitions (Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
mu)
assoc :: Partition -> (Rational, Partition)
assoc Partition
kappa =
let kappa' :: Partition
kappa' = Partition -> Partition
fromPartition Partition
kappa in (Partition -> Partition -> Rational
eLambdaMu Partition
kappa' Partition
mu, Partition
kappa')
([Rational]
weights, [Partition]
lambdas) = [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Rational, Partition)] -> ([Rational], [Partition]))
-> [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. (a -> b) -> a -> b
$ ((Rational, Partition) -> Bool)
-> [(Rational, Partition)] -> [(Rational, Partition)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
/= Rational
0) (Rational -> Bool)
-> ((Rational, Partition) -> Rational)
-> (Rational, Partition)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational, Partition) -> Rational
forall a b. (a, b) -> a
fst) ((Partition -> (Rational, Partition))
-> [Partition] -> [(Rational, Partition)]
forall a b. (a -> b) -> [a] -> [b]
map Partition -> (Rational, Partition)
assoc [Partition]
parts)
f :: b -> a -> (a, b)
f b
weight a
lambda = (a
lambda, b
weight)
mspInCSHbasis :: Partition -> Map Partition Rational
mspInCSHbasis :: Partition -> Map Partition Rational
mspInCSHbasis Partition
mu = QSpray -> Map Partition Rational
forall a. Spray a -> Map Partition a
sprayToMap ([QSpray] -> QSpray
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [QSpray]
sprays)
where
psAssocs :: [(Partition, Rational)]
psAssocs = Map Partition Rational -> [(Partition, Rational)]
forall k a. Map k a -> [(k, a)]
DM.toList (Partition -> Map Partition Rational
mspInPSbasis Partition
mu)
sprays :: [QSpray]
sprays =
[Rational
BaseRing QSpray
c BaseRing QSpray -> QSpray -> QSpray
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Map Partition Rational -> QSpray
forall a. (Eq a, C a) => Map Partition a -> Spray a
comboToSpray (Partition -> Map Partition Rational
pspInCSHbasis Partition
lambda) | (Partition
lambda, Rational
c) <- [(Partition, Rational)]
psAssocs]
_cshCombination ::
forall a. (Eq a, AlgRing.C a)
=> (a -> Rational -> a) -> Spray a -> Map Partition a
_cshCombination :: forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_cshCombination = (Partition -> Map Partition Rational)
-> (a -> Rational -> a) -> Spray a -> Map Partition a
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination Partition -> Map Partition Rational
mspInCSHbasis
cshCombination ::
forall a. (Eq a, AlgField.C a) => Spray a -> Map Partition a
cshCombination :: forall a. (Eq a, C a) => Spray a -> Map Partition a
cshCombination =
(a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_cshCombination (\a
coef Rational
r -> a
coef a -> a -> a
forall a. C a => a -> a -> a
AlgRing.* Rational -> a
forall a. C a => Rational -> a
fromRational Rational
r)
cshCombination' ::
forall a. (Eq a, AlgMod.C Rational a, AlgRing.C a)
=> Spray a -> Map Partition a
cshCombination' :: forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
cshCombination' = (a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_cshCombination ((Rational -> a -> a) -> a -> Rational -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Rational -> a -> a
forall a v. C a v => a -> v -> v
(AlgMod.*>))
esPolynomial :: (AlgRing.C a, Eq a)
=> Int
-> Partition
-> Spray a
esPolynomial :: forall a. (C a, Eq a) => Int -> Partition -> Spray a
esPolynomial Int
n Partition
lambda
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"esPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"esPolynomial: invalid partition."
| Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
lambda = Spray a
forall a. C a => Spray a
unitSpray
| Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n Bool -> Bool -> Bool
|| (Int -> Bool) -> Partition -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
n) Partition
lambda = Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ((Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
forall {a}. (C a, Eq a) => Int -> Spray a
esPolynomialK Partition
lambda)
where
l :: Int
l = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
esPolynomialK :: Int -> Spray a
esPolynomialK Int
k = Int -> Partition -> Spray a
forall a. (C a, Eq a) => Int -> Partition -> Spray a
msPolynomialUnsafe Int
n (Int -> Int -> Partition
forall a. Int -> a -> [a]
replicate Int
k Int
1)
pspInESbasis :: Partition -> Map Partition Rational
pspInESbasis :: Partition -> Map Partition Rational
pspInESbasis Partition
mu = [(Partition, Rational)] -> Map Partition Rational
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList ((Rational -> Partition -> (Partition, Rational))
-> [Rational] -> [Partition] -> [(Partition, Rational)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Rational -> Partition -> (Partition, Rational)
forall {b} {a}. b -> a -> (a, b)
f [Rational]
weights [Partition]
lambdas)
where
wmu :: Int
wmu = Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
mu
parts :: [Partition]
parts = Int -> [Partition]
partitions Int
wmu
e :: Int
e = Int
wmu Int -> Int -> Int
forall a. Num a => a -> a -> a
- Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
mu
e_is_even :: Bool
e_is_even = Int -> Bool
forall a. Integral a => a -> Bool
even Int
e
negateIf :: Rational -> Rational
negateIf = if Bool
e_is_even then Rational -> Rational
forall a. a -> a
id else Rational -> Rational
forall a. Num a => a -> a
negate
pair :: Partition -> (Rational, Partition)
pair Partition
kappa = (Rational -> Rational
negateIf (Partition -> Partition -> Rational
eLambdaMu Partition
kappa Partition
mu), Partition
kappa)
([Rational]
weights, [Partition]
lambdas) = [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Rational, Partition)] -> ([Rational], [Partition]))
-> [(Rational, Partition)] -> ([Rational], [Partition])
forall a b. (a -> b) -> a -> b
$ ((Rational, Partition) -> Bool)
-> [(Rational, Partition)] -> [(Rational, Partition)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
/= Rational
0) (Rational -> Bool)
-> ((Rational, Partition) -> Rational)
-> (Rational, Partition)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rational, Partition) -> Rational
forall a b. (a, b) -> a
fst)
[let lambda :: Partition
lambda = Partition -> Partition
fromPartition Partition
part in Partition -> (Rational, Partition)
pair Partition
lambda | Partition
part <- [Partition]
parts]
f :: b -> a -> (a, b)
f b
weight a
lambda = (a
lambda, b
weight)
mspInESbasis :: Partition -> Map Partition Rational
mspInESbasis :: Partition -> Map Partition Rational
mspInESbasis Partition
mu = QSpray -> Map Partition Rational
forall a. Spray a -> Map Partition a
sprayToMap ([QSpray] -> QSpray
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [QSpray]
sprays)
where
psAssocs :: [(Partition, Rational)]
psAssocs = Map Partition Rational -> [(Partition, Rational)]
forall k a. Map k a -> [(k, a)]
DM.toList (Partition -> Map Partition Rational
mspInPSbasis Partition
mu)
sprays :: [QSpray]
sprays =
[Rational
BaseRing QSpray
c BaseRing QSpray -> QSpray -> QSpray
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Map Partition Rational -> QSpray
forall a. (Eq a, C a) => Map Partition a -> Spray a
comboToSpray (Partition -> Map Partition Rational
pspInESbasis Partition
lambda) | (Partition
lambda, Rational
c) <- [(Partition, Rational)]
psAssocs]
_esCombination ::
forall a. (Eq a, AlgRing.C a)
=> (a -> Rational -> a) -> Spray a -> Map Partition a
_esCombination :: forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_esCombination = (Partition -> Map Partition Rational)
-> (a -> Rational -> a) -> Spray a -> Map Partition a
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination Partition -> Map Partition Rational
mspInESbasis
esCombination ::
forall a. (Eq a, AlgField.C a) => Spray a -> Map Partition a
esCombination :: forall a. (Eq a, C a) => Spray a -> Map Partition a
esCombination =
(a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_esCombination (\a
coef Rational
r -> a
coef a -> a -> a
forall a. C a => a -> a -> a
AlgRing.* Rational -> a
forall a. C a => Rational -> a
fromRational Rational
r)
esCombination' ::
forall a. (Eq a, AlgMod.C Rational a, AlgRing.C a)
=> Spray a -> Map Partition a
esCombination' :: forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
esCombination' = (a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_esCombination ((Rational -> a -> a) -> a -> Rational -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Rational -> a -> a
forall a v. C a v => a -> v -> v
(AlgMod.*>))
cshInSchurBasis :: Int -> Partition -> Map Partition Rational
cshInSchurBasis :: Int -> Partition -> Map Partition Rational
cshInSchurBasis Int
n Partition
mu =
(Partition -> Rational -> Bool)
-> Map Partition Rational -> Map Partition Rational
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
DM.filterWithKey (\Partition
k Rational
_ -> Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n)
((Partition -> Partition)
-> Map Partition Rational -> Map Partition Rational
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
DM.mapKeys Partition -> Partition
fromPartition Map Partition Rational
kNumbers)
where
kNumbers :: Map Partition Rational
kNumbers = (Int -> Rational) -> Map Partition Int -> Map Partition Rational
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map Int -> Rational
forall a. Real a => a -> Rational
toRational (Partition -> Map Partition Int
kostkaNumbersWithGivenMu (Partition -> Partition
mkPartition Partition
mu))
_schurCombination ::
forall a. (Eq a, AlgRing.C a)
=> (a -> Rational -> a) -> Spray a -> Map Partition a
_schurCombination :: forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_schurCombination a -> Rational -> a
func Spray a
spray =
if a
constantTerm a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
forall a. C a => a
AlgAdd.zero
then Map Partition a
schurMap
else Partition -> a -> Map Partition a -> Map Partition a
forall k a. Ord k => k -> a -> Map k a -> Map k a
insert [] a
constantTerm Map Partition a
schurMap
where
constantTerm :: a
constantTerm = Spray a -> a
forall a. C a => Spray a -> a
getConstantTerm Spray a
spray
assocs :: [(Partition, a)]
assocs =
Map Partition a -> [(Partition, a)]
forall k a. Map k a -> [(k, a)]
DM.toList (Map Partition a -> [(Partition, a)])
-> Map Partition a -> [(Partition, a)]
forall a b. (a -> b) -> a -> b
$ (a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_cshCombination a -> Rational -> a
func (Spray a
spray Spray a -> BaseRing (Spray a) -> Spray a
forall b. FunctionLike b => b -> BaseRing b -> b
<+ (a -> a
forall a. C a => a -> a
AlgAdd.negate a
constantTerm))
f :: (Partition, a) -> [(Partition, a)]
f :: (Partition, a) -> [(Partition, a)]
f (Partition
lambda, a
coeff) =
((Partition, Rational) -> (Partition, a))
-> [(Partition, Rational)] -> [(Partition, a)]
forall a b. (a -> b) -> [a] -> [b]
map ((Rational -> a) -> (Partition, Rational) -> (Partition, a)
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second (a -> Rational -> a
func a
coeff)) (Map Partition Rational -> [(Partition, Rational)]
forall k a. Map k a -> [(k, a)]
DM.toList Map Partition Rational
schurCombo)
where
schurCombo :: Map Partition Rational
schurCombo = Int -> Partition -> Map Partition Rational
cshInSchurBasis (Spray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables Spray a
spray) Partition
lambda
schurMap :: Map Partition a
schurMap = (a -> Bool) -> Map Partition a -> Map Partition a
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
forall a. C a => a
AlgAdd.zero)
((a -> a -> a) -> [Map Partition a] -> Map Partition a
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
unionsWith a -> a -> a
forall a. C a => a -> a -> a
(AlgAdd.+) (((Partition, a) -> Map Partition a)
-> [(Partition, a)] -> [Map Partition a]
forall a b. (a -> b) -> [a] -> [b]
map ([(Partition, a)] -> Map Partition a
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList ([(Partition, a)] -> Map Partition a)
-> ((Partition, a) -> [(Partition, a)])
-> (Partition, a)
-> Map Partition a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Partition, a) -> [(Partition, a)]
f) [(Partition, a)]
assocs))
schurCombination ::
forall a. (Eq a, AlgField.C a) => Spray a -> Map Partition a
schurCombination :: forall a. (Eq a, C a) => Spray a -> Map Partition a
schurCombination =
(a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_schurCombination (\a
coef Rational
r -> a
coef a -> a -> a
forall a. C a => a -> a -> a
AlgRing.* Rational -> a
forall a. C a => Rational -> a
fromRational Rational
r)
schurCombination' ::
forall a. (Eq a, AlgMod.C Rational a, AlgRing.C a)
=> Spray a -> Map Partition a
schurCombination' :: forall a. (Eq a, C Rational a, C a) => Spray a -> Map Partition a
schurCombination' = (a -> Rational -> a) -> Spray a -> Map Partition a
forall a.
(Eq a, C a) =>
(a -> Rational -> a) -> Spray a -> Map Partition a
_schurCombination ((Rational -> a -> a) -> a -> Rational -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Rational -> a -> a
forall a v. C a v => a -> v -> v
(AlgMod.*>))
kostkaNumbers ::
Int
-> Rational
-> Map Partition (Map Partition Rational)
kostkaNumbers :: Int -> Rational -> Map Partition (Map Partition Rational)
kostkaNumbers Int
weight Rational
alpha
| Int
weight Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Map Partition (Map Partition Rational)
forall a. HasCallStack => [Char] -> a
error [Char]
"kostkaNumbers: negative weight."
| Int
weight Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
Partition
-> Map Partition Rational -> Map Partition (Map Partition Rational)
forall k a. k -> a -> Map k a
DM.singleton [] (Partition -> Rational -> Map Partition Rational
forall k a. k -> a -> Map k a
DM.singleton [] Rational
1)
| Bool
otherwise =
Int
-> Int
-> Rational
-> Char
-> Map Partition (Map Partition Rational)
forall a.
C a =>
Int -> Int -> a -> Char -> Map Partition (Map Partition a)
_kostkaNumbers Int
weight Int
weight Rational
alpha Char
'P'
symbolicKostkaNumbers :: Int -> Map Partition (Map Partition RatioOfQSprays)
symbolicKostkaNumbers :: Int -> Map Partition (Map Partition RatioOfQSprays)
symbolicKostkaNumbers Int
weight
| Int
weight Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Map Partition (Map Partition RatioOfQSprays)
forall a. HasCallStack => [Char] -> a
error [Char]
"symbolicKostkaNumbers: negative weight."
| Int
weight Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
Partition
-> Map Partition RatioOfQSprays
-> Map Partition (Map Partition RatioOfQSprays)
forall k a. k -> a -> Map k a
DM.singleton [] (Partition -> RatioOfQSprays -> Map Partition RatioOfQSprays
forall k a. k -> a -> Map k a
DM.singleton [] RatioOfQSprays
forall a. (C a, Eq a) => RatioOfSprays a
unitRatioOfSprays)
| Bool
otherwise =
Int -> Int -> Char -> Map Partition (Map Partition RatioOfQSprays)
forall a.
(Eq a, C a) =>
Int
-> Int -> Char -> Map Partition (Map Partition (RatioOfSprays a))
_symbolicKostkaNumbers Int
weight Int
weight Char
'P'
msPolynomialsInJackBasis ::
forall a. (Eq a, AlgField.C a)
=> a -> Char -> Int -> Int -> Map Partition (Map Partition a)
msPolynomialsInJackBasis :: forall a.
(Eq a, C a) =>
a -> Char -> Int -> Int -> Map Partition (Map Partition a)
msPolynomialsInJackBasis a
alpha Char
which Int
n Int
weight =
[(Partition, Map Partition a)] -> Map Partition (Map Partition a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList ([Partition] -> [Map Partition a] -> [(Partition, Map Partition a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
lambdas [Int -> Map Partition a
maps Int
i | Int
i <- [Int
1 .. [Partition] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Partition]
lambdas]])
where
(Matrix a
matrix, [Partition]
lambdas) = Int -> Int -> a -> Char -> (Matrix a, [Partition])
forall a.
(Eq a, C a) =>
Int -> Int -> a -> Char -> (Matrix a, [Partition])
_inverseKostkaMatrix Int
n Int
weight a
alpha Char
which
maps :: Int -> Map Partition a
maps Int
i = (a -> Bool) -> Map Partition a -> Map Partition a
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
forall a. C a => a
AlgAdd.zero)
([(Partition, a)] -> Map Partition a
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList ([Partition] -> [a] -> [(Partition, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
lambdas (Vector a -> [a]
forall a. Vector a -> [a]
V.toList (Int -> Matrix a -> Vector a
forall a. Int -> Matrix a -> Vector a
getRow Int
i Matrix a
matrix))))
msPolynomialsInJackSymbolicBasis ::
(Eq a, AlgField.C a)
=> Char -> Int -> Int -> Map Partition (Map Partition (RatioOfSprays a))
msPolynomialsInJackSymbolicBasis :: forall a.
(Eq a, C a) =>
Char
-> Int -> Int -> Map Partition (Map Partition (RatioOfSprays a))
msPolynomialsInJackSymbolicBasis Char
which Int
n Int
weight =
[(Partition, Map Partition (RatioOfSprays a))]
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList ([Partition]
-> [Map Partition (RatioOfSprays a)]
-> [(Partition, Map Partition (RatioOfSprays a))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
lambdas [Int -> Map Partition (RatioOfSprays a)
maps Int
i | Int
i <- [Int
1 .. [Partition] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Partition]
lambdas]])
where
(Matrix (RatioOfSprays a)
matrix, [Partition]
lambdas) = Int -> Int -> Char -> (Matrix (RatioOfSprays a), [Partition])
forall a.
(Eq a, C a) =>
Int -> Int -> Char -> (Matrix (RatioOfSprays a), [Partition])
_inverseSymbolicKostkaMatrix Int
n Int
weight Char
which
maps :: Int -> Map Partition (RatioOfSprays a)
maps Int
i = (RatioOfSprays a -> Bool)
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (RatioOfSprays a -> RatioOfSprays a -> Bool
forall a. Eq a => a -> a -> Bool
/= RatioOfSprays a
forall a. (C a, Eq a) => RatioOfSprays a
zeroRatioOfSprays)
([(Partition, RatioOfSprays a)] -> Map Partition (RatioOfSprays a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList ([Partition] -> [RatioOfSprays a] -> [(Partition, RatioOfSprays a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
lambdas (Vector (RatioOfSprays a) -> [RatioOfSprays a]
forall a. Vector a -> [a]
V.toList (Int -> Matrix (RatioOfSprays a) -> Vector (RatioOfSprays a)
forall a. Int -> Matrix a -> Vector a
getRow Int
i Matrix (RatioOfSprays a)
matrix))))
jackCombination ::
(Eq a, AlgField.C a)
=> a
-> Char
-> Spray a
-> Map Partition a
jackCombination :: forall a. (Eq a, C a) => a -> Char -> Spray a -> Map Partition a
jackCombination a
alpha Char
which Spray a
spray =
if Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'J', Char
'C', Char
'P', Char
'Q'])
then [Char] -> Map Partition a
forall a. HasCallStack => [Char] -> a
error [Char]
"jackCombination: invalid character, must be 'J', 'C', 'P' or 'Q'."
else
(Partition -> Map Partition a)
-> (a -> a -> a) -> Spray a -> Map Partition a
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination
(\Partition
lambda -> (IntMap (Map Partition (Map Partition a))
combos IntMap (Map Partition (Map Partition a))
-> Int -> Map Partition (Map Partition a)
forall a. IntMap a -> Int -> a
IM.! (Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
lambda)) Map Partition (Map Partition a) -> Partition -> Map Partition a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
lambda)
a -> a -> a
forall a. C a => a -> a -> a
(AlgRing.*) Spray a
spray
where
weights :: Partition
weights = (Int -> Bool) -> Partition -> Partition
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) ((Seq Int -> Int) -> [Seq Int] -> Partition
forall a b. (a -> b) -> [a] -> [b]
map Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum (Spray a -> [Seq Int]
forall a. Spray a -> [Seq Int]
allExponents Spray a
spray))
n :: Int
n = Spray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables Spray a
spray
combos :: IntMap (Map Partition (Map Partition a))
combos =
[(Int, Map Partition (Map Partition a))]
-> IntMap (Map Partition (Map Partition a))
forall a. [(Int, a)] -> IntMap a
IM.fromList
(Partition
-> [Map Partition (Map Partition a)]
-> [(Int, Map Partition (Map Partition a))]
forall a b. [a] -> [b] -> [(a, b)]
zip Partition
weights ((Int -> Map Partition (Map Partition a))
-> Partition -> [Map Partition (Map Partition a)]
forall a b. (a -> b) -> [a] -> [b]
map (a -> Char -> Int -> Int -> Map Partition (Map Partition a)
forall a.
(Eq a, C a) =>
a -> Char -> Int -> Int -> Map Partition (Map Partition a)
msPolynomialsInJackBasis a
alpha Char
which Int
n) Partition
weights))
jackSymbolicCombination ::
Char
-> QSpray
-> Map Partition RatioOfQSprays
jackSymbolicCombination :: Char -> QSpray -> Map Partition RatioOfQSprays
jackSymbolicCombination Char
which QSpray
qspray =
if Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'J', Char
'C', Char
'P', Char
'Q'])
then [Char] -> Map Partition RatioOfQSprays
forall a. HasCallStack => [Char] -> a
error [Char]
"jackSymbolicCombination: invalid character, must be 'J', 'C', 'P' or 'Q'."
else (Partition -> Map Partition RatioOfQSprays)
-> (RatioOfQSprays -> RatioOfQSprays -> RatioOfQSprays)
-> ParametricQSpray
-> Map Partition RatioOfQSprays
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination
(\Partition
lambda -> (IntMap (Map Partition (Map Partition RatioOfQSprays))
combos IntMap (Map Partition (Map Partition RatioOfQSprays))
-> Int -> Map Partition (Map Partition RatioOfQSprays)
forall a. IntMap a -> Int -> a
IM.! (Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
lambda)) Map Partition (Map Partition RatioOfQSprays)
-> Partition -> Map Partition RatioOfQSprays
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
lambda)
RatioOfQSprays -> RatioOfQSprays -> RatioOfQSprays
forall a. C a => a -> a -> a
(AlgRing.*) ((Rational -> RatioOfQSprays) -> QSpray -> ParametricQSpray
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map Rational -> RatioOfQSprays
forall a. (Eq a, C a) => a -> RatioOfSprays a
constantRatioOfSprays QSpray
qspray)
where
weights :: Partition
weights = (Int -> Bool) -> Partition -> Partition
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) ((Seq Int -> Int) -> [Seq Int] -> Partition
forall a b. (a -> b) -> [a] -> [b]
map Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum (QSpray -> [Seq Int]
forall a. Spray a -> [Seq Int]
allExponents QSpray
qspray))
n :: Int
n = QSpray -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables QSpray
qspray
combos :: IntMap (Map Partition (Map Partition RatioOfQSprays))
combos =
[(Int, Map Partition (Map Partition RatioOfQSprays))]
-> IntMap (Map Partition (Map Partition RatioOfQSprays))
forall a. [(Int, a)] -> IntMap a
IM.fromList
(Partition
-> [Map Partition (Map Partition RatioOfQSprays)]
-> [(Int, Map Partition (Map Partition RatioOfQSprays))]
forall a b. [a] -> [b] -> [(a, b)]
zip Partition
weights ((Int -> Map Partition (Map Partition RatioOfQSprays))
-> Partition -> [Map Partition (Map Partition RatioOfQSprays)]
forall a b. (a -> b) -> [a] -> [b]
map (Char -> Int -> Int -> Map Partition (Map Partition RatioOfQSprays)
forall a.
(Eq a, C a) =>
Char
-> Int -> Int -> Map Partition (Map Partition (RatioOfSprays a))
msPolynomialsInJackSymbolicBasis Char
which Int
n) Partition
weights))
jackSymbolicCombination' ::
(Eq a, AlgField.C a)
=> Char
-> ParametricSpray a
-> Map Partition (RatioOfSprays a)
jackSymbolicCombination' :: forall a.
(Eq a, C a) =>
Char -> ParametricSpray a -> Map Partition (RatioOfSprays a)
jackSymbolicCombination' Char
which ParametricSpray a
spray =
if Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'J', Char
'C', Char
'P', Char
'Q'])
then [Char] -> Map Partition (RatioOfSprays a)
forall a. HasCallStack => [Char] -> a
error [Char]
"jackSymbolicCombination': invalid character, must be 'J', 'C', 'P' or 'Q'."
else (Partition -> Map Partition (RatioOfSprays a))
-> (RatioOfSprays a -> RatioOfSprays a -> RatioOfSprays a)
-> ParametricSpray a
-> Map Partition (RatioOfSprays a)
forall a b.
(Eq a, C a) =>
(Partition -> Map Partition b)
-> (a -> b -> a) -> Spray a -> Map Partition a
_symmPolyCombination
(\Partition
lambda -> (IntMap (Map Partition (Map Partition (RatioOfSprays a)))
combos IntMap (Map Partition (Map Partition (RatioOfSprays a)))
-> Int -> Map Partition (Map Partition (RatioOfSprays a))
forall a. IntMap a -> Int -> a
IM.! (Partition -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum Partition
lambda)) Map Partition (Map Partition (RatioOfSprays a))
-> Partition -> Map Partition (RatioOfSprays a)
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
lambda)
RatioOfSprays a -> RatioOfSprays a -> RatioOfSprays a
forall a. C a => a -> a -> a
(AlgRing.*) ParametricSpray a
spray
where
weights :: Partition
weights = (Int -> Bool) -> Partition -> Partition
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) ((Seq Int -> Int) -> [Seq Int] -> Partition
forall a b. (a -> b) -> [a] -> [b]
map Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum (ParametricSpray a -> [Seq Int]
forall a. Spray a -> [Seq Int]
allExponents ParametricSpray a
spray))
n :: Int
n = ParametricSpray a -> Int
forall b. FunctionLike b => b -> Int
numberOfVariables ParametricSpray a
spray
combos :: IntMap (Map Partition (Map Partition (RatioOfSprays a)))
combos =
[(Int, Map Partition (Map Partition (RatioOfSprays a)))]
-> IntMap (Map Partition (Map Partition (RatioOfSprays a)))
forall a. [(Int, a)] -> IntMap a
IM.fromList
(Partition
-> [Map Partition (Map Partition (RatioOfSprays a))]
-> [(Int, Map Partition (Map Partition (RatioOfSprays a)))]
forall a b. [a] -> [b] -> [(a, b)]
zip Partition
weights ((Int -> Map Partition (Map Partition (RatioOfSprays a)))
-> Partition -> [Map Partition (Map Partition (RatioOfSprays a))]
forall a b. (a -> b) -> [a] -> [b]
map (Char
-> Int -> Int -> Map Partition (Map Partition (RatioOfSprays a))
forall a.
(Eq a, C a) =>
Char
-> Int -> Int -> Map Partition (Map Partition (RatioOfSprays a))
msPolynomialsInJackSymbolicBasis Char
which Int
n) Partition
weights))
kostkaFoulkesPolynomial ::
(Eq a, AlgRing.C a) => Partition -> Partition -> Spray a
kostkaFoulkesPolynomial :: forall a. (Eq a, C a) => Partition -> Partition -> Spray a
kostkaFoulkesPolynomial Partition
lambda Partition
mu
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"kostkaFoulkesPolynomial: invalid partition."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
mu) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"kostkaFoulkesPolynomial: invalid partition."
| Bool
otherwise =
Partition -> Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Partition -> Spray a
_kostkaFoulkesPolynomial Partition
lambda Partition
mu
kostkaFoulkesPolynomial' :: Partition -> Partition -> QSpray
kostkaFoulkesPolynomial' :: Partition -> Partition -> QSpray
kostkaFoulkesPolynomial' = Partition -> Partition -> QSpray
forall a. (Eq a, C a) => Partition -> Partition -> Spray a
kostkaFoulkesPolynomial
hallLittlewoodPolynomial ::
(Eq a, AlgRing.C a)
=> Int
-> Partition
-> Char
-> SimpleParametricSpray a
hallLittlewoodPolynomial :: forall a.
(Eq a, C a) =>
Int -> Partition -> Char -> SimpleParametricSpray a
hallLittlewoodPolynomial Int
n Partition
lambda Char
which
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = [Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"hallLittlewoodPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"hallLittlewoodPolynomial: invalid partition."
| Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'P', Char
'Q']) =
[Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"hallLittlewoodPolynomial: last argument must be 'P' or 'Q'."
| Partition -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Partition
lambda = SimpleParametricSpray a
forall a. C a => Spray a
unitSpray
| Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n = SimpleParametricSpray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise = [SimpleParametricSpray a] -> SimpleParametricSpray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [SimpleParametricSpray a]
sprays
where
coeffs :: Map Partition (Spray a)
coeffs = Char -> Partition -> Map Partition (Spray a)
forall a.
(Eq a, C a) =>
Char -> Partition -> Map Partition (Spray a)
_hallLittlewoodPolynomialsInSchurBasis Char
which Partition
lambda
sprays :: [SimpleParametricSpray a]
sprays =
Map Partition (SimpleParametricSpray a)
-> [SimpleParametricSpray a]
forall k a. Map k a -> [a]
DM.elems
((Partition -> Spray a -> SimpleParametricSpray a)
-> Map Partition (Spray a)
-> Map Partition (SimpleParametricSpray a)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey
(\Partition
mu Spray a
c -> BaseRing (SimpleParametricSpray a)
Spray a
c BaseRing (SimpleParametricSpray a)
-> SimpleParametricSpray a -> SimpleParametricSpray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ ((a -> Spray a) -> Spray a -> SimpleParametricSpray a
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map a -> Spray a
forall a. (Eq a, C a) => a -> Spray a
constantSpray (Int -> Partition -> Spray a
forall a. (Eq a, C a) => Int -> Partition -> Spray a
schurPol Int
n Partition
mu))) Map Partition (Spray a)
coeffs)
hallLittlewoodPolynomial' ::
Int
-> Partition
-> Char
-> SimpleParametricQSpray
hallLittlewoodPolynomial' :: Int -> Partition -> Char -> SimpleParametricQSpray
hallLittlewoodPolynomial' = Int -> Partition -> Char -> SimpleParametricQSpray
forall a.
(Eq a, C a) =>
Int -> Partition -> Char -> SimpleParametricSpray a
hallLittlewoodPolynomial
transitionsSchurToHallLittlewood ::
Int
-> Char
-> Map Partition (Map Partition (Spray Int))
transitionsSchurToHallLittlewood :: Int -> Char -> Map Partition (Map Partition (Spray Int))
transitionsSchurToHallLittlewood Int
weight Char
which
| Int
weight Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 =
[Char] -> Map Partition (Map Partition (Spray Int))
forall a. HasCallStack => [Char] -> a
error [Char]
"transitionsHallLittlewoodToSchur: negative weight."
| Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'P', Char
'Q']) =
[Char] -> Map Partition (Map Partition (Spray Int))
forall a. HasCallStack => [Char] -> a
error [Char]
"transitionsHallLittlewoodToSchur: the character must be 'P' or 'Q'."
| Bool
otherwise =
Char -> Int -> Map Partition (Map Partition (Spray Int))
forall a.
(Eq a, C a) =>
Char -> Int -> Map Partition (Map Partition (Spray a))
_transitionMatrixHallLittlewoodSchur Char
which Int
weight
skewHallLittlewoodPolynomial :: (Eq a, AlgRing.C a)
=> Int
-> Partition
-> Partition
-> Char
-> SimpleParametricSpray a
skewHallLittlewoodPolynomial :: forall a.
(Eq a, C a) =>
Int -> Partition -> Partition -> Char -> SimpleParametricSpray a
skewHallLittlewoodPolynomial Int
n Partition
lambda Partition
mu Char
which
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewHallLittlewoodPolynomial: negative number of variables."
| Bool -> Bool
not (Partition -> Partition -> Bool
isSkewPartition Partition
lambda Partition
mu) =
[Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewHallLittlewoodPolynomial: invalid skew partition."
| Bool -> Bool
not (Char
which Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'P', Char
'Q']) =
[Char] -> SimpleParametricSpray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewHallLittlewoodPolynomial: the character must be 'P' or 'Q'."
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
if Partition
lambda Partition -> Partition -> Bool
forall a. Eq a => a -> a -> Bool
== Partition
mu then SimpleParametricSpray a
forall a. C a => Spray a
unitSpray else SimpleParametricSpray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise =
if Char
which Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'P'
then Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
forall a.
(Eq a, C a) =>
Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodP Int
n (Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
lambda) (Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
mu)
else Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
forall a.
(Eq a, C a) =>
Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodQ Int
n (Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
lambda) (Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
mu)
skewHallLittlewoodPolynomial' ::
Int
-> Partition
-> Partition
-> Char
-> SimpleParametricQSpray
skewHallLittlewoodPolynomial' :: Int -> Partition -> Partition -> Char -> SimpleParametricQSpray
skewHallLittlewoodPolynomial' = Int -> Partition -> Partition -> Char -> SimpleParametricQSpray
forall a.
(Eq a, C a) =>
Int -> Partition -> Partition -> Char -> SimpleParametricSpray a
skewHallLittlewoodPolynomial
flaggedSchurPol ::
(Eq a, AlgRing.C a)
=> Partition
-> [Int]
-> [Int]
-> Spray a
flaggedSchurPol :: forall a.
(Eq a, C a) =>
Partition -> Partition -> Partition -> Spray a
flaggedSchurPol Partition
lambda Partition
as Partition
bs
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSchurPol: invalid partition."
| Bool -> Bool
not (Partition -> Bool
forall a. Eq a => [a] -> Bool
allSame [Int
llambda, Int
las, Int
lbs]) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSchurPol: the partition and the lists of lower bounds and upper bounds must have the same length."
| Int
llambda Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
Spray a
forall a. C a => Spray a
unitSpray
| Bool -> Bool
not (Partition -> Bool
isIncreasing Partition
as) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSchurPol: the list of lower bounds is not increasing."
| Bool -> Bool
not (Partition -> Bool
isIncreasing Partition
bs) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSchurPol: the list of upper bounds is not increasing."
| (Bool -> Bool) -> [Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True) ((Int -> Int -> Bool) -> Partition -> Partition -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>) Partition
as Partition
bs) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSchurPol: lower bounds must be smaller than upper bounds."
| Bool
otherwise = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
sprays
where
llambda :: Int
llambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
las :: Int
las = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
as
lbs :: Int
lbs = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
bs
tableaux :: [[Partition]]
tableaux = Partition -> Partition -> Partition -> [[Partition]]
flaggedSemiStandardYoungTableaux Partition
lambda Partition
as Partition
bs
monomial :: [Partition] -> Spray a
monomial [Partition]
tableau =
[Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([Spray a] -> Spray a) -> [Spray a] -> Spray a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' [Int
1 ..] ([Partition] -> Partition
tableauWeight [Partition]
tableau)
sprays :: [Spray a]
sprays = ([Partition] -> Spray a) -> [[Partition]] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map [Partition] -> Spray a
forall {a}. (Eq a, C a) => [Partition] -> Spray a
monomial [[Partition]]
tableaux
flaggedSchurPol' ::
Partition
-> [Int]
-> [Int]
-> QSpray
flaggedSchurPol' :: Partition -> Partition -> Partition -> QSpray
flaggedSchurPol' = Partition -> Partition -> Partition -> QSpray
forall a.
(Eq a, C a) =>
Partition -> Partition -> Partition -> Spray a
flaggedSchurPol
flaggedSkewSchurPol ::
(Eq a, AlgRing.C a)
=> Partition
-> Partition
-> [Int]
-> [Int]
-> Spray a
flaggedSkewSchurPol :: forall a.
(Eq a, C a) =>
Partition -> Partition -> Partition -> Partition -> Spray a
flaggedSkewSchurPol Partition
lambda Partition
mu Partition
as Partition
bs
| Bool -> Bool
not (Partition -> Partition -> Bool
isSkewPartition Partition
lambda Partition
mu) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSkewSchurPol: invalid skew partition."
| Bool -> Bool
not (Partition -> Bool
forall a. Eq a => [a] -> Bool
allSame [Int
llambda, Int
las, Int
lbs]) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSkewSchurPol: the outer partition and the lists of lower bounds and upper bounds must have the same length."
| Bool -> Bool
not (Partition -> Bool
isIncreasing Partition
as) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSkewSchurPol: the list of lower bounds is not increasing."
| Bool -> Bool
not (Partition -> Bool
isIncreasing Partition
bs) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSkewSchurPol: the list of upper bounds is not increasing."
| (Bool -> Bool) -> [Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True) ((Int -> Int -> Bool) -> Partition -> Partition -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
(>) Partition
as Partition
bs) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"flaggedSkewSchurPol: lower bounds must be smaller than upper bounds."
| Partition
lambda Partition -> Partition -> Bool
forall a. Eq a => a -> a -> Bool
== Partition
mu =
Spray a
forall a. C a => Spray a
unitSpray
| Bool
otherwise = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
sprays
where
llambda :: Int
llambda = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
las :: Int
las = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
as
lbs :: Int
lbs = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
bs
tableaux :: [[(Int, Partition)]]
tableaux = Partition
-> Partition -> Partition -> Partition -> [[(Int, Partition)]]
flaggedSkewTableaux Partition
lambda Partition
mu Partition
as Partition
bs
monomial :: [(Int, Partition)] -> Spray a
monomial [(Int, Partition)]
tableau =
[Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([Spray a] -> Spray a) -> [Spray a] -> Spray a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' [Int
1 ..] ([(Int, Partition)] -> Partition
skewTableauWeight [(Int, Partition)]
tableau)
sprays :: [Spray a]
sprays = ([(Int, Partition)] -> Spray a)
-> [[(Int, Partition)]] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map [(Int, Partition)] -> Spray a
forall {a}. (Eq a, C a) => [(Int, Partition)] -> Spray a
monomial [[(Int, Partition)]]
tableaux
flaggedSkewSchurPol' ::
Partition
-> Partition
-> [Int]
-> [Int]
-> QSpray
flaggedSkewSchurPol' :: Partition -> Partition -> Partition -> Partition -> QSpray
flaggedSkewSchurPol' = Partition -> Partition -> Partition -> Partition -> QSpray
forall a.
(Eq a, C a) =>
Partition -> Partition -> Partition -> Partition -> Spray a
flaggedSkewSchurPol
factorialSchurPol ::
(Eq a, AlgRing.C a)
=> Int
-> Partition
-> [a]
-> Spray a
factorialSchurPol :: forall a. (Eq a, C a) => Int -> Partition -> [a] -> Spray a
factorialSchurPol Int
n Partition
lambda [a]
y
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"factorialSchurPol: negative number of variables."
| Bool -> Bool
not (Partition -> Bool
_isPartition Partition
lambda) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"factorialSchurPol: invalid integer partition."
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Spray a
forall a. C a => Spray a
unitSpray else Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise =
[Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
sprays
where
l :: Int
l = Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda
tableaux :: [[Partition]]
tableaux = Int -> Partition -> [[Partition]]
semiStandardYoungTableaux Int
n (Partition -> Partition
toPartition Partition
lambda)
lones :: [Spray a]
lones = [Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
i | Int
i <- [Int
1 .. Int
n]]
idx :: [Partition] -> Int -> Int -> (Int, Int)
idx [Partition]
tableau Int
i Int
j =
let row :: Partition
row = [Partition]
tableau [Partition] -> Int -> Partition
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
a :: Int
a = Partition
row Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
in (Int
a, Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i)
factor :: [Partition] -> Int -> Int -> Spray a
factor [Partition]
tableau Int
i Int
j =
let (Int
a, Int
k) = [Partition] -> Int -> Int -> (Int, Int)
idx [Partition]
tableau Int
i Int
j in [Spray a]
lones [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Spray a -> BaseRing (Spray a) -> Spray a
forall b. FunctionLike b => b -> BaseRing b -> b
<+ [a]
y [a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
i_ :: Partition
i_ = [Int
1 .. Int
l]
ij_ :: [(Int, Int)]
ij_ = [(Int
i, Int
j) | Int
i <- Partition
i_, Int
j <- [Int
1 .. Partition
lambda Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)]]
factors :: [Partition] -> [Spray a]
factors [Partition]
tableau = [[Partition] -> Int -> Int -> Spray a
factor [Partition]
tableau Int
i Int
j | (Int
i, Int
j) <- [(Int, Int)]
ij_]
spray :: [Partition] -> Spray a
spray [Partition]
tableau = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([Partition] -> [Spray a]
factors [Partition]
tableau)
sprays :: [Spray a]
sprays = ([Partition] -> Spray a) -> [[Partition]] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map [Partition] -> Spray a
spray [[Partition]]
tableaux
factorialSchurPol' ::
Int
-> Partition
-> [Rational]
-> QSpray
factorialSchurPol' :: Int -> Partition -> [Rational] -> QSpray
factorialSchurPol' = Int -> Partition -> [Rational] -> QSpray
forall a. (Eq a, C a) => Int -> Partition -> [a] -> Spray a
factorialSchurPol
skewFactorialSchurPol ::
(Eq a, AlgRing.C a)
=> Int
-> Partition
-> Partition
-> IntMap a
-> Spray a
skewFactorialSchurPol :: forall a.
(Eq a, C a) =>
Int -> Partition -> Partition -> IntMap a -> Spray a
skewFactorialSchurPol Int
n Partition
lambda Partition
mu IntMap a
y
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewFactorialSchurPol: negative number of variables."
| Bool -> Bool
not (Partition -> Partition -> Bool
isSkewPartition Partition
lambda Partition
mu) =
[Char] -> Spray a
forall a. HasCallStack => [Char] -> a
error [Char]
"skewFactorialSchurPol: invalid skew integer partition."
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 =
if Partition
lambda Partition -> Partition -> Bool
forall a. Eq a => a -> a -> Bool
== Partition
mu then Spray a
forall a. C a => Spray a
unitSpray else Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
| Bool
otherwise =
[Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
sprays
where
skewPartition :: SkewPartition
skewPartition = (Partition, Partition) -> SkewPartition
mkSkewPartition (Partition -> Partition
toPartition Partition
lambda, Partition -> Partition
toPartition Partition
mu)
skewTableaux :: [SkewTableau Int]
skewTableaux = Int -> SkewPartition -> [SkewTableau Int]
semiStandardSkewTableaux Int
n SkewPartition
skewPartition
getSkewTableau :: SkewTableau a -> [(Int, [a])]
getSkewTableau (SkewTableau [(Int, [a])]
x) = [(Int, [a])]
x
lones :: [Spray a]
lones = [Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
i | Int
i <- [Int
1 .. Int
n]]
idx :: [(Int, Partition)] -> Int -> Int -> (Int, Int)
idx [(Int, Partition)]
tableau Int
i Int
j =
let (Int
offset, Partition
entries) = [(Int, Partition)]
tableau [(Int, Partition)] -> Int -> (Int, Partition)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
a :: Int
a = Partition
entries Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
in (Int
a, Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
offset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i)
factor :: [(Int, Partition)] -> Int -> Int -> Spray a
factor [(Int, Partition)]
tableau Int
i Int
j =
let (Int
a, Int
k) = [(Int, Partition)] -> Int -> Int -> (Int, Int)
idx [(Int, Partition)]
tableau Int
i Int
j in [Spray a]
lones [Spray a] -> Int -> Spray a
forall a. HasCallStack => [a] -> Int -> a
!! (Int
aInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Spray a -> BaseRing (Spray a) -> Spray a
forall b. FunctionLike b => b -> BaseRing b -> b
<+ IntMap a
y IntMap a -> Int -> a
forall a. IntMap a -> Int -> a
IM.! Int
k
i_ :: Partition
i_ = [Int
1 .. Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda]
ij_ :: [(a, t a)] -> [(Int, Int)]
ij_ [(a, t a)]
tableau =
[(Int
i, Int
j) | Int
i <- Partition
i_, Int
j <- [Int
1 .. t a -> Int
forall a. t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ((a, t a) -> t a
forall a b. (a, b) -> b
snd ([(a, t a)]
tableau [(a, t a)] -> Int -> (a, t a)
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)))]]
factors :: [(Int, Partition)] -> [Spray a]
factors [(Int, Partition)]
tableau = [[(Int, Partition)] -> Int -> Int -> Spray a
factor [(Int, Partition)]
tableau Int
i Int
j | (Int
i, Int
j) <- [(Int, Partition)] -> [(Int, Int)]
forall {t :: * -> *} {a} {a}.
Foldable t =>
[(a, t a)] -> [(Int, Int)]
ij_ [(Int, Partition)]
tableau]
spray :: SkewTableau Int -> Spray a
spray SkewTableau Int
tableau = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([(Int, Partition)] -> [Spray a]
factors (SkewTableau Int -> [(Int, Partition)]
forall {a}. SkewTableau a -> [(Int, [a])]
getSkewTableau SkewTableau Int
tableau))
sprays :: [Spray a]
sprays = (SkewTableau Int -> Spray a) -> [SkewTableau Int] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map SkewTableau Int -> Spray a
spray [SkewTableau Int]
skewTableaux
skewFactorialSchurPol' ::
Int
-> Partition
-> Partition
-> IntMap Rational
-> QSpray
skewFactorialSchurPol' :: Int -> Partition -> Partition -> IntMap Rational -> QSpray
skewFactorialSchurPol' = Int -> Partition -> Partition -> IntMap Rational -> QSpray
forall a.
(Eq a, C a) =>
Int -> Partition -> Partition -> IntMap a -> Spray a
skewFactorialSchurPol