{-# LANGUAGE BangPatterns #-}
module Math.Combinat.Partitions.Plane where
import Data.List
import Data.Array
import Math.Combinat.Classes
import Math.Combinat.Partitions
import Math.Combinat.Tableaux as Tableaux
import Math.Combinat.Helper
newtype PlanePart = PlanePart [[Int]] deriving (Eq,Ord,Show)
fromPlanePart :: PlanePart -> [[Int]]
fromPlanePart (PlanePart xs) = xs
isValidPlanePart :: [[Int]] -> Bool
isValidPlanePart pps =
and [ table!(i,j) >= table!(i ,j+1) &&
table!(i,j) >= table!(i+1,j )
| i<-[0..y-1] , j<-[0..x-1]
]
where
table :: Array (Int,Int) Int
table = accumArray const 0 ((0,0),(y,x)) [ ((i,j),k) | (i,ps) <- zip [0..] pps , (j,k) <- zip [0..] ps ]
y = length pps
x = maximum (map length pps)
instance CanBeEmpty PlanePart where
isEmpty = null . fromPlanePart
empty = PlanePart []
toPlanePart :: [[Int]] -> PlanePart
toPlanePart pps = if isValidPlanePart pps
then PlanePart $ filter (not . null) $ map (filter (>0)) $ pps
else error "toPlanePart: not a plane partition"
planePartShape :: PlanePart -> Partition
planePartShape = Tableaux.tableauShape . fromPlanePart
planePartZHeight :: PlanePart -> Int
planePartZHeight (PlanePart xs) =
case xs of
((h:_):_) -> h
_ -> 0
planePartWeight :: PlanePart -> Int
planePartWeight (PlanePart xs) = sum' (map sum' xs)
instance HasWeight PlanePart where
weight = planePartWeight
singleLayer :: Partition -> PlanePart
singleLayer = PlanePart . map (\k -> replicate k 1) . fromPartition
stackLayers :: [Partition] -> PlanePart
stackLayers layers = if and [ isSubPartitionOf p q | (q,p) <- pairs layers ]
then unsafeStackLayers layers
else error "stackLayers: the layers do not form a plane partition"
unsafeStackLayers :: [Partition] -> PlanePart
unsafeStackLayers [] = PlanePart []
unsafeStackLayers (bottom:rest) = PlanePart $ foldl addLayer (fromPlanePart $ singleLayer bottom) rest where
addLayer :: [[Int]] -> Partition -> [[Int]]
addLayer xxs (Partition ps) = [ zipWith (+) xs (replicate p 1 ++ repeat 0) | (xs,p) <- zip xxs (ps ++ repeat 0) ]
planePartLayers :: PlanePart -> [Partition]
planePartLayers pp@(PlanePart xs) = [ layer h | h<-[1..planePartZHeight pp] ] where
layer h = Partition $ filter (>0) $ map sum' $ (map . map) (f h) xs
f h = \k -> if k>=h then 1 else 0
planePartitions :: Int -> [PlanePart]
planePartitions d
| d < 0 = []
| d == 0 = [PlanePart []]
| otherwise = concat [ go (d-n) [p] | n<-[1..d] , p<-partitions n ]
where
go :: Int -> [Partition] -> [PlanePart]
go 0 acc = [unsafeStackLayers (reverse acc)]
go !rem acc@(h:_) = concat [ go (rem-k) (this:acc) | k<-[1..rem] , this <- subPartitions k h ]