module Diagrams.TwoD.Layout.Grid
    (
      gridCat
    , gridCat'
    , gridSnake
    , gridSnake'
    , gridWith
    , sameBoundingRect
    , sameBoundingSquare
    ) where
import           Data.List        (maximumBy)
import           Data.Ord         (comparing)
import           Data.List.Split  (chunksOf)
import           Diagrams.Prelude
gridCat
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => [QDiagram b V2 n Any]
  -> QDiagram b V2 n Any
gridCat diagrams = gridCat' (intSqrt $ length diagrams) diagrams
gridCat'
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => Int -> [QDiagram b V2 n Any]
  -> QDiagram b V2 n Any
gridCat' = gridAnimal id
gridSnake
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => [QDiagram b V2 n Any]
  -> QDiagram b V2 n Any
gridSnake diagrams = gridSnake' (intSqrt $ length diagrams) diagrams
gridSnake'
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => Int -> [QDiagram b V2 n Any]
  -> QDiagram b V2 n Any
gridSnake' = gridAnimal (everyOther reverse)
gridAnimal
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => ([[QDiagram b V2 n Any]] -> [[QDiagram b V2 n Any]]) -> Int -> [QDiagram b V2 n Any]
  -> QDiagram b V2 n Any
gridAnimal rowFunction cols = vcat . map hcat . rowFunction
    . chunksOf cols . sameBoundingRect . padList cols mempty
gridWith
  :: (Renderable (Path V2 n) b, TypeableFloat n)
  => (Int -> Int -> QDiagram b V2 n Any) -> (Int, Int)
  -> QDiagram b V2 n Any
gridWith f (cols, rows) = gridCat' cols diagrams
  where
    diagrams = [ f x y | y <- [0..rows  1] , x <- [0..cols  1] ]
sameBoundingSquare
  :: forall b n. (Renderable (Path V2 n) b, TypeableFloat n)
  => [QDiagram b V2 n Any]
  -> [QDiagram b V2 n Any]
sameBoundingSquare diagrams = map frameOne diagrams
  where
    biggest        = maximumBy (comparing maxDim) diagrams
    maxDim diagram = max (width diagram) (height diagram)
    centerP        = centerPoint biggest
    padSquare      = (square (maxDim biggest) :: D V2 n) # phantom
    frameOne       = atop padSquare . moveOriginTo centerP
sameBoundingRect
  :: forall n b. (Renderable (Path V2 n) b, TypeableFloat n)
  => [QDiagram b V2 n Any]
  -> [QDiagram b V2 n Any]
sameBoundingRect diagrams = map frameOne diagrams
  where
    widest = maximumBy (comparing width) diagrams
    tallest = maximumBy (comparing height) diagrams
    (xCenter :& _) = coords (centerPoint widest)
    (_ :& yCenter) = coords (centerPoint tallest)
    padRect = (rect (width widest) (height tallest) :: D V2 n) # phantom
    frameOne = atop padRect . moveOriginTo (xCenter ^& yCenter)
intSqrt :: Int -> Int
intSqrt = round . sqrt . (fromIntegral :: Int -> Float)
everyOther :: (a -> a) -> [a] -> [a]
everyOther f = zipWith ($) (cycle [id, f])
padList :: Int -> a -> [a] -> [a]
padList m padding xs = xs ++ replicate (mod ( length xs) m) padding