{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Math.Algebra.Jack.Internal
( Partition
, jackCoeffP
, jackCoeffQ
, jackCoeffC
, jackSymbolicCoeffC
, jackSymbolicCoeffPinv
, jackSymbolicCoeffQinv
, _betaratio
, _betaRatioOfSprays
, _isPartition
, _N
, _fromInt
, skewSchurLRCoefficients
, isSkewPartition
, sprayToMap
, comboToSpray
, _kostkaNumbers
, _inverseKostkaMatrix
, _symbolicKostkaNumbers
, _inverseSymbolicKostkaMatrix
, _kostkaFoulkesPolynomial
, _hallLittlewoodPolynomialsInSchurBasis
, _transitionMatrixHallLittlewoodSchur
, skewHallLittlewoodP
, skewHallLittlewoodQ
, flaggedSemiStandardYoungTableaux
, tableauWeight
, isIncreasing
, flaggedSkewTableaux
, skewTableauWeight
)
where
import Prelude
hiding ((*), (+), (-), (/), (^), (*>), product, sum, fromIntegral, fromInteger, recip)
import qualified Prelude as P
import Algebra.Additive ( (+), (-), sum )
import qualified Algebra.Additive as AlgAdd
import Algebra.Field ( (/), recip )
import qualified Algebra.Field as AlgField
import Algebra.Module ( (*>) )
import Algebra.Ring ( (*), product, one
, (^), fromInteger
)
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 (
nub
, foldl1'
, uncons
)
import Data.List.Extra (
unsnoc
)
import Data.List.Index ( iconcatMap )
import Data.Map.Strict ( Map )
import qualified Data.Map.Strict as DM
import Data.Matrix (
Matrix
, nrows
, getCol
, getRow
, minorMatrix
, (<|>)
, (<->)
, rowVector
, colVector
, getElem
, fromLists
)
import Data.Maybe ( fromJust, isJust )
import Data.Sequence (
Seq
, (|>)
, (<|)
, (><)
, Seq ( (:<|) )
)
import qualified Data.Sequence as S
import Data.Tuple.Extra ( fst3 )
import qualified Data.Vector as V
import Math.Algebra.Hspray (
RatioOfSprays, (%:%), (%//%), (%/%)
, unitRatioOfSprays
, zeroRatioOfSprays
, asRatioOfSprays
, Spray, (.^)
, Powers (..)
, SimpleParametricSpray
, zeroSpray
, isZeroSpray
, lone, lone', unitSpray
, sumOfSprays
, productOfSprays
, FunctionLike (..)
)
import Math.Combinat.Partitions.Integer (
fromPartition
, dualPartition
, partitions
, dominates
, partitionWidth
, toPartitionUnsafe
, dropTailingZeros
)
import qualified Math.Combinat.Partitions.Integer as MCP
import Math.Combinat.Partitions.Skew (
SkewPartition
, mkSkewPartition
, skewPartitionElements
)
import Math.Combinat.Tableaux.GelfandTsetlin (
GT
, kostkaGelfandTsetlinPatterns
)
import Math.Combinat.Tableaux.LittlewoodRichardson ( _lrRule )
type Partition = [Int]
gtPatternDiagonals :: GT -> (Int, [MCP.Partition])
gtPatternDiagonals :: GT -> (Int, [Partition])
gtPatternDiagonals GT
pattern = (Int
corner, [Int -> Partition
diagonal Int
j | Int
j <- [Int
1 .. Int
l]])
where
l :: Int
l = GT -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length GT
pattern Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1
corner :: Int
corner = GT
pattern GT -> Int -> Partition
forall a. HasCallStack => [a] -> Int -> a
!! Int
l Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
0
diagonal :: Int -> Partition
diagonal Int
j =
(Partition -> Partition
toPartitionUnsafe (Partition -> Partition)
-> (Partition -> Partition) -> Partition -> Partition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Partition -> Partition
dropTailingZeros)
[GT
pattern GT -> Int -> Partition
forall a. HasCallStack => [a] -> Int -> a
!! Int
r Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
c | (Int
r, Int
c) <- Partition -> Partition -> [(Int, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
j .. Int
l] [Int
0 .. Int
j]]
gtPatternToTableau :: GT -> [Seq Int]
gtPatternToTableau :: GT -> [Seq Int]
gtPatternToTableau GT
pattern =
if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
then Seq (Seq Int) -> [Seq Int]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList (Seq (Seq Int) -> [Seq Int]) -> Seq (Seq Int) -> [Seq Int]
forall a b. (a -> b) -> a -> b
$ Int -> Seq (Seq Int) -> Seq (Seq Int)
go Int
0 Seq (Seq Int)
forall {a}. Seq (Seq a)
startingTableau
else [Int -> Int -> Seq Int
forall a. Int -> a -> Seq a
S.replicate Int
corner Int
1]
where
(Int
corner, [Partition]
diagonals) = GT -> (Int, [Partition])
gtPatternDiagonals GT
pattern
diagonals' :: [Partition]
diagonals' = Partition -> Partition
toPartitionUnsafe [Int
corner] Partition -> [Partition] -> [Partition]
forall a. a -> [a] -> [a]
: [Partition]
diagonals
l :: Int
l = [Partition] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Partition]
diagonals Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1
lambda :: Partition
lambda = [Partition]
diagonals [Partition] -> Int -> Partition
forall a. HasCallStack => [a] -> Int -> a
!! Int
l
m :: Int
m = Partition -> Int
partitionWidth Partition
lambda
startingTableau :: Seq (Seq a)
startingTableau = Int -> Seq a -> Seq (Seq a)
forall a. Int -> a -> Seq a
S.replicate Int
m Seq a
forall a. Seq a
S.Empty
zippedDiagonals :: [(Partition, Partition)]
zippedDiagonals = [Partition] -> [Partition] -> [(Partition, Partition)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Partition]
diagonals [Partition]
diagonals'
skewPartition :: Int -> SkewPartition
skewPartition Int
i = (Partition, Partition) -> SkewPartition
mkSkewPartition ([(Partition, Partition)]
zippedDiagonals [(Partition, Partition)] -> Int -> (Partition, Partition)
forall a. HasCallStack => [a] -> Int -> a
!! Int
i)
go :: Int -> Seq (Seq Int) -> Seq (Seq Int)
go Int
i Seq (Seq Int)
tableau
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Seq (Seq Int) -> Seq (Seq Int)
go Int
1 ((Seq Int -> Seq Int) -> Int -> Seq (Seq Int) -> Seq (Seq Int)
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' ((Seq Int -> Seq Int -> Seq Int) -> Seq Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Seq Int -> Seq Int
forall a. Seq a -> Seq a -> Seq a
(><) (Int -> Int -> Seq Int
forall a. Int -> a -> Seq a
S.replicate Int
corner Int
1)) Int
0 Seq (Seq Int)
tableau)
| Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
2 = Seq (Seq Int)
tableau
| Bool
otherwise =
Int -> Seq (Seq Int) -> Seq (Seq Int)
go (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) (Int -> Seq (Seq Int) -> SkewPartition -> Seq (Seq Int)
growTableau (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Seq (Seq Int)
tableau (Int -> SkewPartition
skewPartition (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)))
growTableau :: Int -> Seq (Seq Int) -> SkewPartition -> Seq (Seq Int)
growTableau :: Int -> Seq (Seq Int) -> SkewPartition -> Seq (Seq Int)
growTableau Int
j Seq (Seq Int)
tableau SkewPartition
skewPart =
((Int, Int) -> Seq (Seq Int) -> Seq (Seq Int))
-> Seq (Seq Int) -> [(Int, Int)] -> Seq (Seq Int)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
DF.foldr (\(Int
i, Int
_) -> (Seq Int -> Seq Int) -> Int -> Seq (Seq Int) -> Seq (Seq Int)
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' ((Seq Int -> Int -> Seq Int) -> Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
(|>) Int
j) (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)) Seq (Seq Int)
tableau
(SkewPartition -> [(Int, Int)]
skewPartitionElements SkewPartition
skewPart)
semiStandardTableauxWithGivenShapeAndWeight ::
Partition -> Partition -> [[Seq Int]]
semiStandardTableauxWithGivenShapeAndWeight :: Partition -> Partition -> [[Seq Int]]
semiStandardTableauxWithGivenShapeAndWeight Partition
lambda Partition
mu =
if Partition
lambda' Partition -> Partition -> Bool
`dominates` Partition
mu'
then (GT -> [Seq Int]) -> [GT] -> [[Seq Int]]
forall a b. (a -> b) -> [a] -> [b]
map GT -> [Seq Int]
gtPatternToTableau (Partition -> Partition -> [GT]
kostkaGelfandTsetlinPatterns Partition
lambda' Partition
mu')
else []
where
lambda' :: Partition
lambda' = Partition -> Partition
toPartitionUnsafe Partition
lambda
mu' :: Partition
mu' = Partition -> Partition
toPartitionUnsafe Partition
mu
flaggedSemiStandardYoungTableaux :: Partition -> [Int] -> [Int] -> [[[Int]]]
flaggedSemiStandardYoungTableaux :: Partition -> Partition -> Partition -> [GT]
flaggedSemiStandardYoungTableaux Partition
lambda Partition
as Partition
bs =
Partition -> Partition -> Int -> [GT]
worker (Int -> Partition
forall a. a -> [a]
repeat Int
0) Partition
lambda Int
0
where
worker :: Partition -> Partition -> Int -> [GT]
worker Partition
_ [] Int
_ = [[]]
worker Partition
prevRow (Int
s:Partition
ss) Int
i
= [ (Partition
rPartition -> GT -> GT
forall a. a -> [a] -> [a]
:GT
rs)
| Partition
r <- Int -> Int -> Int -> Partition -> GT
row (Partition
bs Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i) Int
s (Partition
as Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i) Partition
prevRow
, GT
rs <- Partition -> Partition -> Int -> [GT]
worker ((Int -> Int) -> Partition -> Partition
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Partition
r) Partition
ss (Int
i Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1) ]
row :: Int -> Int -> Int -> [Int] -> [[Int]]
row :: Int -> Int -> Int -> Partition -> GT
row Int
n Int
len Int
prev Partition
xxs =
if Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then [[]]
else [ (Int
jInt -> Partition -> Partition
forall a. a -> [a] -> [a]
:Partition
js) | Int
j <- [Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
x Int
prev .. Int
n], Partition
js <- Int -> Int -> Int -> Partition -> GT
row Int
n (Int
lenInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
j Partition
xs ]
where
(Int
x, Partition
xs) = Maybe (Int, Partition) -> (Int, Partition)
forall a. HasCallStack => Maybe a -> a
fromJust (Partition -> Maybe (Int, Partition)
forall a. [a] -> Maybe (a, [a])
uncons Partition
xxs)
tableauWeight :: [[Int]] -> [Int]
tableauWeight :: GT -> Partition
tableauWeight GT
tableau = [Int -> Int
count Int
i | Int
i <- [Int
1 .. Int
m]]
where
x :: Partition
x = GT -> Partition
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat GT
tableau
m :: Int
m = Partition -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum Partition
x
count :: Int -> Int
count Int
i = Partition -> Int
forall a. C a => [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
i) | Int
k <- Partition
x]
flaggedSkewTableaux ::
Partition -> Partition -> [Int] -> [Int] -> [[(Int,[Int])]]
flaggedSkewTableaux :: Partition
-> Partition -> Partition -> Partition -> [[(Int, Partition)]]
flaggedSkewTableaux Partition
lambda Partition
mu Partition
as Partition
bs = Partition
-> Partition
-> Partition
-> Partition
-> Int
-> [[(Int, Partition)]]
worker Partition
uus Partition
vvs Partition
dds (Int -> Partition
forall a. a -> [a]
repeat Int
1) Int
0
where
uus :: Partition
uus = Partition
mu Partition -> Partition -> Partition
forall a. [a] -> [a] -> [a]
++ (Int -> Int -> Partition
forall a. Int -> a -> [a]
replicate (Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda Int -> Int -> Int
forall a. C a => a -> a -> a
- Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
mu) Int
0)
vvs :: Partition
vvs = (Int -> Int -> Int) -> Partition -> Partition -> Partition
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) Partition
lambda Partition
uus
dds :: Partition
dds = Partition -> Partition
_diffSequence Partition
uus
_diffSequence :: [Int] -> [Int]
_diffSequence :: Partition -> Partition
_diffSequence = Partition -> Partition
forall {a}. C a => [a] -> [a]
go where
go :: [a] -> [a]
go (a
x:ys :: [a]
ys@(a
y:[a]
_)) = (a
xa -> a -> a
forall a. C a => a -> a -> a
-a
y) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
ys
go [a
x] = [a
x]
go [] = []
worker :: [Int] -> [Int] -> [Int] -> [Int] -> Int -> [[(Int,[Int])]]
worker :: Partition
-> Partition
-> Partition
-> Partition
-> Int
-> [[(Int, Partition)]]
worker (Int
u:Partition
us) (Int
v:Partition
vs) (Int
d:Partition
ds) Partition
lb Int
i
= [ (Int
u, Partition
this)(Int, Partition) -> [(Int, Partition)] -> [(Int, Partition)]
forall a. a -> [a] -> [a]
:[(Int, Partition)]
rest
| Partition
this <- Int -> Int -> Int -> Partition -> GT
row (Partition
bs Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i) Int
v (Partition
as Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i) Partition
lb
, let lb' :: Partition
lb' = (Int -> Int -> Partition
forall a. Int -> a -> [a]
replicate Int
d Int
1 Partition -> Partition -> Partition
forall a. [a] -> [a] -> [a]
++ (Int -> Int) -> Partition -> Partition
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Partition
this)
, [(Int, Partition)]
rest <- Partition
-> Partition
-> Partition
-> Partition
-> Int
-> [[(Int, Partition)]]
worker Partition
us Partition
vs Partition
ds Partition
lb' (Int
i Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)]
worker [] Partition
_ Partition
_ Partition
_ Int
_ = [ [] ]
worker (Int
_:Partition
_) [] Partition
_ Partition
_ Int
_ = [ [] ]
worker (Int
_:Partition
_) (Int
_:Partition
_) [] Partition
_ Int
_ = [ [] ]
row :: Int -> Int -> Int -> [Int] -> [[Int]]
row :: Int -> Int -> Int -> Partition -> GT
row Int
n Int
len Int
prev Partition
xxs =
if Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then [[]]
else [ (Int
jInt -> Partition -> Partition
forall a. a -> [a] -> [a]
:Partition
js) | Int
j <- [Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
x Int
prev .. Int
n], Partition
js <- Int -> Int -> Int -> Partition -> GT
row Int
n (Int
lenInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Int
j Partition
xs ]
where
(Int
x, Partition
xs) = Maybe (Int, Partition) -> (Int, Partition)
forall a. HasCallStack => Maybe a -> a
fromJust (Partition -> Maybe (Int, Partition)
forall a. [a] -> Maybe (a, [a])
uncons Partition
xxs)
skewTableauWeight :: [(Int, [Int])] -> [Int]
skewTableauWeight :: [(Int, Partition)] -> Partition
skewTableauWeight [(Int, Partition)]
skewT = [Int -> Int
count Int
i | Int
i <- [Int
1 .. Int
m]]
where
(Partition
_, GT
entries) = [(Int, Partition)] -> (Partition, GT)
forall a b. [(a, b)] -> ([a], [b])
unzip [(Int, Partition)]
skewT
x :: Partition
x = GT -> Partition
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat GT
entries
m :: Int
m = Partition -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum Partition
x
count :: Int -> Int
count Int
i = Partition -> Int
forall a. C a => [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
i) | Int
k <- Partition
x]
isIncreasing :: [Int] -> Bool
isIncreasing :: Partition -> Bool
isIncreasing Partition
s =
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Partition
s Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Partition
s Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
iInt -> Int -> Int
forall a. C 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
s Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
2]]
isDecreasing :: Seq Int -> Bool
isDecreasing :: Seq Int -> Bool
isDecreasing Seq Int
s =
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Seq Int
s Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Seq Int
s Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) | Int
i <- [Int
0 .. Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
s Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
2]]
cartesianProduct :: Seq Int -> [Seq Int]
cartesianProduct :: Seq Int -> [Seq Int]
cartesianProduct (Seq Int
S.Empty) = []
cartesianProduct (Int
i:<|Seq Int
is)
| Seq Int -> Bool
forall a. Seq a -> Bool
S.null Seq Int
is = [Int -> Seq Int
forall a. a -> Seq a
S.singleton Int
j | Int
j <- [Int
i, Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1 .. Int
0]]
| Bool
otherwise = [Int
j Int -> Seq Int -> Seq Int
forall a. a -> Seq a -> Seq a
<| Seq Int
s | Int
j <- [Int
i, Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1 .. Int
0], Seq Int
s <- [Seq Int]
previous]
where
previous :: [Seq Int]
previous = Seq Int -> [Seq Int]
cartesianProduct Seq Int
is
horizontalStrip :: Seq Int -> Seq Int -> Bool
horizontalStrip :: Seq Int -> Seq Int -> Bool
horizontalStrip Seq Int
lambda Seq Int
mu = (Int -> Bool) -> Seq Int -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Int -> Partition -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int
0, Int
1]) Seq Int
theta'
where
lambda' :: Seq Int
lambda' = Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList (Partition -> Seq Int) -> Partition -> Seq Int
forall a b. (a -> b) -> a -> b
$ Partition -> Partition
_dualPartition (Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList Seq Int
lambda)
mu' :: Seq Int
mu' = Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList (Partition -> Seq Int) -> Partition -> Seq Int
forall a b. (a -> b) -> a -> b
$ Partition -> Partition
_dualPartition (Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList Seq Int
mu)
mu'' :: Seq Int
mu'' = Seq Int
mu' Seq Int -> Seq Int -> Seq Int
forall a. Seq a -> Seq a -> Seq a
>< (Int -> Int -> Seq Int
forall a. Int -> a -> Seq a
S.replicate (Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
lambda' Int -> Int -> Int
forall a. C a => a -> a -> a
- Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
mu') Int
0)
theta' :: Seq Int
theta' = (Int -> Int -> Int) -> Seq Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
S.zipWith (-) Seq Int
lambda' Seq Int
mu''
columnStrictTableau :: [Seq Int] -> Bool
columnStrictTableau :: [Seq Int] -> Bool
columnStrictTableau [Seq Int]
tableau =
[Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and ((Seq Int -> Seq Int -> Bool) -> [Seq Int] -> [Seq Int] -> [Bool]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Seq Int -> Seq Int -> Bool
horizontalStrip [Seq Int]
tableau [Seq Int]
tail_tableau)
where tail_tableau :: [Seq Int]
tail_tableau = Int -> [Seq Int] -> [Seq Int]
forall a. Int -> [a] -> [a]
drop Int
1 [Seq Int]
tableau
_paths :: Int -> Seq Int -> Seq Int -> [[Seq Int]]
_paths :: Int -> Seq Int -> Seq Int -> [[Seq Int]]
_paths Int
n Seq Int
lambda Seq Int
mu = ([Seq Int] -> Bool) -> [[Seq Int]] -> [[Seq Int]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Seq Int] -> Bool
columnStrictTableau [[Seq Int]]
tableaux
where
mu' :: Seq Int
mu' = Seq Int
mu Seq Int -> Seq Int -> Seq Int
forall a. Seq a -> Seq a -> Seq a
>< (Int -> Int -> Seq Int
forall a. Int -> a -> Seq a
S.replicate (Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
lambda Int -> Int -> Int
forall a. C a => a -> a -> a
- Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
mu) Int
0)
diffs :: Seq Int
diffs = (Int -> Int -> Int) -> Seq Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
S.zipWith (-) Seq Int
lambda Seq Int
mu'
grid :: [Seq Int]
grid = Seq Int -> [Seq Int]
cartesianProduct Seq Int
diffs
kappas :: [Seq Int]
kappas = (Seq Int -> Bool) -> [Seq Int] -> [Seq Int]
forall a. (a -> Bool) -> [a] -> [a]
filter Seq Int -> Bool
isDecreasing [(Int -> Int -> Int) -> Seq Int -> Seq Int -> Seq Int
forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
S.zipWith Int -> Int -> Int
forall a. C a => a -> a -> a
(+) Seq Int
kappa Seq Int
mu' | Seq Int
kappa <- [Seq Int]
grid]
combos :: GT
combos = Int -> Int -> Int -> GT
combinations Int
0 ([Seq Int] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Seq Int]
kappas Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1) (Int
nInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)
where
combinations :: Int -> Int -> Int -> [[Int]]
combinations :: Int -> Int -> Int -> GT
combinations Int
a Int
b Int
m
| Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [[]]
| Int
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = [[Int
i] | Int
i <- [Int
a .. Int
b]]
| Bool
otherwise =
[Int
i Int -> Partition -> Partition
forall a. a -> [a] -> [a]
: Partition
combo | Int
i <- [Int
a .. Int
b], Partition
combo <- Int -> Int -> Int -> GT
combinations Int
i Int
b (Int
mInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)]
tableaux :: [[Seq Int]]
tableaux =
(Partition -> [Seq Int]) -> GT -> [[Seq Int]]
forall a b. (a -> b) -> [a] -> [b]
map (\Partition
combo -> Seq Int
lambda Seq Int -> [Seq Int] -> [Seq Int]
forall a. a -> [a] -> [a]
: ((Int -> Seq Int) -> Partition -> [Seq Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Seq Int] -> Int -> Seq Int
forall a. HasCallStack => [a] -> Int -> a
(!!) [Seq Int]
kappas) Partition
combo) [Seq Int] -> [Seq Int] -> [Seq Int]
forall a. [a] -> [a] -> [a]
++ [Seq Int
mu']) GT
combos
psi_lambda_mu :: forall a. (Eq a, AlgRing.C a)
=> Seq Int -> Seq Int -> Spray a
psi_lambda_mu :: forall a. (Eq a, C a) => Seq Int -> Seq Int -> Spray a
psi_lambda_mu Seq Int
lambda Seq Int
mu = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays [Spray a]
sprays
where
range :: Partition
range = [Int
1 .. Seq Int
lambda Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` Int
0]
pair :: Int -> (Int, Int)
pair Int
j = (
Int
1 Int -> Int -> Int
forall a. C a => a -> a -> a
+ Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum ((Int -> Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
k -> Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j)) Seq Int
lambda)
, Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum ((Int -> Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
k -> Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j)) Seq Int
mu)
)
pairs :: [(Int, Int)]
pairs = ((Int, Int) -> Bool) -> [(Int, Int)] -> [(Int, Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Int
l, Int
m) -> Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
m) ((Int -> (Int, Int)) -> Partition -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map Int -> (Int, Int)
pair Partition
range)
t :: Int -> Spray a
t = Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
1
sprays :: [Spray a]
sprays = ((Int, Int) -> Spray a) -> [(Int, Int)] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
_, Int
m) -> a
BaseRing (Spray a)
forall a. C a => a
AlgRing.one BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> Spray a -> Spray a
forall a. C a => a -> a
AlgAdd.negate (Int -> Spray a
t Int
m)) [(Int, Int)]
pairs
phi_lambda_mu :: forall a. (Eq a, AlgRing.C a)
=> Seq Int -> Seq Int -> Spray a
phi_lambda_mu :: forall a. (Eq a, C a) => Seq Int -> Seq Int -> Spray a
phi_lambda_mu Seq Int
lambda Seq Int
mu = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays [Spray a]
sprays
where
range :: Partition
range = [Int
1 .. Seq Int
lambda Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` Int
0]
pair :: Int -> (Int, Int)
pair Int
j = (
Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum ((Int -> Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
k -> Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j)) Seq Int
lambda)
, Int
1 Int -> Int -> Int
forall a. C a => a -> a -> a
+ Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum ((Int -> Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> Seq a -> Seq b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
k -> Bool -> Int
forall a. Enum a => a -> Int
fromEnum (Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
j)) Seq Int
mu)
)
pairs :: [(Int, Int)]
pairs = ((Int, Int) -> Bool) -> [(Int, Int)] -> [(Int, Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Int
l, Int
m) -> Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
m) ((Int -> (Int, Int)) -> Partition -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map Int -> (Int, Int)
pair Partition
range)
t :: Int -> Spray a
t = Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
1
sprays :: [Spray a]
sprays = ((Int, Int) -> Spray a) -> [(Int, Int)] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
m, Int
_) -> a
BaseRing (Spray a)
forall a. C a => a
AlgRing.one BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> Spray a -> Spray a
forall a. C a => a -> a
AlgAdd.negate (Int -> Spray a
t Int
m)) [(Int, Int)]
pairs
skewHallLittlewoodP :: forall a. (Eq a, AlgRing.C a)
=> Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodP :: forall a.
(Eq a, C a) =>
Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodP Int
n Seq Int
lambda Seq Int
mu =
[Spray (Spray a)] -> Spray (Spray a)
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [[Spray (Spray a)] -> Spray (Spray a)
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([Spray (Spray a)] -> Spray (Spray a))
-> [Spray (Spray a)] -> Spray (Spray a)
forall a b. (a -> b) -> a -> b
$ [Seq Int] -> [Spray (Spray a)]
sprays ([Seq Int] -> [Seq Int]
forall a. [a] -> [a]
reverse [Seq Int]
path) | [Seq Int]
path <- [[Seq Int]]
paths]
where
paths :: [[Seq Int]]
paths = Int -> Seq Int -> Seq Int -> [[Seq Int]]
_paths Int
n Seq Int
lambda Seq Int
mu
lones :: [Int -> Spray (Spray a)]
lones = [Int -> Int -> Spray (Spray a)
forall a. C a => Int -> Int -> Spray a
lone' Int
i | Int
i <- [Int
1 .. Int
n]]
sprays :: [Seq Int] -> [Spray (Spray a)]
sprays [Seq Int]
nu =
[Seq Int -> Seq Int -> Spray a
forall a. (Eq a, C a) => Seq Int -> Seq Int -> Spray a
psi_lambda_mu Seq Int
next_nu_i Seq Int
nu_i BaseRing (Spray (Spray a)) -> Spray (Spray a) -> Spray (Spray a)
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Int -> Spray (Spray a)
lone_i (Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum Seq Int
next_nu_i Int -> Int -> Int
forall a. C a => a -> a -> a
- Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum Seq Int
nu_i)
| (Seq Int
next_nu_i, Seq Int
nu_i, Int -> Spray (Spray a)
lone_i) <- [Seq Int]
-> [Seq Int]
-> [Int -> Spray (Spray a)]
-> [(Seq Int, Seq Int, Int -> Spray (Spray a))]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (Int -> [Seq Int] -> [Seq Int]
forall a. Int -> [a] -> [a]
drop Int
1 [Seq Int]
nu) [Seq Int]
nu [Int -> Spray (Spray a)]
lones]
skewHallLittlewoodQ :: forall a. (Eq a, AlgRing.C a)
=> Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodQ :: forall a.
(Eq a, C a) =>
Int -> Seq Int -> Seq Int -> SimpleParametricSpray a
skewHallLittlewoodQ Int
n Seq Int
lambda Seq Int
mu =
[Spray (Spray a)] -> Spray (Spray a)
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [[Spray (Spray a)] -> Spray (Spray a)
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays ([Spray (Spray a)] -> Spray (Spray a))
-> [Spray (Spray a)] -> Spray (Spray a)
forall a b. (a -> b) -> a -> b
$ [Seq Int] -> [Spray (Spray a)]
sprays ([Seq Int] -> [Seq Int]
forall a. [a] -> [a]
reverse [Seq Int]
path) | [Seq Int]
path <- [[Seq Int]]
paths]
where
paths :: [[Seq Int]]
paths = Int -> Seq Int -> Seq Int -> [[Seq Int]]
_paths Int
n Seq Int
lambda Seq Int
mu
lones :: [Int -> Spray (Spray a)]
lones = [Int -> Int -> Spray (Spray a)
forall a. C a => Int -> Int -> Spray a
lone' Int
i | Int
i <- [Int
1 .. Int
n]]
sprays :: [Seq Int] -> [Spray (Spray a)]
sprays [Seq Int]
nu =
[Seq Int -> Seq Int -> Spray a
forall a. (Eq a, C a) => Seq Int -> Seq Int -> Spray a
phi_lambda_mu Seq Int
next_nu_i Seq Int
nu_i BaseRing (Spray (Spray a)) -> Spray (Spray a) -> Spray (Spray a)
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Int -> Spray (Spray a)
lone_i (Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum Seq Int
next_nu_i Int -> Int -> Int
forall a. C a => a -> a -> a
- Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum Seq Int
nu_i)
| (Seq Int
next_nu_i, Seq Int
nu_i, Int -> Spray (Spray a)
lone_i) <- [Seq Int]
-> [Seq Int]
-> [Int -> Spray (Spray a)]
-> [(Seq Int, Seq Int, Int -> Spray (Spray a))]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (Int -> [Seq Int] -> [Seq Int]
forall a. Int -> [a] -> [a]
drop Int
1 [Seq Int]
nu) [Seq Int]
nu [Int -> Spray (Spray a)]
lones]
charge :: Seq Int -> Int
charge :: Seq Int -> Int
charge Seq Int
w = if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then Int
0 else Seq Int -> Int
forall a. Num a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
DF.sum Seq Int
indices' Int -> Int -> Int
forall a. C a => a -> a -> a
+ Seq Int -> Int
charge Seq Int
w'
where
l :: Int
l = Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
w
n :: Int
n = Seq Int -> Int
forall a. Ord a => Seq a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
DF.maximum Seq Int
w
(Seq Int
positions', Seq Int
indices') =
Int -> Seq Int -> Seq Int -> (Seq Int, Seq Int)
go Int
1 (Int -> Seq Int
forall a. a -> Seq a
S.singleton (Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Seq Int -> Maybe Int
forall a. Eq a => a -> Seq a -> Maybe Int
S.elemIndexL Int
1 Seq Int
w)) (Int -> Seq Int
forall a. a -> Seq a
S.singleton Int
0)
w' :: Seq Int
w' = (Int -> Seq Int -> Seq Int) -> Seq Int -> Seq Int -> Seq Int
forall a b. (a -> b -> b) -> b -> Seq a -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
DF.foldr Int -> Seq Int -> Seq Int
forall a. Int -> Seq a -> Seq a
S.deleteAt Seq Int
w (Seq Int -> Seq Int
forall a. Ord a => Seq a -> Seq a
S.sort Seq Int
positions')
go :: Int -> Seq Int -> Seq Int -> (Seq Int, Seq Int)
go :: Int -> Seq Int -> Seq Int -> (Seq Int, Seq Int)
go Int
r Seq Int
positions Seq Int
indices
| Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n = (Seq Int
positions, Seq Int
indices)
| Bool
otherwise = Int -> Seq Int -> Seq Int -> (Seq Int, Seq Int)
go (Int
rInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) (Seq Int
positions Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
|> Int
pos') (Seq Int
indices Seq Int -> Int -> Seq Int
forall a. Seq a -> a -> Seq a
|> Int
index')
where
pos :: Int
pos = Seq Int
positions Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` (Int
rInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)
index :: Int
index = Seq Int
indices Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
`S.index` (Int
rInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)
v :: Seq Int
v = Int -> Seq Int -> Seq Int
forall a. Int -> Seq a -> Seq a
S.drop (Int
posInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Seq Int
w
rindex :: Maybe Int
rindex = Int -> Seq Int -> Maybe Int
forall a. Eq a => a -> Seq a -> Maybe Int
S.elemIndexL (Int
rInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Seq Int
v
(Int
pos', Int
index') =
if Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust Maybe Int
rindex
then (Int
1 Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
pos Int -> Int -> Int
forall a. C a => a -> a -> a
+ Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust Maybe Int
rindex, Int
index)
else (Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Int -> Seq Int -> Maybe Int
forall a. Eq a => a -> Seq a -> Maybe Int
S.elemIndexL (Int
rInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Seq Int
w), Int
index Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)
_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 =
if Partition -> Int
forall a. C a => [a] -> a
sum Partition
lambda Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Partition -> Int
forall a. C a => [a] -> a
sum Partition
mu
then [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays [Spray a]
sprays
else Spray a
forall a. (Eq a, C a) => Spray a
zeroSpray
where
tableaux :: [[Seq Int]]
tableaux = Partition -> Partition -> [[Seq Int]]
semiStandardTableauxWithGivenShapeAndWeight Partition
lambda Partition
mu
mm :: Int -> Spray a
mm = Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
1
sprays :: [Spray a]
sprays =
([Seq Int] -> Spray a) -> [[Seq Int]] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Spray a
mm (Int -> Spray a) -> ([Seq Int] -> Int) -> [Seq Int] -> Spray a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq Int -> Int
charge (Seq Int -> Int) -> ([Seq Int] -> Seq Int) -> [Seq Int] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Seq Int -> Seq Int -> Seq Int) -> [Seq Int] -> Seq Int
forall a. HasCallStack => (a -> a -> a) -> [a] -> a
foldl1' Seq Int -> Seq Int -> Seq Int
forall a. Seq a -> Seq a -> Seq a
(S.><)) ([Seq Int] -> Seq Int)
-> ([Seq Int] -> [Seq Int]) -> [Seq Int] -> Seq Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Seq Int -> Seq Int) -> [Seq Int] -> [Seq Int]
forall a b. (a -> b) -> [a] -> [b]
map Seq Int -> Seq Int
forall a. Seq a -> Seq a
S.reverse))) [[Seq Int]]
tableaux
b_lambda :: (Eq a, AlgRing.C a) => Partition -> Spray a
b_lambda :: forall a. (Eq a, C a) => Partition -> Spray a
b_lambda Partition
lambda = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays [Spray a]
sprays
where
table :: Partition
table = [Partition -> Int
forall a. C a => [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 -> Partition
forall a. Eq a => [a] -> [a]
nub Partition
lambda]
sprays :: [Spray a]
sprays = (Int -> Spray a) -> Partition -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Spray a
forall {a}. (Eq a, C a) => Int -> Spray a
phi Partition
table
where
phi :: Int -> Spray a
phi Int
r = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
productOfSprays
[a
BaseRing (Spray a)
forall a. C a => a
AlgRing.one BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> Spray a -> Spray a
forall a. C a => a -> a
AlgAdd.negate (Int -> Int -> Spray a
forall a. C a => Int -> Int -> Spray a
lone' Int
1 Int
i) | Int
i <- [Int
1 .. Int
r]]
_transitionMatrixHallLittlewoodSchur ::
(Eq a, AlgRing.C a) => Char -> Int -> Map Partition (Map Partition (Spray a))
_transitionMatrixHallLittlewoodSchur :: forall a.
(Eq a, C a) =>
Char -> Int -> Map Partition (Map Partition (Spray a))
_transitionMatrixHallLittlewoodSchur Char
which Int
weight =
[(Partition, Map Partition (Spray a))]
-> Map Partition (Map Partition (Spray a))
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList ([(Partition, Map Partition (Spray a))]
-> Map Partition (Map Partition (Spray a)))
-> [(Partition, Map Partition (Spray a))]
-> Map Partition (Map Partition (Spray a))
forall a b. (a -> b) -> a -> b
$ if Char
which Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'P'
then GT
-> [Map Partition (Spray a)]
-> [(Partition, Map Partition (Spray a))]
forall a b. [a] -> [b] -> [(a, b)]
zip GT
lambdas [Int -> Map Partition (Spray a)
maps Int
i | Int
i <- Partition
rg]
else GT
-> [Map Partition (Spray a)]
-> [(Partition, Map Partition (Spray a))]
forall a b. [a] -> [b] -> [(a, b)]
zip GT
lambdas
[(Partition -> Spray a -> Spray a)
-> Map Partition (Spray a) -> Map Partition (Spray a)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
lambda Spray a
c -> Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
b_lambda Partition
lambda Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
c) (Int -> Map Partition (Spray a)
maps Int
i) | Int
i <- Partition
rg]
where
lambdas :: GT
lambdas = GT -> GT
forall a. [a] -> [a]
reverse ((Partition -> Partition) -> [Partition] -> GT
forall a b. (a -> b) -> [a] -> [b]
map Partition -> Partition
fromPartition (Int -> [Partition]
partitions Int
weight))
rg :: Partition
rg = [Int
1 .. GT -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length GT
lambdas]
kfs :: [[Spray a]]
kfs = (Partition -> [Spray a]) -> GT -> [[Spray a]]
forall a b. (a -> b) -> [a] -> [b]
map Partition -> [Spray a]
forall {a}. (Eq a, C a) => Partition -> [Spray a]
f GT
lambdas
f :: Partition -> [Spray a]
f Partition
kappa =
(Partition -> Spray a) -> GT -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\Partition
mu -> Partition -> Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Partition -> Spray a
_kostkaFoulkesPolynomial Partition
kappa Partition
mu)
GT
lambdas
matrix :: Matrix (Spray a)
matrix = Matrix (Spray a) -> Matrix (Spray a)
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseUnitTriangularMatrix ([[Spray a]] -> Matrix (Spray a)
forall a. [[a]] -> Matrix a
fromLists [[Spray a]]
kfs)
maps :: Int -> Map Partition (Spray a)
maps Int
i = (Spray a -> Bool)
-> Map Partition (Spray a) -> Map Partition (Spray a)
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (Bool -> Bool
not (Bool -> Bool) -> (Spray a -> Bool) -> Spray a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spray a -> Bool
forall a. Spray a -> Bool
isZeroSpray)
([(Partition, Spray a)] -> Map Partition (Spray a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList (GT -> [Spray a] -> [(Partition, Spray a)]
forall a b. [a] -> [b] -> [(a, b)]
zip GT
lambdas (Vector (Spray a) -> [Spray a]
forall a. Vector a -> [a]
V.toList (Int -> Matrix (Spray a) -> Vector (Spray a)
forall a. Int -> Matrix a -> Vector a
getRow Int
i Matrix (Spray a)
matrix))))
_hallLittlewoodPolynomialsInSchurBasis ::
(Eq a, AlgRing.C a) => Char -> Partition -> Map Partition (Spray a)
_hallLittlewoodPolynomialsInSchurBasis :: forall a.
(Eq a, C a) =>
Char -> Partition -> Map Partition (Spray a)
_hallLittlewoodPolynomialsInSchurBasis Char
which Partition
lambda =
if Char
which Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'P'
then Map Partition (Spray a)
coeffs
else (Spray a -> Spray a)
-> Map Partition (Spray a) -> Map Partition (Spray a)
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
(^*^) (Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
b_lambda Partition
lambda)) Map Partition (Spray a)
coeffs
where
weight :: Int
weight = Partition -> Int
forall a. C a => [a] -> a
sum Partition
lambda
lambdas :: GT
lambdas =
GT -> GT
forall a. [a] -> [a]
reverse (GT -> GT) -> GT -> GT
forall a b. (a -> b) -> a -> b
$ (Partition -> Bool) -> GT -> GT
forall a. (a -> Bool) -> [a] -> [a]
filter (Partition -> Partition -> Bool
forall a. Ord a => a -> a -> Bool
<= Partition
lambda) ((Partition -> Partition) -> [Partition] -> GT
forall a b. (a -> b) -> [a] -> [b]
map Partition -> Partition
fromPartition (Int -> [Partition]
partitions Int
weight))
kfs :: [[Spray a]]
kfs = (Partition -> [Spray a]) -> GT -> [[Spray a]]
forall a b. (a -> b) -> [a] -> [b]
map Partition -> [Spray a]
forall {a}. (Eq a, C a) => Partition -> [Spray a]
f GT
lambdas
f :: Partition -> [Spray a]
f Partition
kappa =
(Partition -> Spray a) -> GT -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\Partition
mu -> Partition -> Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Partition -> Spray a
_kostkaFoulkesPolynomial Partition
kappa Partition
mu)
GT
lambdas
matrix :: Matrix (Spray a)
matrix = Matrix (Spray a) -> Matrix (Spray a)
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseUnitTriangularMatrix ([[Spray a]] -> Matrix (Spray a)
forall a. [[a]] -> Matrix a
fromLists [[Spray a]]
kfs)
coeffs :: Map Partition (Spray a)
coeffs = (Spray a -> Bool)
-> Map Partition (Spray a) -> Map Partition (Spray a)
forall a k. (a -> Bool) -> Map k a -> Map k a
DM.filter (Bool -> Bool
not (Bool -> Bool) -> (Spray a -> Bool) -> Spray a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spray a -> Bool
forall a. Spray a -> Bool
isZeroSpray)
([(Partition, Spray a)] -> Map Partition (Spray a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList (GT -> [Spray a] -> [(Partition, Spray a)]
forall a b. [a] -> [b] -> [(a, b)]
zip GT
lambdas (Vector (Spray a) -> [Spray a]
forall a. Vector a -> [a]
V.toList (Int -> Matrix (Spray a) -> Vector (Spray a)
forall a. Int -> Matrix a -> Vector a
getRow Int
1 Matrix (Spray a)
matrix))))
_e :: AlgRing.C a => MCP.Partition -> a -> a
_e :: forall a. C a => Partition -> a -> a
_e Partition
lambda a
alpha =
a
alpha a -> a -> a
forall a. C a => a -> a -> a
* Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Partition -> Int
_n (Partition -> Partition
dualPartition Partition
lambda)) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Partition -> Int
_n Partition
lambda)
where
_n :: Partition -> Int
_n Partition
mu = Partition -> Int
forall a. C a => [a] -> a
sum ((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
(P.*) [Int
0 .. ] (Partition -> Partition
fromPartition Partition
mu))
_eSymbolic :: (Eq a, AlgRing.C a) => MCP.Partition -> Spray a
_eSymbolic :: forall a. (Eq a, C a) => Partition -> Spray a
_eSymbolic Partition
lambda =
Partition -> Int
_n (Partition -> Partition
dualPartition Partition
lambda) Int -> Spray a -> Spray a
forall a. (C a, Eq a) => Int -> a -> a
.^ Spray a
alpha Spray a -> BaseRing (Spray a) -> Spray a
forall b. FunctionLike b => b -> BaseRing b -> b
<+ Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (- Partition -> Int
_n Partition
lambda)
where
alpha :: Spray a
alpha = Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
1
_n :: Partition -> Int
_n Partition
mu = Partition -> Int
forall a. C a => [a] -> a
sum ((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
(P.*) [Int
0 .. ] (Partition -> Partition
fromPartition Partition
mu))
_inverseKostkaMatrix ::
forall a. (Eq a, AlgField.C a)
=> Int -> Int -> a -> Char -> (Matrix a, [Partition])
_inverseKostkaMatrix :: forall a. (Eq a, C a) => Int -> Int -> a -> Char -> (Matrix a, GT)
_inverseKostkaMatrix Int
n Int
weight a
alpha Char
which =
(Matrix a -> Matrix a
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseTriangularMatrix ([[a]] -> Matrix a
forall a. [[a]] -> Matrix a
fromLists ((Partition -> [a]) -> GT -> [[a]]
forall a b. (a -> b) -> [a] -> [b]
map Partition -> [a]
row GT
lambdas)), GT
lambdas)
where
kostkaNumbers :: Map Partition (Map Partition a)
kostkaNumbers = Int -> Int -> a -> Char -> Map Partition (Map Partition a)
forall a.
C a =>
Int -> Int -> a -> Char -> Map Partition (Map Partition a)
_kostkaNumbers Int
n Int
weight a
alpha Char
which
lambdas :: GT
lambdas = GT -> GT
forall a. [a] -> [a]
reverse (GT -> GT) -> GT -> GT
forall a b. (a -> b) -> a -> b
$ Map Partition (Map Partition a) -> GT
forall k a. Map k a -> [k]
DM.keys Map Partition (Map Partition a)
kostkaNumbers
msCombo :: Partition -> Map Partition a
msCombo Partition
lambda = Map Partition (Map Partition a)
kostkaNumbers Map Partition (Map Partition a) -> Partition -> Map Partition a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
lambda
row :: Partition -> [a]
row Partition
lambda =
(Partition -> a) -> GT -> [a]
forall a b. (a -> b) -> [a] -> [b]
map ((Partition -> Map Partition a -> a)
-> Map Partition a -> Partition -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> Partition -> Map Partition a -> a
forall k a. Ord k => a -> k -> Map k a -> a
DM.findWithDefault a
forall a. C a => a
AlgAdd.zero) (Partition -> Map Partition a
msCombo Partition
lambda)) GT
lambdas
_kostkaNumbers ::
forall a. (AlgField.C a)
=> Int -> Int -> a -> Char -> Map Partition (Map Partition a)
_kostkaNumbers :: forall a.
C a =>
Int -> Int -> a -> Char -> Map Partition (Map Partition a)
_kostkaNumbers Int
nv Int
weight a
alpha Char
which = Map Partition (Map Partition a)
kostkaMatrix'
where
coeffsP :: Map Partition a
coeffsP = [(Partition, a)] -> Map Partition a
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(Partition
kappa, a -> a
forall a. C a => a -> a
recip (Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffP Partition
kappa a
alpha))| Partition
kappa <- GT
lambdas']
coeffsC :: Map Partition a
coeffsC = [(Partition, a)] -> Map Partition a
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(Partition
kappa, Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffC Partition
kappa a
alpha a -> a -> a
forall a. C a => a -> a -> a
/ Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffP Partition
kappa a
alpha)
| Partition
kappa <- GT
lambdas']
coeffsQ :: Map Partition a
coeffsQ = [(Partition, a)] -> Map Partition a
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(Partition
kappa, Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffQ Partition
kappa a
alpha a -> a -> a
forall a. C a => a -> a -> a
/ Partition -> a -> a
forall a. C a => Partition -> a -> a
jackCoeffP Partition
kappa a
alpha)
| Partition
kappa <- GT
lambdas']
kostkaMatrix :: Map Partition (Map Partition a)
kostkaMatrix = (Partition -> Partition)
-> Map Partition (Map Partition a)
-> Map Partition (Map Partition a)
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
DM.mapKeys Partition -> Partition
fromPartition (Int -> Map Partition (Map Partition a)
rec ([Partition] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Partition]
lambdas))
kostkaMatrix' :: Map Partition (Map Partition a)
kostkaMatrix' = case Char
which of
Char
'J' -> (Partition -> Map Partition a -> Map Partition a)
-> Map Partition (Map Partition a)
-> Map Partition (Map Partition a)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition a
m -> (a -> a) -> Map Partition a -> Map Partition a
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (a -> a -> a
forall a. C a => a -> a -> a
(*) (Map Partition a
coeffsP Map Partition a -> Partition -> a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition a
m)
Map Partition (Map Partition a)
kostkaMatrix
Char
'P' -> Map Partition (Map Partition a)
kostkaMatrix
Char
'C' -> (Partition -> Map Partition a -> Map Partition a)
-> Map Partition (Map Partition a)
-> Map Partition (Map Partition a)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition a
m -> (a -> a) -> Map Partition a -> Map Partition a
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (a -> a -> a
forall a. C a => a -> a -> a
(*) (Map Partition a
coeffsC Map Partition a -> Partition -> a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition a
m)
Map Partition (Map Partition a)
kostkaMatrix
Char
'Q' -> (Partition -> Map Partition a -> Map Partition a)
-> Map Partition (Map Partition a)
-> Map Partition (Map Partition a)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition a
m -> (a -> a) -> Map Partition a -> Map Partition a
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (a -> a -> a
forall a. C a => a -> a -> a
(*) (Map Partition a
coeffsQ Map Partition a -> Partition -> a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition a
m)
Map Partition (Map Partition a)
kostkaMatrix
Char
_ -> [Char] -> Map Partition (Map Partition a)
forall a. HasCallStack => [Char] -> a
error [Char]
"_kostkaNumbers: should not happen."
mu_r_plus ::
Seq Int -> (Int, Int) -> Int -> (MCP.Partition, (Int, Int), Int)
mu_r_plus :: Seq Int -> (Int, Int) -> Int -> (Partition, (Int, Int), Int)
mu_r_plus Seq Int
mu pair :: (Int, Int)
pair@(Int
i, Int
j) Int
r =
(
Partition -> Partition
MCP.Partition (Partition -> Partition) -> Partition -> Partition
forall a b. (a -> b) -> a -> b
$
Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList (Seq Int -> Partition) -> Seq Int -> Partition
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> Seq Int -> Seq Int
forall a. (a -> Bool) -> Seq a -> Seq a
S.dropWhileR (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$ Seq Int -> Seq Int
forall a. Seq a -> Seq a
S.reverse (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$ Seq Int -> Seq Int
forall a. Ord a => Seq a -> Seq a
S.sort (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$
(Int -> Int) -> Int -> Seq Int -> Seq Int
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' (Int -> Int -> Int
forall a. Num a => a -> a -> a
(P.+) Int
r) Int
i ((Int -> Int) -> Int -> Seq Int -> Seq Int
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
r) Int
j Seq Int
mu)
, (Int, Int)
pair
, Int
r
)
lambdas :: [Partition]
lambdas = [Partition] -> [Partition]
forall a. [a] -> [a]
reverse ([Partition] -> [Partition]) -> [Partition] -> [Partition]
forall a b. (a -> b) -> a -> b
$
(Partition -> Bool) -> [Partition] -> [Partition]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Partition
part -> Partition -> Int
partitionWidth Partition
part Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
nv) (Int -> [Partition]
partitions Int
weight)
lambdas' :: GT
lambdas' = (Partition -> Partition) -> [Partition] -> GT
forall a b. (a -> b) -> [a] -> [b]
map Partition -> Partition
fromPartition [Partition]
lambdas
rec :: Int -> Map MCP.Partition (Map Partition a)
rec :: Int -> Map Partition (Map Partition a)
rec Int
n = if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
then Partition -> Map Partition a -> Map Partition (Map Partition a)
forall k a. k -> a -> Map k a
DM.singleton (Partition -> Partition
MCP.Partition [Int
weight])
(Partition -> a -> Map Partition a
forall k a. k -> a -> Map k a
DM.singleton [Int
weight] a
forall a. C a => a
AlgRing.one)
else Partition
-> Map Partition a
-> Map Partition (Map Partition a)
-> Map Partition (Map Partition a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
DM.insert Partition
mu (Partition -> a -> Map Partition a
forall k a. k -> a -> Map k a
DM.singleton Partition
mu' a
forall a. C a => a
AlgRing.one)
(
[(Partition, Map Partition a)] -> Map Partition (Map Partition a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(
Partition
kappa
, Partition -> a -> Map Partition a -> Map Partition a
forall k a. Ord k => k -> a -> Map k a -> Map k a
DM.insert Partition
mu' (Map Partition a
newColumn Map Partition a -> Partition -> a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa) (Map Partition (Map Partition a)
previous Map Partition (Map Partition a) -> Partition -> Map Partition a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)
) | Partition
kappa <- [Partition]
kappas]
)
where
previous :: Map Partition (Map Partition a)
previous = Int -> Map Partition (Map Partition a)
rec (Int
n Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1)
parts :: [Partition]
parts = Int -> [Partition] -> [Partition]
forall a. Int -> [a] -> [a]
take Int
n [Partition]
lambdas
([Partition]
kappas, Partition
mu) = Maybe ([Partition], Partition) -> ([Partition], Partition)
forall a. HasCallStack => Maybe a -> a
fromJust ([Partition] -> Maybe ([Partition], Partition)
forall a. [a] -> Maybe ([a], a)
unsnoc [Partition]
parts)
_e_mu_alpha :: a
_e_mu_alpha = Partition -> a -> a
forall a. C a => Partition -> a -> a
_e Partition
mu a
alpha
mu' :: Partition
mu' = Partition -> Partition
fromPartition Partition
mu
mu'' :: Seq Int
mu'' = Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
mu'
l :: Int
l = Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
mu''
pairs :: [(Int, Int)]
pairs = [(Int
i, Int
j) | Int
i <- [Int
0 .. Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
2], Int
j <- [Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1 .. Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1]]
triplets :: [(Partition, (Int, Int), Int)]
triplets = [Seq Int -> (Int, Int) -> Int -> (Partition, (Int, Int), Int)
mu_r_plus Seq Int
mu'' (Int
i, Int
j) Int
r
| (Int
i, Int
j) <- [(Int, Int)]
pairs, Int
r <- [Int
1 .. Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
j]]
newColumn :: Map Partition a
newColumn =
[(Partition, a)] -> Map Partition a
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList [(Partition
kappa, Partition -> a
f Partition
kappa) | Partition
kappa <- [Partition]
kappas]
f :: Partition -> a
f Partition
kappa = [a] -> a
forall a. C a => [a] -> a
AlgAdd.sum [a]
xs
where
previousRow :: Map Partition a
previousRow = Map Partition (Map Partition a)
previous Map Partition (Map Partition a) -> Partition -> Map Partition a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa
triplets' :: [(Partition, (Int, Int), Int)]
triplets' = ((Partition, (Int, Int), Int) -> Bool)
-> [(Partition, (Int, Int), Int)] -> [(Partition, (Int, Int), Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Partition -> Partition -> Bool
dominates Partition
kappa) (Partition -> Bool)
-> ((Partition, (Int, Int), Int) -> Partition)
-> (Partition, (Int, Int), Int)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Partition, (Int, Int), Int) -> Partition
forall a b c. (a, b, c) -> a
fst3) [(Partition, (Int, Int), Int)]
triplets
ee :: a
ee = Partition -> a -> a
forall a. C a => Partition -> a -> a
_e Partition
kappa a
alpha a -> a -> a
forall a. C a => a -> a -> a
- a
_e_mu_alpha
xs :: [a]
xs = [
Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
P.- Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
P.+ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
P.* Int
r)
a -> a -> a
forall a. C a => a -> a -> a
* (Map Partition a
previousRow Map Partition a -> Partition -> a
forall k a. Ord k => Map k a -> k -> a
DM.! (Partition -> Partition
fromPartition Partition
nu)) a -> a -> a
forall a. C a => a -> a -> a
/ a
ee
| (Partition
nu, (Int
i, Int
j), Int
r) <- [(Partition, (Int, Int), Int)]
triplets'
]
_symbolicKostkaNumbers ::
forall a. (Eq a, AlgField.C a)
=> Int -> Int -> Char -> Map Partition (Map Partition (RatioOfSprays a))
_symbolicKostkaNumbers :: forall a.
(Eq a, C a) =>
Int
-> Int -> Char -> Map Partition (Map Partition (RatioOfSprays a))
_symbolicKostkaNumbers Int
nv Int
weight Char
which = Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix'
where
coeffsP :: Map Partition (RatioOfSprays a)
coeffsP = [(Partition, RatioOfSprays a)] -> Map Partition (RatioOfSprays a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(Partition
kappa, Spray a -> RatioOfSprays a
forall a. C a => Spray a -> RatioOfSprays a
asRatioOfSprays (Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffPinv Partition
kappa))
| Partition
kappa <- GT
lambdas']
coeffsC :: Map Partition (RatioOfSprays a)
coeffsC = [(Partition, RatioOfSprays a)] -> Map Partition (RatioOfSprays a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(
Partition
kappa
, (Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffPinv Partition
kappa :: Spray a) Spray a -> RatioOfSprays a -> RatioOfSprays a
forall a v. C a v => a -> v -> v
*> Partition -> RatioOfSprays a
forall a. (Eq a, C a) => Partition -> RatioOfSprays a
jackSymbolicCoeffC Partition
kappa
) | Partition
kappa <- GT
lambdas']
coeffsQ :: Map Partition (RatioOfSprays a)
coeffsQ = [(Partition, RatioOfSprays a)] -> Map Partition (RatioOfSprays a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[(
Partition
kappa
, Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffPinv Partition
kappa Spray a -> Spray a -> RatioOfSprays a
forall a. (Eq a, C a) => Spray a -> Spray a -> RatioOfSprays a
%//% Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffQinv Partition
kappa
) | Partition
kappa <- GT
lambdas']
kostkaMatrix :: Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix = (Partition -> Partition)
-> Map Partition (Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
DM.mapKeys Partition -> Partition
fromPartition (Int -> Map Partition (Map Partition (RatioOfSprays a))
rec ([Partition] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Partition]
lambdas))
kostkaMatrix' :: Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix' = case Char
which of
Char
'J' -> (Partition
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition (RatioOfSprays a)
m -> (RatioOfSprays a -> RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (RatioOfSprays a -> RatioOfSprays a -> RatioOfSprays a
forall a. C a => a -> a -> a
(*) (Map Partition (RatioOfSprays a)
coeffsP Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition (RatioOfSprays a)
m)
Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix
Char
'P' -> Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix
Char
'C' -> (Partition
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition (RatioOfSprays a)
m -> (RatioOfSprays a -> RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (RatioOfSprays a -> RatioOfSprays a -> RatioOfSprays a
forall a. C a => a -> a -> a
(*) (Map Partition (RatioOfSprays a)
coeffsC Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition (RatioOfSprays a)
m)
Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix
Char
'Q' -> (Partition
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a b. (k -> a -> b) -> Map k a -> Map k b
DM.mapWithKey (\Partition
kappa Map Partition (RatioOfSprays a)
m -> (RatioOfSprays a -> RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
forall a b k. (a -> b) -> Map k a -> Map k b
DM.map (RatioOfSprays a -> RatioOfSprays a -> RatioOfSprays a
forall a. C a => a -> a -> a
(*) (Map Partition (RatioOfSprays a)
coeffsQ Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)) Map Partition (RatioOfSprays a)
m)
Map Partition (Map Partition (RatioOfSprays a))
kostkaMatrix
Char
_ -> [Char] -> Map Partition (Map Partition (RatioOfSprays a))
forall a. HasCallStack => [Char] -> a
error [Char]
"_symbolicKostkaNumbers: should not happen."
mu_r_plus ::
Seq Int -> (Int, Int) -> Int -> (MCP.Partition, (Int, Int), Int)
mu_r_plus :: Seq Int -> (Int, Int) -> Int -> (Partition, (Int, Int), Int)
mu_r_plus Seq Int
mu pair :: (Int, Int)
pair@(Int
i, Int
j) Int
r =
(
Partition -> Partition
MCP.Partition (Partition -> Partition) -> Partition -> Partition
forall a b. (a -> b) -> a -> b
$
Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList (Seq Int -> Partition) -> Seq Int -> Partition
forall a b. (a -> b) -> a -> b
$ (Int -> Bool) -> Seq Int -> Seq Int
forall a. (a -> Bool) -> Seq a -> Seq a
S.dropWhileR (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$ Seq Int -> Seq Int
forall a. Seq a -> Seq a
S.reverse (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$ Seq Int -> Seq Int
forall a. Ord a => Seq a -> Seq a
S.sort (Seq Int -> Seq Int) -> Seq Int -> Seq Int
forall a b. (a -> b) -> a -> b
$
(Int -> Int) -> Int -> Seq Int -> Seq Int
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' (Int -> Int -> Int
forall a. Num a => a -> a -> a
(P.+) Int
r) Int
i ((Int -> Int) -> Int -> Seq Int -> Seq Int
forall a. (a -> a) -> Int -> Seq a -> Seq a
S.adjust' (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
r) Int
j Seq Int
mu)
, (Int, Int)
pair
, Int
r
)
lambdas :: [Partition]
lambdas = [Partition] -> [Partition]
forall a. [a] -> [a]
reverse ([Partition] -> [Partition]) -> [Partition] -> [Partition]
forall a b. (a -> b) -> a -> b
$
(Partition -> Bool) -> [Partition] -> [Partition]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Partition
part -> Partition -> Int
partitionWidth Partition
part Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
nv) (Int -> [Partition]
partitions Int
weight)
lambdas' :: GT
lambdas' = (Partition -> Partition) -> [Partition] -> GT
forall a b. (a -> b) -> [a] -> [b]
map Partition -> Partition
fromPartition [Partition]
lambdas
rec :: Int -> Map MCP.Partition (Map Partition (RatioOfSprays a))
rec :: Int -> Map Partition (Map Partition (RatioOfSprays a))
rec Int
n = if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
then Partition
-> Map Partition (RatioOfSprays a)
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a. k -> a -> Map k a
DM.singleton (Partition -> Partition
MCP.Partition [Int
weight])
(Partition -> RatioOfSprays a -> Map Partition (RatioOfSprays a)
forall k a. k -> a -> Map k a
DM.singleton [Int
weight] RatioOfSprays a
forall a. (C a, Eq a) => RatioOfSprays a
unitRatioOfSprays)
else Partition
-> Map Partition (RatioOfSprays a)
-> Map Partition (Map Partition (RatioOfSprays a))
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a. Ord k => k -> a -> Map k a -> Map k a
DM.insert Partition
mu (Partition -> RatioOfSprays a -> Map Partition (RatioOfSprays a)
forall k a. k -> a -> Map k a
DM.singleton Partition
mu' RatioOfSprays a
forall a. (C a, Eq a) => RatioOfSprays a
unitRatioOfSprays)
(
[(Partition, Map Partition (RatioOfSprays a))]
-> Map Partition (Map Partition (RatioOfSprays a))
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList
[
(
Partition
kappa
, Partition
-> RatioOfSprays a
-> Map Partition (RatioOfSprays a)
-> Map Partition (RatioOfSprays a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
DM.insert Partition
mu' (Map Partition (RatioOfSprays a)
newColumn Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa) (Map Partition (Map Partition (RatioOfSprays a))
previous Map Partition (Map Partition (RatioOfSprays a))
-> Partition -> Map Partition (RatioOfSprays a)
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa)
)
| Partition
kappa <- [Partition]
kappas
]
)
where
previous :: Map Partition (Map Partition (RatioOfSprays a))
previous = Int -> Map Partition (Map Partition (RatioOfSprays a))
rec (Int
n Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1)
parts :: [Partition]
parts = Int -> [Partition] -> [Partition]
forall a. Int -> [a] -> [a]
take Int
n [Partition]
lambdas
([Partition]
kappas, Partition
mu) = Maybe ([Partition], Partition) -> ([Partition], Partition)
forall a. HasCallStack => Maybe a -> a
fromJust ([Partition] -> Maybe ([Partition], Partition)
forall a. [a] -> Maybe ([a], a)
unsnoc [Partition]
parts)
_eSymbolic_mu :: Spray a
_eSymbolic_mu = Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
_eSymbolic Partition
mu
mu' :: Partition
mu' = Partition -> Partition
fromPartition Partition
mu
mu'' :: Seq Int
mu'' = Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
mu'
l :: Int
l = Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
mu''
pairs :: [(Int, Int)]
pairs = [(Int
i, Int
j) | Int
i <- [Int
0 .. Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
2], Int
j <- [Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
+Int
1 .. Int
lInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1]]
triplets :: [(Partition, (Int, Int), Int)]
triplets = [Seq Int -> (Int, Int) -> Int -> (Partition, (Int, Int), Int)
mu_r_plus Seq Int
mu'' (Int
i, Int
j) Int
r
| (Int
i, Int
j) <- [(Int, Int)]
pairs, Int
r <- [Int
1 .. Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
j]]
newColumn :: Map Partition (RatioOfSprays a)
newColumn =
[(Partition, RatioOfSprays a)] -> Map Partition (RatioOfSprays a)
forall k a. [(k, a)] -> Map k a
DM.fromDistinctDescList [(Partition
kappa, Partition -> RatioOfSprays a
f Partition
kappa) | Partition
kappa <- [Partition]
kappas]
f :: Partition -> RatioOfSprays a
f Partition
kappa = [RatioOfSprays a] -> RatioOfSprays a
forall a. C a => [a] -> a
AlgAdd.sum [RatioOfSprays a]
xs
where
previousRow :: Map Partition (RatioOfSprays a)
previousRow = Map Partition (Map Partition (RatioOfSprays a))
previous Map Partition (Map Partition (RatioOfSprays a))
-> Partition -> Map Partition (RatioOfSprays a)
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
kappa
triplets' :: [(Partition, (Int, Int), Int)]
triplets' = ((Partition, (Int, Int), Int) -> Bool)
-> [(Partition, (Int, Int), Int)] -> [(Partition, (Int, Int), Int)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Partition -> Partition -> Bool
dominates Partition
kappa) (Partition -> Bool)
-> ((Partition, (Int, Int), Int) -> Partition)
-> (Partition, (Int, Int), Int)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Partition, (Int, Int), Int) -> Partition
forall a b c. (a, b, c) -> a
fst3) [(Partition, (Int, Int), Int)]
triplets
ee :: Spray a
ee = Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
_eSymbolic Partition
kappa Spray a -> Spray a -> Spray a
forall a. C a => a -> a -> a
- Spray a
_eSymbolic_mu
xs :: [RatioOfSprays a]
xs = [
(
(Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
P.- Seq Int -> Int -> Int
forall a. Seq a -> Int -> a
S.index Seq Int
mu'' Int
j Int -> Int -> Int
forall a. Num a => a -> a -> a
P.+ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
P.* Int
r)
Int -> RatioOfSprays a -> RatioOfSprays a
forall a. (C a, Eq a) => Int -> a -> a
.^ (Map Partition (RatioOfSprays a)
previousRow Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall k a. Ord k => Map k a -> k -> a
DM.! (Partition -> Partition
fromPartition Partition
nu))
) RatioOfSprays a -> Spray a -> RatioOfSprays a
forall a.
(Eq a, C a) =>
RatioOfSprays a -> Spray a -> RatioOfSprays a
%/% Spray a
ee
| (Partition
nu, (Int
i, Int
j), Int
r) <- [(Partition, (Int, Int), Int)]
triplets'
]
_inverseSymbolicKostkaMatrix ::
forall a. (Eq a, AlgField.C a)
=> Int -> Int -> Char -> (Matrix (RatioOfSprays a), [Partition])
_inverseSymbolicKostkaMatrix :: forall a.
(Eq a, C a) =>
Int -> Int -> Char -> (Matrix (RatioOfSprays a), GT)
_inverseSymbolicKostkaMatrix Int
n Int
weight Char
which =
(
Matrix (RatioOfSprays a) -> Matrix (RatioOfSprays a)
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseTriangularMatrix ([[RatioOfSprays a]] -> Matrix (RatioOfSprays a)
forall a. [[a]] -> Matrix a
fromLists [(Partition -> RatioOfSprays a) -> GT -> [RatioOfSprays a]
forall a b. (a -> b) -> [a] -> [b]
map (Partition -> Partition -> RatioOfSprays a
row Partition
mu) GT
lambdas | Partition
mu <- GT
lambdas])
, GT
lambdas
)
where
kostkaNumbers :: Map Partition (Map Partition (RatioOfSprays a))
kostkaNumbers = Int
-> Int -> Char -> Map Partition (Map Partition (RatioOfSprays a))
forall a.
(Eq a, C a) =>
Int
-> Int -> Char -> Map Partition (Map Partition (RatioOfSprays a))
_symbolicKostkaNumbers Int
n Int
weight Char
which
lambdas :: GT
lambdas = GT -> GT
forall a. [a] -> [a]
reverse (GT -> GT) -> GT -> GT
forall a b. (a -> b) -> a -> b
$ Map Partition (Map Partition (RatioOfSprays a)) -> GT
forall k a. Map k a -> [k]
DM.keys Map Partition (Map Partition (RatioOfSprays a))
kostkaNumbers
msCombo :: Partition -> Map Partition (RatioOfSprays a)
msCombo Partition
lambda = Map Partition (Map Partition (RatioOfSprays a))
kostkaNumbers Map Partition (Map Partition (RatioOfSprays a))
-> Partition -> Map Partition (RatioOfSprays a)
forall k a. Ord k => Map k a -> k -> a
DM.! Partition
lambda
row :: Partition -> Partition -> RatioOfSprays a
row = (Partition -> Map Partition (RatioOfSprays a) -> RatioOfSprays a)
-> Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (RatioOfSprays a
-> Partition -> Map Partition (RatioOfSprays a) -> RatioOfSprays a
forall k a. Ord k => a -> k -> Map k a -> a
DM.findWithDefault RatioOfSprays a
forall a. (C a, Eq a) => RatioOfSprays a
zeroRatioOfSprays) (Map Partition (RatioOfSprays a) -> Partition -> RatioOfSprays a)
-> (Partition -> Map Partition (RatioOfSprays a))
-> Partition
-> Partition
-> RatioOfSprays a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Partition -> Map Partition (RatioOfSprays a)
msCombo
inverseTriangularMatrix :: (Eq a, AlgField.C a) => Matrix a -> Matrix a
inverseTriangularMatrix :: forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseTriangularMatrix Matrix a
mat =
if Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then [[a]] -> Matrix a
forall a. [[a]] -> Matrix a
fromLists [[a -> a
forall a. C a => a -> a
recip (Int -> Int -> Matrix a -> a
forall a. Int -> Int -> Matrix a -> a
getElem Int
1 Int
1 Matrix a
mat)]] else Matrix a
invmat
where
d :: Int
d = Matrix a -> Int
forall a. Matrix a -> Int
nrows Matrix a
mat
invminor :: Matrix a
invminor = Matrix a -> Matrix a
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseTriangularMatrix (Int -> Int -> Matrix a -> Matrix a
forall a. Int -> Int -> Matrix a -> Matrix a
minorMatrix Int
d Int
d Matrix a
mat)
lastColumn :: Vector a
lastColumn = Vector a -> Vector a
forall a. Vector a -> Vector a
V.init (Int -> Matrix a -> Vector a
forall a. Int -> Matrix a -> Vector a
getCol Int
d Matrix a
mat)
vectors :: [(Vector a, Vector a)]
vectors = [
(
Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
V.drop (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) (Int -> Matrix a -> Vector a
forall a. Int -> Matrix a -> Vector a
getRow Int
i Matrix a
invminor)
, Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
V.drop (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Vector a
lastColumn
)
| Int
i <- [Int
1 .. Int
dInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1]
]
lastEntry :: a
lastEntry = a -> a
forall a. C a => a -> a
recip (Int -> Int -> Matrix a -> a
forall a. Int -> Int -> Matrix a -> a
getElem Int
d Int
d Matrix a
mat)
newColumn :: Matrix a
newColumn = Vector a -> Matrix a
forall a. Vector a -> Matrix a
colVector ([a] -> Vector a
forall a. [a] -> Vector a
V.fromList
[a -> a
forall a. C a => a -> a
AlgAdd.negate (a
lastEntry a -> a -> a
forall a. C a => a -> a -> a
* (a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
V.foldl1 a -> a -> a
forall a. C a => a -> a -> a
(AlgAdd.+) ((a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. C a => a -> a -> a
(*) Vector a
u Vector a
v))
| (Vector a
u, Vector a
v) <- [(Vector a, Vector a)]
vectors]
)
newRow :: Matrix a
newRow = Vector a -> Matrix a
forall a. Vector a -> Matrix a
rowVector (Vector a -> a -> Vector a
forall a. Vector a -> a -> Vector a
V.snoc (Int -> a -> Vector a
forall a. Int -> a -> Vector a
V.replicate (Int
d Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1) a
forall a. C a => a
AlgAdd.zero) a
lastEntry)
invmat :: Matrix a
invmat = (Matrix a
invminor Matrix a -> Matrix a -> Matrix a
forall a. Matrix a -> Matrix a -> Matrix a
<|> Matrix a
newColumn) Matrix a -> Matrix a -> Matrix a
forall a. Matrix a -> Matrix a -> Matrix a
<-> Matrix a
newRow
inverseUnitTriangularMatrix :: (Eq a, AlgRing.C a) => Matrix a -> Matrix a
inverseUnitTriangularMatrix :: forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseUnitTriangularMatrix Matrix a
mat =
if Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then Matrix a
mat else Matrix a
invmat
where
d :: Int
d = Matrix a -> Int
forall a. Matrix a -> Int
nrows Matrix a
mat
invminor :: Matrix a
invminor = Matrix a -> Matrix a
forall a. (Eq a, C a) => Matrix a -> Matrix a
inverseUnitTriangularMatrix (Int -> Int -> Matrix a -> Matrix a
forall a. Int -> Int -> Matrix a -> Matrix a
minorMatrix Int
d Int
d Matrix a
mat)
lastColumn :: Vector a
lastColumn = Vector a -> Vector a
forall a. Vector a -> Vector a
V.init (Int -> Matrix a -> Vector a
forall a. Int -> Matrix a -> Vector a
getCol Int
d Matrix a
mat)
vectors :: [(Vector a, Vector a)]
vectors = [
(
Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
V.drop (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) (Int -> Matrix a -> Vector a
forall a. Int -> Matrix a -> Vector a
getRow Int
i Matrix a
invminor)
, Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
V.drop (Int
iInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) Vector a
lastColumn
)
| Int
i <- [Int
1 .. Int
dInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1]
]
newColumn :: Matrix a
newColumn = Vector a -> Matrix a
forall a. Vector a -> Matrix a
colVector ([a] -> Vector a
forall a. [a] -> Vector a
V.fromList
[a -> a
forall a. C a => a -> a
AlgAdd.negate ((a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
V.foldl1 a -> a -> a
forall a. C a => a -> a -> a
(AlgAdd.+) ((a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. C a => a -> a -> a
(*) Vector a
u Vector a
v))
| (Vector a
u, Vector a
v) <- [(Vector a, Vector a)]
vectors]
)
newRow :: Matrix a
newRow = Vector a -> Matrix a
forall a. Vector a -> Matrix a
rowVector (Vector a -> a -> Vector a
forall a. Vector a -> a -> Vector a
V.snoc (Int -> a -> Vector a
forall a. Int -> a -> Vector a
V.replicate (Int
d Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1) a
forall a. C a => a
AlgAdd.zero) a
forall a. C a => a
AlgRing.one)
invmat :: Matrix a
invmat = (Matrix a
invminor Matrix a -> Matrix a -> Matrix a
forall a. Matrix a -> Matrix a -> Matrix a
<|> Matrix a
newColumn) Matrix a -> Matrix a -> Matrix a
forall a. Matrix a -> Matrix a -> Matrix a
<-> Matrix a
newRow
_isPartition :: Partition -> Bool
_isPartition :: Partition -> Bool
_isPartition [] = Bool
True
_isPartition [Int
x] = Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
_isPartition (Int
x:xs :: Partition
xs@(Int
y:Partition
_)) = (Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
y) Bool -> Bool -> Bool
&& Partition -> Bool
_isPartition Partition
xs
_diffSequence :: [Int] -> [Int]
_diffSequence :: Partition -> Partition
_diffSequence = Partition -> Partition
forall {a}. C a => [a] -> [a]
go where
go :: [a] -> [a]
go (a
x:ys :: [a]
ys@(a
y:[a]
_)) = (a
xa -> a -> a
forall a. C a => a -> a -> a
-a
y) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
ys
go [a
x] = [a
x]
go [] = []
_dualPartition :: Partition -> Partition
_dualPartition :: Partition -> Partition
_dualPartition [] = []
_dualPartition Partition
xs = Int -> Partition -> Partition -> Partition
forall {t}. (C t, Num t) => t -> Partition -> Partition -> [t]
go Int
0 (Partition -> Partition
_diffSequence Partition
xs) [] where
go :: t -> Partition -> Partition -> [t]
go !t
i (Int
d:Partition
ds) Partition
acc = t -> Partition -> Partition -> [t]
go (t
it -> t -> t
forall a. C a => a -> a -> a
+t
1) Partition
ds (Int
dInt -> Partition -> Partition
forall a. a -> [a] -> [a]
:Partition
acc)
go t
n [] Partition
acc = t -> Partition -> [t]
forall {t}. (C t, Num t) => t -> Partition -> [t]
finish t
n Partition
acc
finish :: t -> Partition -> [t]
finish !t
j (Int
k:Partition
ks) = Int -> t -> [t]
forall a. Int -> a -> [a]
replicate Int
k t
j [t] -> [t] -> [t]
forall a. [a] -> [a] -> [a]
++ t -> Partition -> [t]
finish (t
jt -> t -> t
forall a. C a => a -> a -> a
-t
1) Partition
ks
finish t
_ [] = []
_ij :: Partition -> ([Int], [Int])
_ij :: Partition -> (Partition, Partition)
_ij Partition
lambda =
(
(Int -> Int -> Partition) -> Partition -> Partition
forall a b. (Int -> a -> [b]) -> [a] -> [b]
iconcatMap (\Int
i Int
a -> Int -> Int -> Partition
forall a. Int -> a -> [a]
replicate Int
a (Int
i Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1)) Partition
lambda,
(Int -> Partition) -> Partition -> Partition
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Int
a -> [Int
1 .. Int
a]) ((Int -> Bool) -> Partition -> Partition
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
0) Partition
lambda)
)
_convParts :: AlgRing.C b => [Int] -> ([b], [b])
_convParts :: forall b. C b => Partition -> ([b], [b])
_convParts Partition
lambda =
((Int -> b) -> Partition -> [b]
forall a b. (a -> b) -> [a] -> [b]
map Int -> b
forall a b. (C a, C b) => a -> b
fromIntegral Partition
lambda, (Int -> b) -> Partition -> [b]
forall a b. (a -> b) -> [a] -> [b]
map Int -> b
forall a b. (C a, C b) => a -> b
fromIntegral (Partition -> Partition
_dualPartition Partition
lambda))
_N :: [Int] -> [Int] -> Int
_N :: Partition -> Partition -> Int
_N Partition
lambda Partition
mu = Partition -> Int
forall a. C a => [a] -> a
sum (Partition -> Int) -> Partition -> Int
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int) -> Partition -> Partition -> Partition
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. C a => a -> a -> a
(*) Partition
mu Partition
prods
where
prods :: Partition
prods = (Int -> Int) -> Partition -> Partition
forall a b. (a -> b) -> [a] -> [b]
map (\Int
i -> Partition -> Int
forall a. C a => [a] -> a
product (Partition -> Int) -> Partition -> Int
forall a b. (a -> b) -> a -> b
$ Int -> Partition -> Partition
forall a. Int -> [a] -> [a]
drop Int
i ((Int -> Int) -> Partition -> Partition
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. C a => a -> a -> a
+Int
1) Partition
lambda)) [Int
1 .. Partition -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Partition
lambda]
hookLengths :: AlgRing.C a => Partition -> a -> ([a], [a])
hookLengths :: forall a. C a => Partition -> a -> ([a], [a])
hookLengths Partition
lambda a
alpha = ([a]
lower, [a]
upper)
where
(Partition
i, Partition
j) = Partition -> (Partition, Partition)
_ij Partition
lambda
([a]
lambda', [a]
lambdaConj') = Partition -> ([a], [a])
forall b. C b => Partition -> ([b], [b])
_convParts Partition
lambda
upper :: [a]
upper = (Int -> Int -> a) -> Partition -> Partition -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ([a] -> [a] -> Int -> Int -> a
fup [a]
lambdaConj' [a]
lambda') Partition
i Partition
j
where
fup :: [a] -> [a] -> Int -> Int -> a
fup [a]
x [a]
y Int
ii Int
jj =
[a]
x[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
jjInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
ii a -> a -> a
forall a. C a => a -> a -> a
+
a
alpha a -> a -> a
forall a. C a => a -> a -> a
* ([a]
y[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Int
jj Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1))
lower :: [a]
lower = (Int -> Int -> a) -> Partition -> Partition -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ([a] -> [a] -> Int -> Int -> a
flow [a]
lambdaConj' [a]
lambda') Partition
i Partition
j
where
flow :: [a] -> [a] -> Int -> Int -> a
flow [a]
x [a]
y Int
ii Int
jj =
[a]
x[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
jjInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- (Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1) a -> a -> a
forall a. C a => a -> a -> a
+
a
alpha a -> a -> a
forall a. C a => a -> a -> a
* ([a]
y[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
jj)
_productHookLengths :: AlgRing.C a => Partition -> a -> a
_productHookLengths :: forall a. C a => Partition -> a -> a
_productHookLengths Partition
lambda a
alpha = [a] -> a
forall a. C a => [a] -> a
product [a]
lower a -> a -> a
forall a. C a => a -> a -> a
* [a] -> a
forall a. C a => [a] -> a
product [a]
upper
where
([a]
lower, [a]
upper) = Partition -> a -> ([a], [a])
forall a. C a => Partition -> a -> ([a], [a])
hookLengths Partition
lambda a
alpha
jackCoeffC :: AlgField.C a => Partition -> a -> a
jackCoeffC :: forall a. C a => Partition -> a -> a
jackCoeffC Partition
lambda a
alpha =
a
alphaa -> Integer -> a
forall a. C a => a -> Integer -> a
^Integer
k a -> a -> a
forall a. C a => a -> a -> a
* Integer -> a
forall a. C a => Integer -> a
fromInteger ([Integer] -> Integer
forall a. C a => [a] -> a
product [Integer
2 .. Integer
k]) a -> a -> a
forall a. C a => a -> a -> a
* a -> a
forall a. C a => a -> a
recip a
jlambda
where
k :: Integer
k = Int -> Integer
forall a b. (C a, C b) => a -> b
fromIntegral (Partition -> Int
forall a. C a => [a] -> a
sum Partition
lambda)
jlambda :: a
jlambda = Partition -> a -> a
forall a. C a => Partition -> a -> a
_productHookLengths Partition
lambda a
alpha
jackCoeffP :: AlgField.C a => Partition -> a -> a
jackCoeffP :: forall a. C a => Partition -> a -> a
jackCoeffP Partition
lambda a
alpha = a
forall a. C a => a
one a -> a -> a
forall a. C a => a -> a -> a
/ [a] -> a
forall a. C a => [a] -> a
product [a]
lower
where
([a]
lower, [a]
_) = Partition -> a -> ([a], [a])
forall a. C a => Partition -> a -> ([a], [a])
hookLengths Partition
lambda a
alpha
jackCoeffQ :: AlgField.C a => Partition -> a -> a
jackCoeffQ :: forall a. C a => Partition -> a -> a
jackCoeffQ Partition
lambda a
alpha = a
forall a. C a => a
one a -> a -> a
forall a. C a => a -> a -> a
/ [a] -> a
forall a. C a => [a] -> a
product [a]
upper
where
([a]
_, [a]
upper) = Partition -> a -> ([a], [a])
forall a. C a => Partition -> a -> ([a], [a])
hookLengths Partition
lambda a
alpha
symbolicHookLengthsProducts :: forall a. (Eq a, AlgRing.C a)
=> Partition -> (Spray a, Spray a)
symbolicHookLengthsProducts :: forall a. (Eq a, C a) => Partition -> (Spray a, Spray a)
symbolicHookLengthsProducts Partition
lambda = ([Spray a] -> Spray a
forall a. C a => [a] -> a
product [Spray a]
lower, [Spray a] -> Spray a
forall a. C a => [a] -> a
product [Spray a]
upper)
where
alpha :: Spray a
alpha = Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
1 :: Spray a
(Partition
i, Partition
j) = Partition -> (Partition, Partition)
_ij Partition
lambda
([a]
lambda', [a]
lambdaConj') = Partition -> ([a], [a])
forall b. C b => Partition -> ([b], [b])
_convParts Partition
lambda
upper :: [Spray a]
upper = (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ([a] -> [a] -> Int -> Int -> Spray a
fup [a]
lambdaConj' [a]
lambda') Partition
i Partition
j
where
fup :: [a] -> [a] -> Int -> Int -> Spray a
fup [a]
x [a]
y Int
ii Int
jj =
([a]
x[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
jjInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
ii) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+>
(([a]
y[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Int
jj Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1)) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
alpha)
lower :: [Spray a]
lower = (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ([a] -> [a] -> Int -> Int -> Spray a
flow [a]
lambdaConj' [a]
lambda') Partition
i Partition
j
where
flow :: [a] -> [a] -> Int -> Int -> Spray a
flow [a]
x [a]
y Int
ii Int
jj =
([a]
x[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
jjInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral (Int
ii Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
1)) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+>
(([a]
y[a] -> Int -> a
forall a. HasCallStack => [a] -> Int -> a
!!(Int
iiInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1) a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
jj) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
alpha)
symbolicHookLengthsProduct :: (Eq a, AlgRing.C a) => Partition -> Spray a
symbolicHookLengthsProduct :: forall a. (Eq a, C a) => Partition -> Spray a
symbolicHookLengthsProduct Partition
lambda = Spray a
lower Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
upper
where
(Spray a
lower, Spray a
upper) = Partition -> (Spray a, Spray a)
forall a. (Eq a, C a) => Partition -> (Spray a, Spray a)
symbolicHookLengthsProducts Partition
lambda
jackSymbolicCoeffC ::
forall a. (Eq a, AlgField.C a) => Partition -> RatioOfSprays a
jackSymbolicCoeffC :: forall a. (Eq a, C a) => Partition -> RatioOfSprays a
jackSymbolicCoeffC Partition
lambda =
((Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
factorialk) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
alphaSpray a -> Int -> Spray a
forall b. (FunctionLike b, C b) => b -> Int -> b
^**^Int
k) Spray a -> Spray a -> RatioOfSprays a
forall a. Spray a -> Spray a -> RatioOfSprays a
%:% Spray a
jlambda
where
alpha :: Spray a
alpha = Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
1 :: Spray a
k :: Int
k = Partition -> Int
forall a. C a => [a] -> a
sum Partition
lambda
factorialk :: Int
factorialk = Partition -> Int
forall a. C a => [a] -> a
product [Int
2 .. Int
k]
jlambda :: Spray a
jlambda = Partition -> Spray a
forall a. (Eq a, C a) => Partition -> Spray a
symbolicHookLengthsProduct Partition
lambda
jackSymbolicCoeffPinv :: (Eq a, AlgField.C a) => Partition -> Spray a
jackSymbolicCoeffPinv :: forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffPinv Partition
lambda = Spray a
lower
where
(Spray a
lower, Spray a
_) = Partition -> (Spray a, Spray a)
forall a. (Eq a, C a) => Partition -> (Spray a, Spray a)
symbolicHookLengthsProducts Partition
lambda
jackSymbolicCoeffQinv :: (Eq a, AlgField.C a) => Partition -> Spray a
jackSymbolicCoeffQinv :: forall a. (Eq a, C a) => Partition -> Spray a
jackSymbolicCoeffQinv Partition
lambda = Spray a
upper
where
(Spray a
_, Spray a
upper) = Partition -> (Spray a, Spray a)
forall a. (Eq a, C a) => Partition -> (Spray a, Spray a)
symbolicHookLengthsProducts Partition
lambda
_betaratio :: AlgField.C a => Partition -> Partition -> Int -> a -> a
_betaratio :: forall a. C a => Partition -> Partition -> Int -> a -> a
_betaratio Partition
kappa Partition
mu Int
k a
alpha = a
alpha a -> a -> a
forall a. C a => a -> a -> a
* a
prod1 a -> a -> a
forall a. C a => a -> a -> a
* a
prod2 a -> a -> a
forall a. C a => a -> a -> a
* a
prod3
where
mukm1 :: Int
mukm1 = Partition
mu Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
kInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)
t :: a
t = Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
k a -> a -> a
forall a. C a => a -> a -> a
- a
alpha a -> a -> a
forall a. C a => a -> a -> a
* Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
mukm1
u :: [a]
u = (Int -> Int -> a) -> Partition -> Partition -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
s Int
kap -> a
t a -> a -> a
forall a. C a => a -> a -> a
+ a
forall a. C a => a
one a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
s a -> a -> a
forall a. C a => a -> a -> a
+ a
alpha a -> a -> a
forall a. C a => a -> a -> a
* Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
kap)
[Int
1 .. Int
k] Partition
kappa
v :: [a]
v = (Int -> Int -> a) -> Partition -> Partition -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
s Int
m -> a
t a -> a -> a
forall a. C a => a -> a -> a
- Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
s a -> a -> a
forall a. C a => a -> a -> a
+ a
alpha a -> a -> a
forall a. C a => a -> a -> a
* Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
m)
[Int
1 .. Int
kInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1] Partition
mu
w :: [a]
w = (Int -> Int -> a) -> Partition -> Partition -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
s Int
m -> Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
m a -> a -> a
forall a. C a => a -> a -> a
- a
t a -> a -> a
forall a. C a => a -> a -> a
- a
alpha a -> a -> a
forall a. C a => a -> a -> a
* Int -> a
forall a b. (C a, C b) => a -> b
fromIntegral Int
s)
[Int
1 .. Int
mukm1Int -> Int -> Int
forall a. C a => a -> a -> a
-Int
1] (Partition -> Partition
_dualPartition Partition
mu)
prod1 :: a
prod1 = [a] -> a
forall a. C a => [a] -> a
product ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (\a
x -> a
x a -> a -> a
forall a. C a => a -> a -> a
/ (a
x a -> a -> a
forall a. C a => a -> a -> a
+ a
alpha a -> a -> a
forall a. C a => a -> a -> a
- a
forall a. C a => a
one)) [a]
u
prod2 :: a
prod2 = [a] -> a
forall a. C a => [a] -> a
product ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (\a
x -> (a
x a -> a -> a
forall a. C a => a -> a -> a
+ a
alpha) a -> a -> a
forall a. C a => a -> a -> a
/ a
x) [a]
v
prod3 :: a
prod3 = [a] -> a
forall a. C a => [a] -> a
product ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (\a
x -> (a
x a -> a -> a
forall a. C a => a -> a -> a
+ a
alpha) a -> a -> a
forall a. C a => a -> a -> a
/ a
x) [a]
w
_betaRatioOfSprays :: forall a. (Eq a, AlgField.C a)
=> Partition -> Partition -> Int -> RatioOfSprays a
_betaRatioOfSprays :: forall a.
(Eq a, C a) =>
Partition -> Partition -> Int -> RatioOfSprays a
_betaRatioOfSprays Partition
kappa Partition
mu Int
k =
((Spray a
x Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
num1 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
num2 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
num3) Spray a -> Spray a -> RatioOfSprays a
forall a. Spray a -> Spray a -> RatioOfSprays a
%:% (Spray a
den1 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
den2 Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^*^ Spray a
den3))
where
mukm1 :: Int
mukm1 = Partition
mu Partition -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! (Int
kInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1)
x :: Spray a
x = Int -> Spray a
forall a. C a => Int -> Spray a
lone Int
1 :: Spray a
u :: [Spray a]
u = (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(
\Int
s Int
kap ->
(Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
k Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
s Int -> Int -> Int
forall a. C a => a -> a -> a
+ Int
1) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> ((Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
kap Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
mukm1) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
x)
)
[Int
1 .. Int
k] Partition
kappa
v :: [Spray a]
v = (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(
\Int
s Int
m -> (Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
k Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
s) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> ((Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
m Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
mukm1) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
x)
)
[Int
1 .. Int
kInt -> Int -> Int
forall a. C a => a -> a -> a
-Int
1] Partition
mu
w :: [Spray a]
w = (Int -> Int -> Spray a) -> Partition -> Partition -> [Spray a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(
\Int
s Int
m -> (Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
m Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
k) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
+> ((Int -> BaseRing (Spray a)
forall a b. (C a, C b) => a -> b
fromIntegral (Int -> BaseRing (Spray a)) -> Int -> BaseRing (Spray a)
forall a b. (a -> b) -> a -> b
$ Int
mukm1 Int -> Int -> Int
forall a. C a => a -> a -> a
- Int
s) BaseRing (Spray a) -> Spray a -> Spray a
forall b. FunctionLike b => BaseRing b -> b -> b
*^ Spray a
x)
)
[Int
1 .. Int
mukm1Int -> Int -> Int
forall a. C a => a -> a -> a
-Int
1] (Partition -> Partition
_dualPartition Partition
mu)
num1 :: Spray a
num1 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product [Spray a]
u
den1 :: Spray a
den1 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product ([Spray a] -> Spray a) -> [Spray a] -> Spray a
forall a b. (a -> b) -> a -> b
$ (Spray a -> Spray a) -> [Spray a] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\Spray a
p -> Spray a
p Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
x Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^-^ Spray a
forall a. C a => Spray a
unitSpray) [Spray a]
u
num2 :: Spray a
num2 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product ([Spray a] -> Spray a) -> [Spray a] -> Spray a
forall a b. (a -> b) -> a -> b
$ (Spray a -> Spray a) -> [Spray a] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\Spray a
p -> Spray a
p Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
x) [Spray a]
v
den2 :: Spray a
den2 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product [Spray a]
v
num3 :: Spray a
num3 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product ([Spray a] -> Spray a) -> [Spray a] -> Spray a
forall a b. (a -> b) -> a -> b
$ (Spray a -> Spray a) -> [Spray a] -> [Spray a]
forall a b. (a -> b) -> [a] -> [b]
map (\Spray a
p -> Spray a
p Spray a -> Spray a -> Spray a
forall b. (FunctionLike b, C b) => b -> b -> b
^+^ Spray a
x) [Spray a]
w
den3 :: Spray a
den3 = [Spray a] -> Spray a
forall a. C a => [a] -> a
product [Spray a]
w
_fromInt :: (AlgRing.C a, Eq a) => Int -> a
_fromInt :: forall a. (C a, Eq a) => Int -> a
_fromInt Int
k = Int
k Int -> a -> a
forall a. (C a, Eq a) => Int -> a -> a
.^ a
forall a. C a => a
AlgRing.one
skewSchurLRCoefficients :: Partition -> Partition -> DM.Map Partition Int
skewSchurLRCoefficients :: Partition -> Partition -> Map Partition Int
skewSchurLRCoefficients Partition
lambda Partition
mu =
(Partition -> Partition) -> Map Partition Int -> Map Partition Int
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
DM.mapKeys Partition -> Partition
fromPartition (Partition -> Partition -> Map Partition Int
_lrRule Partition
lambda' Partition
mu')
where
lambda' :: Partition
lambda' = Partition -> Partition
MCP.Partition Partition
lambda
mu' :: Partition
mu' = Partition -> Partition
MCP.Partition Partition
mu
isSkewPartition :: Partition -> Partition -> Bool
isSkewPartition :: Partition -> Partition -> Bool
isSkewPartition Partition
lambda Partition
mu =
Partition -> Bool
_isPartition Partition
lambda Bool -> Bool -> Bool
&& Partition -> Bool
_isPartition Partition
mu Bool -> Bool -> Bool
&& (Int -> Bool) -> Partition -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0) ((Int -> Int -> Int) -> Partition -> Partition -> Partition
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (-) Partition
lambda Partition
mu)
sprayToMap :: Spray a -> Map [Int] a
sprayToMap :: forall a. Spray a -> Map Partition a
sprayToMap Spray a
spray =
[(Partition, a)] -> Map Partition a
forall k a. Ord k => [(k, a)] -> Map k a
DM.fromList (HashMap Partition a -> [(Partition, a)]
forall k v. HashMap k v -> [(k, v)]
HM.toList (HashMap Partition a -> [(Partition, a)])
-> HashMap Partition a -> [(Partition, a)]
forall a b. (a -> b) -> a -> b
$ (Powers -> Partition) -> Spray a -> HashMap Partition a
forall k2 k1 v.
(Eq k2, Hashable k2) =>
(k1 -> k2) -> HashMap k1 v -> HashMap k2 v
HM.mapKeys (Seq Int -> Partition
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
DF.toList (Seq Int -> Partition)
-> (Powers -> Seq Int) -> Powers -> Partition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Powers -> Seq Int
exponents) Spray a
spray)
comboToSpray :: (Eq a, AlgRing.C a) => Map Partition a -> Spray a
comboToSpray :: forall a. (Eq a, C a) => Map Partition a -> Spray a
comboToSpray Map Partition a
combo = [Spray a] -> Spray a
forall a. (Eq a, C a) => [Spray a] -> Spray a
sumOfSprays
[ let part' :: Seq Int
part' = Partition -> Seq Int
forall a. [a] -> Seq a
S.fromList Partition
part in Powers -> a -> Spray a
forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton (Seq Int -> Int -> Powers
Powers Seq Int
part' (Seq Int -> Int
forall a. Seq a -> Int
S.length Seq Int
part')) a
c
| (Partition
part, a
c) <- Map Partition a -> [(Partition, a)]
forall k a. Map k a -> [(k, a)]
DM.toList Map Partition a
combo ]