{-# LANGUAGE CPP, BangPatterns, FlexibleInstances, TypeSynonymInstances, MultiParamTypeClasses #-}
module Math.Combinat.Tableaux where
import Data.List
import Math.Combinat.Classes
import Math.Combinat.Numbers ( factorial , binomial )
import Math.Combinat.Partitions.Integer
import Math.Combinat.Partitions.Integer.IntList ( _dualPartition )
import Math.Combinat.ASCII
import Math.Combinat.Helper
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
type Tableau a = [[a]]
asciiTableau :: Show a => Tableau a -> ASCII
asciiTableau t = tabulate (HRight,VTop) (HSepSpaces 1, VSepEmpty)
$ (map . map) asciiShow
$ t
instance CanBeEmpty (Tableau a) where
empty = []
isEmpty = null
instance Show a => DrawASCII (Tableau a) where
ascii = asciiTableau
_tableauShape :: Tableau a -> [Int]
_tableauShape t = map length t
tableauShape :: Tableau a -> Partition
tableauShape t = toPartition (_tableauShape t)
instance HasShape (Tableau a) Partition where
shape = tableauShape
tableauWeight :: Tableau a -> Int
tableauWeight = sum' . map length
instance HasWeight (Tableau a) where
weight = tableauWeight
dualTableau :: Tableau a -> Tableau a
dualTableau = transpose
instance HasDuality (Tableau a) where
dual = dualTableau
tableauContent :: Tableau a -> [a]
tableauContent = concat
hooks :: Partition -> Tableau (Int,Int)
hooks part = zipWith f p [1..] where
p = fromPartition part
q = _dualPartition p
f l i = zipWith (\x y -> (x-i+1,y)) q [l,l-1..1]
hookLengths :: Partition -> Tableau Int
hookLengths part = (map . map) (\(i,j) -> i+j-1) (hooks part)
rowWord :: Tableau a -> [a]
rowWord = concat . reverse
rowWordToTableau :: Ord a => [a] -> Tableau a
rowWordToTableau xs = reverse rows where
rows = break xs
break [] = [[]]
break [x] = [[x]]
break (x:xs@(y:_)) = if x>y
then [x] : break xs
else let (h:t) = break xs in (x:h):t
columnWord :: Tableau a -> [a]
columnWord = rowWord . transpose
columnWordToTableau :: Ord a => [a] -> Tableau a
columnWordToTableau = transpose . rowWordToTableau
isLatticeWord :: [Int] -> Bool
isLatticeWord = go Map.empty where
go :: Map Int Int -> [Int] -> Bool
go _ [] = True
go !table (i:is) =
if check i
then go table' is
else False
where
table' = Map.insertWith (+) i 1 table
check j = j==1 || cnt (j-1) >= cnt j
cnt j = case Map.lookup j table' of
Just k -> k
Nothing -> 0
isSemiStandardTableau :: Tableau Int -> Bool
isSemiStandardTableau t = weak && strict where
weak = and [ isWeaklyIncreasing xs | xs <- t ]
strict = and [ isStrictlyIncreasing ys | ys <- dt ]
dt = dualTableau t
semiStandardYoungTableaux :: Int -> Partition -> [Tableau Int]
semiStandardYoungTableaux n part = worker (repeat 0) shape where
shape = fromPartition part
worker _ [] = [[]]
worker prevRow (s:ss)
= [ (r:rs) | r <- row n s 1 prevRow, rs <- worker (map (+1) r) ss ]
row :: Int -> Int -> Int -> [Int] -> [[Int]]
row _ 0 _ _ = [[]]
row n len prev (x:xs) = [ (a:as) | a <- [max x prev..n] , as <- row n (len-1) a xs ]
countSemiStandardYoungTableaux :: Int -> Partition -> Integer
countSemiStandardYoungTableaux n shape = k `div` h where
h = product $ map fromIntegral $ concat $ hookLengths shape
k = product [ fromIntegral (n+j-i) | (i,j) <- elements shape ]
isStandardTableau :: Tableau Int -> Bool
isStandardTableau t = isSemiStandardTableau t && sort (concat t) == [1..n] where
n = sum [ length xs | xs <- t ]
standardYoungTableaux :: Partition -> [Tableau Int]
standardYoungTableaux shape' = map rev $ tableaux shape where
shape = fromPartition shape'
rev = reverse . map reverse
tableaux :: [Int] -> [Tableau Int]
tableaux p =
case p of
[] -> [[]]
[n] -> [[[n,n-1..1]]]
_ -> worker (n,k) 0 [] p
where
n = sum p
k = length p
worker :: (Int,Int) -> Int -> [Int] -> [Int] -> [Tableau Int]
worker _ _ _ [] = []
worker nk i ls (x:rs) = case rs of
(y:_) -> if x==y
then worker nk (i+1) (x:ls) rs
else worker2 nk i ls x rs
[] -> worker2 nk i ls x rs
worker2 :: (Int,Int) -> Int -> [Int] -> Int -> [Int] -> [Tableau Int]
worker2 nk@(n,k) i ls x rs = new ++ worker nk (i+1) (x:ls) rs where
old = if x>1
then tableaux $ reverse ls ++ (x-1) : rs
else map ([]:) $ tableaux $ reverse ls ++ rs
a = k-1-i
new =
map (f a) old
f :: Int -> Tableau Int -> Tableau Int
f _ [] = []
f 0 (t:ts) = (n:t) : f (-1) ts
f j (t:ts) = t : f (j-1) ts
countStandardYoungTableaux :: Partition -> Integer
countStandardYoungTableaux part =
factorial n `div` h where
h = product $ map fromIntegral $ concat $ hookLengths part
n = weight part