-- | Tableau diagrams {-# LANGUAGE FlexibleContexts #-} module Math.Combinat.Diagrams.Tableaux where -------------------------------------------------------------------------------- import Math.Combinat.Tableaux import Math.Combinat.Partitions import Math.Combinat.Diagrams.Partitions -- import Data.Monoid import Data.VectorSpace import Data.Colour import Diagrams.Core import Diagrams.Prelude import Diagrams.TwoD.Text -------------------------------------------------------------------------------- -- | Draws a Ferrers diagram with the default settings (English notation, black) drawTableau :: (Renderable (Path R2) b, Renderable Text b) => Tableau Int -> Diagram b R2 drawTableau = drawTableau' EnglishNotation black drawTableau' :: (Renderable (Path R2) b, Renderable Text b) => PartitionConvention -- ^ orientation -> Colour Double -- ^ color -> Tableau Int -> Diagram b R2 drawTableau' convention color tableau = numbers <> boxes where part = shape tableau ps = fromPartition part :: [Int] n = length ps numbers = mconcat [ number j i a | i<-[(0::Int)..n-1], (j,a)<-zip [(0::Int)..] (tableau!!i) ] # lc color number x y a = trafo x y $ scale 0.85 $ text (show a) # lw none # lc color # fc color v = 0.22 :: Double trafo x y = case convention of EnglishNotation -> translate (r2 (0.5 + fromIntegral x , - 1 + v - fromIntegral y)) EnglishNotationCCW -> translate (r2 (0.5 + fromIntegral y , v + fromIntegral x)) FrenchNotation -> translate (r2 (0.5 + fromIntegral x , v + fromIntegral y)) -- numberSize = 0.35 :: Double -- linewidth = 0.025 :: Double boxes = drawPartitionBoxes convention part --------------------------------------------------------------------------------