{-# LANGUAGE BangPatterns, ScopedTypeVariables #-}
module Math.Combinat.Tableaux.GelfandTsetlin where
import Data.List
import Data.Maybe
import Data.Monoid
import Data.Ord
import Control.Monad
import Control.Monad.Trans.State
import Data.Map (Map)
import qualified Data.Map as Map
import Math.Combinat.Partitions.Integer
import Math.Combinat.Tableaux
import Math.Combinat.Helper
import Math.Combinat.ASCII
kostkaNumber :: Partition -> Partition -> Int
kostkaNumber :: Partition -> Partition -> Int
kostkaNumber = Partition -> Partition -> Int
countKostkaGelfandTsetlinPatterns
kostkaNumberReferenceNaive :: Partition -> Partition -> Int
kostkaNumberReferenceNaive :: Partition -> Partition -> Int
kostkaNumberReferenceNaive Partition
plambda pmu :: Partition
pmu@(Partition [Int]
mu) = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
stuff where
stuff :: [Int]
stuff = [ (Int
1::Int) | Tableau Int
t <- Int -> Partition -> [Tableau Int]
semiStandardYoungTableaux Int
k Partition
plambda , Tableau Int -> Bool
forall a (t :: * -> *).
(Ord a, Foldable t, Num a, Enum a) =>
t [a] -> Bool
cond Tableau Int
t ]
k :: Int
k = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
mu
cond :: t [a] -> Bool
cond t [a]
t = [ ([a] -> a
forall a. [a] -> a
head [a]
xs, [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs) | [a]
xs <- [a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
group ([a] -> [a]
forall a. Ord a => [a] -> [a]
sort ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ t [a] -> [a]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat t [a]
t) ] [(a, Int)] -> [(a, Int)] -> Bool
forall a. Eq a => a -> a -> Bool
== [a] -> [Int] -> [(a, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [a
1..] [Int]
mu
{-# SPECIALIZE kostkaNumbersWithGivenLambda :: Partition -> Map Partition Int #-}
{-# SPECIALIZE kostkaNumbersWithGivenLambda :: Partition -> Map Partition Integer #-}
kostkaNumbersWithGivenLambda :: forall coeff. Num coeff => Partition -> Map Partition coeff
kostkaNumbersWithGivenLambda :: Partition -> Map Partition coeff
kostkaNumbersWithGivenLambda plambda :: Partition
plambda@(Partition [Int]
lam) = State (Map Partition (Map Partition coeff)) (Map Partition coeff)
-> Map Partition (Map Partition coeff) -> Map Partition coeff
forall s a. State s a -> s -> a
evalState ([Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
worker [Int]
lam) Map Partition (Map Partition coeff)
forall k a. Map k a
Map.empty where
worker :: [Int] -> State (Map Partition (Map Partition coeff)) (Map Partition coeff)
worker :: [Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
worker [Int]
unlam = case [Int]
unlam of
[] -> Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall a b. (a -> b) -> a -> b
$ Partition -> coeff -> Map Partition coeff
forall k a. k -> a -> Map k a
Map.singleton ([Int] -> Partition
Partition []) coeff
1
[Int]
_ -> do
Map Partition (Map Partition coeff)
cache <- StateT
(Map Partition (Map Partition coeff))
Identity
(Map Partition (Map Partition coeff))
forall (m :: * -> *) s. Monad m => StateT s m s
get
case Partition
-> Map Partition (Map Partition coeff)
-> Maybe (Map Partition coeff)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ([Int] -> Partition
Partition [Int]
unlam) Map Partition (Map Partition coeff)
cache of
Just Map Partition coeff
sol -> Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall (m :: * -> *) a. Monad m => a -> m a
return Map Partition coeff
sol
Maybe (Map Partition coeff)
Nothing -> do
let s :: Int
s = (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Int
0 [Int]
unlam
[Map Partition coeff]
subsols <- Tableau Int
-> ([Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> StateT
(Map Partition (Map Partition coeff))
Identity
[Map Partition coeff]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM ([Int] -> Tableau Int
prevLambdas0 [Int]
unlam) (([Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> StateT
(Map Partition (Map Partition coeff))
Identity
[Map Partition coeff])
-> ([Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> StateT
(Map Partition (Map Partition coeff))
Identity
[Map Partition coeff]
forall a b. (a -> b) -> a -> b
$ \[Int]
p -> do
Map Partition coeff
sub <- [Int]
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
worker [Int]
p
let t :: Int
t = Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int -> Int -> Int) -> Int -> [Int] -> Int
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Int
0 [Int]
p
f :: (Partition, b) -> Maybe (Partition, b)
f (Partition [Int]
xs , b
c) = case [Int]
xs of
(Int
y:[Int]
_) -> if Int
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
y then (Partition, b) -> Maybe (Partition, b)
forall a. a -> Maybe a
Just ([Int] -> Partition
Partition (Int
tInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
xs) , b
c) else Maybe (Partition, b)
forall a. Maybe a
Nothing
[] -> if Int
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then (Partition, b) -> Maybe (Partition, b)
forall a. a -> Maybe a
Just ([Int] -> Partition
Partition [Int
t] , b
c) else Maybe (Partition, b)
forall a. Maybe a
Nothing
if Int
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall a b. (a -> b) -> a -> b
$ [(Partition, coeff)] -> Map Partition coeff
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Partition, coeff)] -> Map Partition coeff)
-> [(Partition, coeff)] -> Map Partition coeff
forall a b. (a -> b) -> a -> b
$ ((Partition, coeff) -> Maybe (Partition, coeff))
-> [(Partition, coeff)] -> [(Partition, coeff)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Partition, coeff) -> Maybe (Partition, coeff)
forall b. (Partition, b) -> Maybe (Partition, b)
f ([(Partition, coeff)] -> [(Partition, coeff)])
-> [(Partition, coeff)] -> [(Partition, coeff)]
forall a b. (a -> b) -> a -> b
$ Map Partition coeff -> [(Partition, coeff)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Partition coeff
sub
else Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff))
-> Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall a b. (a -> b) -> a -> b
$ Map Partition coeff
forall k a. Map k a
Map.empty
let sol :: Map Partition coeff
sol = (coeff -> coeff -> coeff)
-> [Map Partition coeff] -> Map Partition coeff
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
(a -> a -> a) -> f (Map k a) -> Map k a
Map.unionsWith coeff -> coeff -> coeff
forall a. Num a => a -> a -> a
(+) [Map Partition coeff]
subsols
Map Partition (Map Partition coeff)
-> StateT (Map Partition (Map Partition coeff)) Identity ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Map Partition (Map Partition coeff)
-> StateT (Map Partition (Map Partition coeff)) Identity ())
-> Map Partition (Map Partition coeff)
-> StateT (Map Partition (Map Partition coeff)) Identity ()
forall a b. (a -> b) -> a -> b
$! (Partition
-> Map Partition coeff
-> Map Partition (Map Partition coeff)
-> Map Partition (Map Partition coeff)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert ([Int] -> Partition
Partition [Int]
unlam) Map Partition coeff
sol Map Partition (Map Partition coeff)
cache)
Map Partition coeff
-> State
(Map Partition (Map Partition coeff)) (Map Partition coeff)
forall (m :: * -> *) a. Monad m => a -> m a
return Map Partition coeff
sol
prevLambdas0 :: [Int] -> [[Int]]
prevLambdas0 :: [Int] -> Tableau Int
prevLambdas0 (Int
l:[Int]
ls) = Int -> [Int] -> Tableau Int
forall a. (Enum a, Num a) => a -> [a] -> [[a]]
go Int
l [Int]
ls where
go :: a -> [a] -> [[a]]
go a
b [a
a] = [ [a
x] | a
x <- [a
a..a
b] ] [[a]] -> [[a]] -> [[a]]
forall a. [a] -> [a] -> [a]
++ [ [a
x,a
y] | a
x <- [a
a..a
b] , a
y<-[a
1..a
a] ]
go a
b (a
a:[a]
as) = [ a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs | a
x <- [a
a..a
b] , [a]
xs <- a -> [a] -> [[a]]
go a
a [a]
as ]
go a
b [] = [] [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [ [a
j] | a
j <- [a
1..a
b] ]
prevLambdas0 [] = []
kostkaNumbersWithGivenMu :: Partition -> Map Partition Int
kostkaNumbersWithGivenMu :: Partition -> Map Partition Int
kostkaNumbersWithGivenMu (Partition [Int]
mu) = [Int] -> Map Partition Int
forall coeff. Num coeff => [Int] -> Map Partition coeff
iteratedPieriRule ([Int] -> [Int]
forall a. [a] -> [a]
reverse [Int]
mu)
type GT = [[Int]]
asciiGT :: GT -> ASCII
asciiGT :: Tableau Int -> ASCII
asciiGT Tableau Int
gt = (HAlign, VAlign) -> (HSep, VSep) -> [[ASCII]] -> ASCII
tabulate (HAlign
HRight,VAlign
VTop) (Int -> HSep
HSepSpaces Int
1, VSep
VSepEmpty)
([[ASCII]] -> ASCII) -> [[ASCII]] -> ASCII
forall a b. (a -> b) -> a -> b
$ (([Int] -> [ASCII]) -> Tableau Int -> [[ASCII]]
forall a b. (a -> b) -> [a] -> [b]
map (([Int] -> [ASCII]) -> Tableau Int -> [[ASCII]])
-> ((Int -> ASCII) -> [Int] -> [ASCII])
-> (Int -> ASCII)
-> Tableau Int
-> [[ASCII]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> ASCII) -> [Int] -> [ASCII]
forall a b. (a -> b) -> [a] -> [b]
map) Int -> ASCII
forall a. Show a => a -> ASCII
asciiShow
(Tableau Int -> [[ASCII]]) -> Tableau Int -> [[ASCII]]
forall a b. (a -> b) -> a -> b
$ Tableau Int
gt
kostkaGelfandTsetlinPatterns :: Partition -> Partition -> [GT]
kostkaGelfandTsetlinPatterns :: Partition -> Partition -> [Tableau Int]
kostkaGelfandTsetlinPatterns Partition
lambda (Partition [Int]
mu) = Partition -> [Int] -> [Tableau Int]
kostkaGelfandTsetlinPatterns' Partition
lambda [Int]
mu
kostkaGelfandTsetlinPatterns' :: Partition -> [Int] -> [GT]
kostkaGelfandTsetlinPatterns' :: Partition -> [Int] -> [Tableau Int]
kostkaGelfandTsetlinPatterns' plam :: Partition
plam@(Partition [Int]
lambda0) [Int]
mu0
| [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Int]
mu0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = []
| Int
wlam Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = if Int
wmu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then [ [] ] else []
| Int
wmu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
wlam Bool -> Bool -> Bool
&& Partition
plam Partition -> Partition -> Bool
`dominates` Partition
pmu = [Tableau Int]
list
| Bool
otherwise = []
where
pmu :: Partition
pmu = [Int] -> Partition
mkPartition [Int]
mu0
nlam :: Int
nlam = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
lambda0
nmu :: Int
nmu = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
mu0
n :: Int
n = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nlam Int
nmu
lambda :: [Int]
lambda = [Int]
lambda0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nlam) Int
0
mu :: [Int]
mu = [Int]
mu0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nmu ) Int
0
revlam :: [Int]
revlam = [Int] -> [Int]
forall a. [a] -> [a]
reverse [Int]
lambda
wmu :: Int
wmu = [Int] -> Int
forall a. Num a => [a] -> a
sum' [Int]
mu
wlam :: Int
wlam = [Int] -> Int
forall a. Num a => [a] -> a
sum' [Int]
lambda
list :: [Tableau Int]
list = [Int] -> [Int] -> [Int] -> [Int] -> Tableau Int -> [Tableau Int]
worker
[Int]
revlam
((Int -> Int -> Int) -> [Int] -> [Int]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) [Int]
mu)
(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Int
0)
(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n ) Int
0)
[]
worker
:: [Int]
-> [Int]
-> [Int]
-> [Int]
-> [[Int]]
-> [GT]
worker :: [Int] -> [Int] -> [Int] -> [Int] -> Tableau Int -> [Tableau Int]
worker (Int
rl:[Int]
rls) (Int
smu:[Int]
smus) (Int
a:[Int]
acc) (Int
lastx0:[Int]
lastrowt) Tableau Int
table = [Tableau Int]
stuff
where
x0 :: Int
x0 = Int
smu Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
a
stuff :: [Tableau Int]
stuff = [[Tableau Int]] -> [Tableau Int]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [Int] -> [Int] -> [Int] -> [Int] -> Tableau Int -> [Tableau Int]
worker [Int]
rls [Int]
smus ((Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) [Int]
acc ([Int] -> [Int]
forall a. [a] -> [a]
tail [Int]
row)) ([Int] -> [Int]
forall a. [a] -> [a]
init [Int]
row) ([Int]
row[Int] -> Tableau Int -> Tableau Int
forall a. a -> [a] -> [a]
:Tableau Int
table)
| [Int]
row <- Int -> [Int] -> [Int] -> Tableau Int
boundedNonIncrSeqs' Int
x0 ((Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
rl) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
lastx0 Int
x0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
lastrowt)) [Int]
lambda
]
worker [Int
rl] [Int]
_ [Int]
_ [Int]
_ Tableau Int
table = [ [Int
rl][Int] -> Tableau Int -> Tableau Int
forall a. a -> [a] -> [a]
:Tableau Int
table ]
worker [] [Int]
_ [Int]
_ [Int]
_ Tableau Int
_ = [ [] ]
boundedNonIncrSeqs' :: Int -> [Int] -> [Int] -> [[Int]]
boundedNonIncrSeqs' :: Int -> [Int] -> [Int] -> Tableau Int
boundedNonIncrSeqs' = Int -> [Int] -> [Int] -> Tableau Int
forall a. (Ord a, Num a, Enum a) => a -> [a] -> [a] -> [[a]]
go where
go :: a -> [a] -> [a] -> [[a]]
go a
h0 (a
a:[a]
as) (a
b:[a]
bs) = [ a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
hs | a
h <- [(a -> a -> a
forall a. Ord a => a -> a -> a
max a
0 a
a)..(a -> a -> a
forall a. Ord a => a -> a -> a
min a
h0 a
b)] , [a]
hs <- a -> [a] -> [a] -> [[a]]
go a
h [a]
as [a]
bs ]
go a
_ [] [a]
_ = [[]]
go a
_ [a]
_ [] = [[]]
countKostkaGelfandTsetlinPatterns :: Partition -> Partition -> Int
countKostkaGelfandTsetlinPatterns :: Partition -> Partition -> Int
countKostkaGelfandTsetlinPatterns plam :: Partition
plam@(Partition [Int]
lambda0) pmu :: Partition
pmu@(Partition [Int]
mu0)
| Int
wlam Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = if Int
wmu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
1 else Int
0
| Int
wmu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
wlam Bool -> Bool -> Bool
&& Partition
plam Partition -> Partition -> Bool
`dominates` Partition
pmu = Int
cnt
| Bool
otherwise = Int
0
where
nlam :: Int
nlam = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
lambda0
nmu :: Int
nmu = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
mu0
n :: Int
n = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
nlam Int
nmu
lambda :: [Int]
lambda = [Int]
lambda0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nlam) Int
0
mu :: [Int]
mu = [Int]
mu0 [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
nmu ) Int
0
revlam :: [Int]
revlam = [Int] -> [Int]
forall a. [a] -> [a]
reverse [Int]
lambda
wmu :: Int
wmu = [Int] -> Int
forall a. Num a => [a] -> a
sum' [Int]
mu
wlam :: Int
wlam = [Int] -> Int
forall a. Num a => [a] -> a
sum' [Int]
lambda
cnt :: Int
cnt = [Int] -> [Int] -> [Int] -> [Int] -> Int
worker
[Int]
revlam
((Int -> Int -> Int) -> [Int] -> [Int]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) [Int]
mu)
(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Int
0)
(Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate (Int
n ) Int
0)
worker
:: [Int]
-> [Int]
-> [Int]
-> [Int]
-> Int
worker :: [Int] -> [Int] -> [Int] -> [Int] -> Int
worker (Int
rl:[Int]
rls) (Int
smu:[Int]
smus) (Int
a:[Int]
acc) (Int
lastx0:[Int]
lastrowt) = Int
stuff
where
x0 :: Int
x0 = Int
smu Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
a
stuff :: Int
stuff = [Int] -> Int
forall a. Num a => [a] -> a
sum'
[ [Int] -> [Int] -> [Int] -> [Int] -> Int
worker [Int]
rls [Int]
smus ((Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) [Int]
acc ([Int] -> [Int]
forall a. [a] -> [a]
tail [Int]
row)) ([Int] -> [Int]
forall a. [a] -> [a]
init [Int]
row)
| [Int]
row <- Int -> [Int] -> [Int] -> Tableau Int
boundedNonIncrSeqs' Int
x0 ((Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
rl) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
lastx0 Int
x0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
lastrowt)) [Int]
lambda
]
worker [Int
rl] [Int]
_ [Int]
_ [Int]
_ = Int
1
worker [] [Int]
_ [Int]
_ [Int]
_ = Int
1
boundedNonIncrSeqs' :: Int -> [Int] -> [Int] -> [[Int]]
boundedNonIncrSeqs' :: Int -> [Int] -> [Int] -> Tableau Int
boundedNonIncrSeqs' = Int -> [Int] -> [Int] -> Tableau Int
forall a. (Ord a, Num a, Enum a) => a -> [a] -> [a] -> [[a]]
go where
go :: a -> [a] -> [a] -> [[a]]
go a
h0 (a
a:[a]
as) (a
b:[a]
bs) = [ a
ha -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
hs | a
h <- [(a -> a -> a
forall a. Ord a => a -> a -> a
max a
0 a
a)..(a -> a -> a
forall a. Ord a => a -> a -> a
min a
h0 a
b)] , [a]
hs <- a -> [a] -> [a] -> [[a]]
go a
h [a]
as [a]
bs ]
go a
_ [] [a]
_ = [[]]
go a
_ [a]
_ [] = [[]]
iteratedPieriRule :: Num coeff => [Int] -> Map Partition coeff
iteratedPieriRule :: [Int] -> Map Partition coeff
iteratedPieriRule = Partition -> [Int] -> Map Partition coeff
forall coeff.
Num coeff =>
Partition -> [Int] -> Map Partition coeff
iteratedPieriRule' ([Int] -> Partition
Partition [])
iteratedPieriRule' :: Num coeff => Partition -> [Int] -> Map Partition coeff
iteratedPieriRule' :: Partition -> [Int] -> Map Partition coeff
iteratedPieriRule' Partition
plambda [Int]
ns = (Partition, coeff) -> [Int] -> Map Partition coeff
forall coeff.
Num coeff =>
(Partition, coeff) -> [Int] -> Map Partition coeff
iteratedPieriRule'' (Partition
plambda,coeff
1) [Int]
ns
{-# SPECIALIZE iteratedPieriRule'' :: (Partition,Int ) -> [Int] -> Map Partition Int #-}
{-# SPECIALIZE iteratedPieriRule'' :: (Partition,Integer) -> [Int] -> Map Partition Integer #-}
iteratedPieriRule'' :: Num coeff => (Partition,coeff) -> [Int] -> Map Partition coeff
iteratedPieriRule'' :: (Partition, coeff) -> [Int] -> Map Partition coeff
iteratedPieriRule'' (Partition
plambda,coeff
coeff0) [Int]
ns = Map Partition coeff -> [Int] -> Map Partition coeff
forall a. Num a => Map Partition a -> [Int] -> Map Partition a
worker (Partition -> coeff -> Map Partition coeff
forall k a. k -> a -> Map k a
Map.singleton Partition
plambda coeff
coeff0) [Int]
ns where
worker :: Map Partition a -> [Int] -> Map Partition a
worker Map Partition a
old [] = Map Partition a
old
worker Map Partition a
old (Int
n:[Int]
ns) = Map Partition a -> [Int] -> Map Partition a
worker Map Partition a
new [Int]
ns where
stuff :: [(a, [Partition])]
stuff = [ (a
coeff, Partition -> Int -> [Partition]
pieriRule Partition
lam Int
n) | (Partition
lam,a
coeff) <- Map Partition a -> [(Partition, a)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Partition a
old ]
new :: Map Partition a
new = (Map Partition a -> (a, [Partition]) -> Map Partition a)
-> Map Partition a -> [(a, [Partition])] -> Map Partition a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Map Partition a -> (a, [Partition]) -> Map Partition a
forall (t :: * -> *) k a.
(Foldable t, Ord k, Num a) =>
Map k a -> (a, t k) -> Map k a
f Map Partition a
forall k a. Map k a
Map.empty [(a, [Partition])]
stuff
f :: Map k a -> (a, t k) -> Map k a
f Map k a
t0 (a
c,t k
ps) = (Map k a -> k -> Map k a) -> Map k a -> t k -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Map k a
t k
p -> (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith a -> a -> a
forall a. Num a => a -> a -> a
(+) k
p a
c Map k a
t) Map k a
t0 t k
ps
iteratedDualPieriRule :: Num coeff => [Int] -> Map Partition coeff
iteratedDualPieriRule :: [Int] -> Map Partition coeff
iteratedDualPieriRule = Partition -> [Int] -> Map Partition coeff
forall coeff.
Num coeff =>
Partition -> [Int] -> Map Partition coeff
iteratedDualPieriRule' ([Int] -> Partition
Partition [])
iteratedDualPieriRule' :: Num coeff => Partition -> [Int] -> Map Partition coeff
iteratedDualPieriRule' :: Partition -> [Int] -> Map Partition coeff
iteratedDualPieriRule' Partition
plambda [Int]
ns = (Partition, coeff) -> [Int] -> Map Partition coeff
forall coeff.
Num coeff =>
(Partition, coeff) -> [Int] -> Map Partition coeff
iteratedDualPieriRule'' (Partition
plambda,coeff
1) [Int]
ns
{-# SPECIALIZE iteratedDualPieriRule'' :: (Partition,Int ) -> [Int] -> Map Partition Int #-}
{-# SPECIALIZE iteratedDualPieriRule'' :: (Partition,Integer) -> [Int] -> Map Partition Integer #-}
iteratedDualPieriRule'' :: Num coeff => (Partition,coeff) -> [Int] -> Map Partition coeff
iteratedDualPieriRule'' :: (Partition, coeff) -> [Int] -> Map Partition coeff
iteratedDualPieriRule'' (Partition
plambda,coeff
coeff0) [Int]
ns = Map Partition coeff -> [Int] -> Map Partition coeff
forall a. Num a => Map Partition a -> [Int] -> Map Partition a
worker (Partition -> coeff -> Map Partition coeff
forall k a. k -> a -> Map k a
Map.singleton Partition
plambda coeff
coeff0) [Int]
ns where
worker :: Map Partition a -> [Int] -> Map Partition a
worker Map Partition a
old [] = Map Partition a
old
worker Map Partition a
old (Int
n:[Int]
ns) = Map Partition a -> [Int] -> Map Partition a
worker Map Partition a
new [Int]
ns where
stuff :: [(a, [Partition])]
stuff = [ (a
coeff, Partition -> Int -> [Partition]
dualPieriRule Partition
lam Int
n) | (Partition
lam,a
coeff) <- Map Partition a -> [(Partition, a)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Partition a
old ]
new :: Map Partition a
new = (Map Partition a -> (a, [Partition]) -> Map Partition a)
-> Map Partition a -> [(a, [Partition])] -> Map Partition a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Map Partition a -> (a, [Partition]) -> Map Partition a
forall (t :: * -> *) k a.
(Foldable t, Ord k, Num a) =>
Map k a -> (a, t k) -> Map k a
f Map Partition a
forall k a. Map k a
Map.empty [(a, [Partition])]
stuff
f :: Map k a -> (a, t k) -> Map k a
f Map k a
t0 (a
c,t k
ps) = (Map k a -> k -> Map k a) -> Map k a -> t k -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Map k a
t k
p -> (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith a -> a -> a
forall a. Num a => a -> a -> a
(+) k
p a
c Map k a
t) Map k a
t0 t k
ps