module Math.Combinat.Diagrams.Tableaux.Skew where
import Math.Combinat.Partitions
import Math.Combinat.Partitions.Skew
import Math.Combinat.Tableaux.Skew
import Math.Combinat.Diagrams.Partitions.Skew
import Linear.Vector
import Data.Colour
import Diagrams.Core
import Diagrams.Prelude
import Diagrams.TwoD.Text
drawSkewTableau
:: (Renderable (Path V2 Double) b, Renderable (Text Double) b)
=> SkewTableau Int
-> QDiagram b V2 Double Any
drawSkewTableau = drawSkewTableau' EnglishNotation black False
drawSkewTableau'
:: (Renderable (Path V2 Double) b, Renderable (Text Double) b)
=> PartitionConvention
-> Colour Double
-> Bool
-> SkewTableau Int
-> QDiagram b V2 Double Any
drawSkewTableau' convention color drawInner tableau = numbers <> boxes where
skewPart = skewTableauShape tableau
xas :: [(Int,[Int])]
SkewTableau xas = tableau
n = length xas
numbers = mconcat [ number (j+x) i a | (i,(x,as)) <- zip [(0::Int)..n1] xas , (j,a)<-zip [(0::Int)..] as ]
# lc color
number x y a = trafo x y $ scale (0.85 :: Double) $ 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))
boxes = if drawInner
then drawSkewPartitionBoxesWithInner (lightgray,black) convention skewPart
else drawSkewPartitionBoxes convention skewPart