{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
-- | Sizes grid cells & positions elements to them.
module Graphics.Layout.Grid(Grid(..), Track(..), GridItem(..), GridItem'(..), Alignment(..),
        buildTrack, buildGrid, setCellBox, enumerate, gridItemBox, cellSize,
        trackMin, trackNat, gridEstWidth, sizeTrackMins, sizeTrackNats, sizeTrackMaxs,
        trackPosition, gridPosition, trackLayout, gridLayout) where

import Data.Either (fromRight)
import Data.Text (Text)
import Data.List (intersperse)
import Graphics.Layout.Box as B

import Debug.Trace (trace)

-- | An element which positions it's children within a grid.
type Grid m n = Size (Track m) (Track n)
-- | The sizes to which children are alonged on a single axis.
data Track x = Track {
    -- | The desired size of each cell.
    -- If Left specifies ratio of excess space to use.
    Track x -> [Either x Double]
cells :: [Either x Double],
    -- | The minimum amount of space each cell should take.
    Track x -> [Double]
trackMins :: [Double],
    -- | The ideal amount of space each cell should take.
    Track x -> [Double]
trackNats :: [Double],
    -- | How much space to add between cells.
    Track x -> x
gap :: x
}
-- | Which cells a child should be aligned to.
type GridItem = Size GridItem' GridItem'
-- | How a grid child should be aligned per-axis.
data GridItem' = GridItem {
    -- | On which cell should this child start.
    GridItem' -> Int
cellStart :: Int,
    -- | Before which cell should this child end.
    GridItem' -> Int
cellEnd :: Int,
    -- | How to redistribute excess space.
    GridItem' -> Alignment
alignment :: Alignment,
    -- | The minimum amount of space to allocate to this child.
    GridItem' -> Double
minSize :: Double,
    -- | The maximum aount of space to allocate to this child.
    GridItem' -> Double
natSize :: Double
}
-- | How to redistribute excess space.
data Alignment = Start | Mid | End

-- | Constructs a track with default (to-be-computed) values & given cell sizes.
buildTrack :: CastDouble x => [Either x Double] -> Track x
buildTrack :: [Either x Double] -> Track x
buildTrack cells :: [Either x Double]
cells = [Either x Double] -> [Double] -> [Double] -> x -> Track x
forall x. [Either x Double] -> [Double] -> [Double] -> x -> Track x
Track [Either x Double]
cells [] [] (x -> Track x) -> x -> Track x
forall a b. (a -> b) -> a -> b
$ Double -> x
forall a. CastDouble a => Double -> a
fromDouble 0
-- | Constructs a grid with default (to-be-computed) values & given cell sizes.
buildGrid :: (CastDouble m, CastDouble n) =>
        [Either m Double] -> [Either n Double] -> Grid m n
buildGrid :: [Either m Double] -> [Either n Double] -> Grid m n
buildGrid rows :: [Either m Double]
rows cols :: [Either n Double]
cols = Track n -> Track m -> Grid m n
forall m n. n -> m -> Size m n
Size ([Either n Double] -> Track n
forall x. CastDouble x => [Either x Double] -> Track x
buildTrack [Either n Double]
cols) ([Either m Double] -> Track m
forall x. CastDouble x => [Either x Double] -> Track x
buildTrack [Either m Double]
rows)

-- | Verify that the track is properly formed & can be validly processed.
verifyTrack :: Track x -> [GridItem'] -> Bool
verifyTrack :: Track x -> [GridItem'] -> Bool
verifyTrack track :: Track x
track cells' :: [GridItem']
cells' = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [
    GridItem' -> Int
cellStart GridItem'
cell Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< [Either x Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Track x -> [Either x Double]
forall x. Track x -> [Either x Double]
cells Track x
track) Bool -> Bool -> Bool
&& GridItem' -> Int
cellStart GridItem'
cell Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0 Bool -> Bool -> Bool
&&
    GridItem' -> Int
cellEnd GridItem'
cell Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< [Either x Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Track x -> [Either x Double]
forall x. Track x -> [Either x Double]
cells Track x
track) Bool -> Bool -> Bool
&& GridItem' -> Int
cellEnd GridItem'
cell Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> GridItem' -> Int
cellStart GridItem'
cell
  | GridItem'
cell <- [GridItem']
cells']
-- | Verify that the grid is properly formed & can be validly processed.
verifyGrid :: Grid m n -> [GridItem] -> Bool
verifyGrid :: Grid m n -> [GridItem] -> Bool
verifyGrid grid :: Grid m n
grid cells :: [GridItem]
cells =
    Track n -> [GridItem'] -> Bool
forall x. Track x -> [GridItem'] -> Bool
verifyTrack (Grid m n -> Track n
forall m n. Size m n -> n
inline Grid m n
grid) ((GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> n
inline [GridItem]
cells) Bool -> Bool -> Bool
&& Track m -> [GridItem'] -> Bool
forall x. Track x -> [GridItem'] -> Bool
verifyTrack (Grid m n -> Track m
forall m n. Size m n -> m
block Grid m n
grid) ((GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> m
block [GridItem]
cells)

-- | Compute the minimum size for the track given cell sizes.
-- Refers to computed min sizes if cached.
trackMin :: (n -> Double) -> Track n -> Double
trackMin :: (n -> Double) -> Track n -> Double
trackMin cb :: n -> Double
cb self :: Track n
self@Track { trackMins :: forall x. Track x -> [Double]
trackMins = [] } =
    [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
intersperse (n -> Double
cb (n -> Double) -> n -> Double
forall a b. (a -> b) -> a -> b
$ Track n -> n
forall x. Track x -> x
gap Track n
self) [n -> Double
cb n
x | Left x :: n
x <- Track n -> [Either n Double]
forall x. Track x -> [Either x Double]
cells Track n
self]
trackMin cb :: n -> Double
cb self :: Track n
self = [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
intersperse (n -> Double
cb (n -> Double) -> n -> Double
forall a b. (a -> b) -> a -> b
$ Track n -> n
forall x. Track x -> x
gap Track n
self) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ Track n -> [Double]
forall x. Track x -> [Double]
trackMins Track n
self
-- | Compute the natural size for the track given cell sizes.
-- Refers to compute natural sizes if cached.
trackNat :: (n -> Double) -> Track n -> Double
trackNat :: (n -> Double) -> Track n -> Double
trackNat cb :: n -> Double
cb self :: Track n
self@Track { trackNats :: forall x. Track x -> [Double]
trackNats = [] } =
    [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
intersperse (n -> Double
cb (n -> Double) -> n -> Double
forall a b. (a -> b) -> a -> b
$ Track n -> n
forall x. Track x -> x
gap Track n
self) [n -> Double
cb n
x | Left x :: n
x <- Track n -> [Either n Double]
forall x. Track x -> [Either x Double]
cells Track n
self]
trackNat cb :: n -> Double
cb self :: Track n
self = [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
intersperse (n -> Double
cb (n -> Double) -> n -> Double
forall a b. (a -> b) -> a -> b
$ Track n -> n
forall x. Track x -> x
gap Track n
self) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ Track n -> [Double]
forall x. Track x -> [Double]
trackNats Track n
self

-- | Selects all children entirely on the specified cell.
cellsForIndex :: [GridItem'] -> Int -> [GridItem']
cellsForIndex :: [GridItem'] -> Int -> [GridItem']
cellsForIndex cells :: [GridItem']
cells ix :: Int
ix =
    [GridItem'
cell | GridItem'
cell <- [GridItem']
cells, GridItem' -> Int
cellStart GridItem'
cell Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
ix, GridItem' -> Int
cellStart GridItem'
cell Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Int
forall a. Enum a => a -> a
pred (GridItem' -> Int
cellEnd GridItem'
cell)]
-- | Sets minimum & natural sizes from the given padded box.
setCellBox :: (CastDouble m, CastDouble n) => GridItem -> PaddedBox m n -> GridItem
setCellBox :: GridItem -> PaddedBox m n -> GridItem
setCellBox (Size x :: GridItem'
x y :: GridItem'
y) box :: PaddedBox m n
box = GridItem' -> GridItem' -> GridItem
forall m n. n -> m -> Size m n
Size GridItem'
x {
    minSize :: Double
minSize = PaddedBox m Double -> Double
forall n m. Num n => PaddedBox m n -> n
B.minWidth (PaddedBox m Double -> Double) -> PaddedBox m Double -> Double
forall a b. (a -> b) -> a -> b
$ (n -> Double) -> PaddedBox m n -> PaddedBox m Double
forall n nn m. (n -> nn) -> PaddedBox m n -> PaddedBox m nn
mapX' n -> Double
forall a. CastDouble a => a -> Double
toDouble PaddedBox m n
box,
    natSize :: Double
natSize = PaddedBox m Double -> Double
forall n m. Num n => PaddedBox m n -> n
B.width (PaddedBox m Double -> Double) -> PaddedBox m Double -> Double
forall a b. (a -> b) -> a -> b
$ (n -> Double) -> PaddedBox m n -> PaddedBox m Double
forall n nn m. (n -> nn) -> PaddedBox m n -> PaddedBox m nn
mapX' n -> Double
forall a. CastDouble a => a -> Double
toDouble PaddedBox m n
box
  } GridItem'
y {
    minSize :: Double
minSize = PaddedBox Double n -> Double
forall m n. Num m => PaddedBox m n -> m
B.minHeight (PaddedBox Double n -> Double) -> PaddedBox Double n -> Double
forall a b. (a -> b) -> a -> b
$ (m -> Double) -> PaddedBox m n -> PaddedBox Double n
forall m mm n. (m -> mm) -> PaddedBox m n -> PaddedBox mm n
mapY' m -> Double
forall a. CastDouble a => a -> Double
toDouble PaddedBox m n
box,
    natSize :: Double
natSize = PaddedBox Double n -> Double
forall m n. Num m => PaddedBox m n -> m
B.height (PaddedBox Double n -> Double) -> PaddedBox Double n -> Double
forall a b. (a -> b) -> a -> b
$ (m -> Double) -> PaddedBox m n -> PaddedBox Double n
forall m mm n. (m -> mm) -> PaddedBox m n -> PaddedBox mm n
mapY' m -> Double
forall a. CastDouble a => a -> Double
toDouble PaddedBox m n
box
  }

-- | Estimate grid width to inform proper width calculation.
gridEstWidth :: Grid y Length -> [GridItem] -> Double
gridEstWidth :: Grid y Length -> [GridItem] -> Double
gridEstWidth (Size cols :: Track Length
cols _) childs :: [GridItem]
childs = (Length -> Double) -> Track Length -> Double
forall n. (n -> Double) -> Track n -> Double
trackNat Length -> Double
forall a. CastDouble a => a -> Double
toDouble Track Length
cols {
    trackMins :: [Double]
trackMins = Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackMins 0 Track Length
cols ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> n
inline [GridItem]
childs,
    trackNats :: [Double]
trackNats = Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackNats 0 Track Length
cols ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> n
inline [GridItem]
childs
  }
-- | Calculate minimum sizes for all cells in the track.
-- Sized to fit given children.
sizeTrackMins :: Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackMins :: Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackMins parent :: Double
parent track :: Track Length
track childs :: [GridItem']
childs = ((Int, Either Length Double) -> Double)
-> [(Int, Either Length Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Either Length Double) -> Double
forall b. (Int, Either Length b) -> Double
inner ([(Int, Either Length Double)] -> [Double])
-> [(Int, Either Length Double)] -> [Double]
forall a b. (a -> b) -> a -> b
$ [Either Length Double] -> [(Int, Either Length Double)]
forall b. [b] -> [(Int, b)]
enumerate ([Either Length Double] -> [(Int, Either Length Double)])
-> [Either Length Double] -> [(Int, Either Length Double)]
forall a b. (a -> b) -> a -> b
$ Track Length -> [Either Length Double]
forall x. Track x -> [Either x Double]
cells Track Length
track
  where
    inner :: (Int, Either Length b) -> Double
inner (_, Left (Pixels x :: Double
x)) = Double
x
    inner (_, Left (Percent x :: Double
x)) = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
parent
    inner arg :: (Int, Either Length b)
arg@(ix :: Int
ix, Left Preferred) =
        [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ (0Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
:) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem' -> Double) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map GridItem' -> Double
natSize ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ [GridItem'] -> Int -> [GridItem']
cellsForIndex [GridItem']
childs Int
ix
    inner (ix :: Int
ix, _) =
        [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ (0Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
:) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem' -> Double) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map GridItem' -> Double
minSize ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ [GridItem'] -> Int -> [GridItem']
cellsForIndex [GridItem']
childs Int
ix
-- | Compute natural sizes for all cells in the track.
-- Sized to fit given children.
sizeTrackNats :: Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackNats :: Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackNats parent :: Double
parent track :: Track Length
track childs :: [GridItem']
childs = ((Int, Either Length Double) -> Double)
-> [(Int, Either Length Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Either Length Double) -> Double
forall b. (Int, Either Length b) -> Double
inner ([(Int, Either Length Double)] -> [Double])
-> [(Int, Either Length Double)] -> [Double]
forall a b. (a -> b) -> a -> b
$ [Either Length Double] -> [(Int, Either Length Double)]
forall b. [b] -> [(Int, b)]
enumerate ([Either Length Double] -> [(Int, Either Length Double)])
-> [Either Length Double] -> [(Int, Either Length Double)]
forall a b. (a -> b) -> a -> b
$ Track Length -> [Either Length Double]
forall x. Track x -> [Either x Double]
cells Track Length
track
  where
    inner :: (Int, Either Length b) -> Double
inner (_, Left (Pixels x :: Double
x)) = Double
x
    inner (_, Left (Percent x :: Double
x)) = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
parent
    inner arg :: (Int, Either Length b)
arg@(ix :: Int
ix, Left Min) =
        [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ (0Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
:) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem' -> Double) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map GridItem' -> Double
minSize ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ [GridItem'] -> Int -> [GridItem']
cellsForIndex [GridItem']
childs Int
ix
    inner (ix :: Int
ix, _) =
        [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ (0Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
:) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ (GridItem' -> Double) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map GridItem' -> Double
natSize ([GridItem'] -> [Double]) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> a -> b
$ [GridItem'] -> Int -> [GridItem']
cellsForIndex [GridItem']
childs Int
ix
-- | Compute maximum sizes for all cells in the track, sized to the parent element.
sizeTrackMaxs :: Double -> Track Length -> [Double]
sizeTrackMaxs :: Double -> Track Length -> [Double]
sizeTrackMaxs parent :: Double
parent track :: Track Length
track = (((Double, Double), Either Length Double) -> Double)
-> [((Double, Double), Either Length Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Double -> ((Double, Double), Either Length Double) -> Double
inner Double
fr) ([((Double, Double), Either Length Double)] -> [Double])
-> [((Double, Double), Either Length Double)] -> [Double]
forall a b. (a -> b) -> a -> b
$ [(Double, Double)]
-> [Either Length Double]
-> [((Double, Double), Either Length Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip [(Double, Double)]
subsizes ([Either Length Double]
 -> [((Double, Double), Either Length Double)])
-> [Either Length Double]
-> [((Double, Double), Either Length Double)]
forall a b. (a -> b) -> a -> b
$ Track Length -> [Either Length Double]
forall x. Track x -> [Either x Double]
cells Track Length
track
  where
    subsizes :: [(Double, Double)]
subsizes = [Double] -> [Double] -> [(Double, Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Track Length -> [Double]
forall x. Track x -> [Double]
trackMins Track Length
track) (Track Length -> [Double]
forall x. Track x -> [Double]
trackNats Track Length
track)
    fr :: Double
fr = Double -> Double -> Double
forall a. Ord a => a -> a -> a
Prelude.max 0 Double
fr'
    fr' :: Double
fr' = (Double
parent Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
estimate)Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/([Either Length Double] -> Double
forall a. (Enum a, Num a) => [Either Length a] -> a
countFRs ([Either Length Double] -> Double)
-> [Either Length Double] -> Double
forall a b. (a -> b) -> a -> b
$ Track Length -> [Either Length Double]
forall x. Track x -> [Either x Double]
cells Track Length
track)
    estimate :: Double
estimate = [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ Double -> [Double] -> [Double]
forall a. a -> [a] -> [a]
intersperse (Double -> Length -> Double
lowerLength Double
parent (Length -> Double) -> Length -> Double
forall a b. (a -> b) -> a -> b
$ Track Length -> Length
forall x. Track x -> x
gap Track Length
track) ([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$
            (((Double, Double), Either Length Double) -> Double)
-> [((Double, Double), Either Length Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (Double -> ((Double, Double), Either Length Double) -> Double
inner 0) ([((Double, Double), Either Length Double)] -> [Double])
-> [((Double, Double), Either Length Double)] -> [Double]
forall a b. (a -> b) -> a -> b
$ [(Double, Double)]
-> [Either Length Double]
-> [((Double, Double), Either Length Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip [(Double, Double)]
subsizes ([Either Length Double]
 -> [((Double, Double), Either Length Double)])
-> [Either Length Double]
-> [((Double, Double), Either Length Double)]
forall a b. (a -> b) -> a -> b
$ Track Length -> [Either Length Double]
forall x. Track x -> [Either x Double]
cells Track Length
track
    inner :: Double -> ((Double, Double), Either Length Double) -> Double
inner _ (_, Left (Pixels x :: Double
x)) = Double
x
    inner _ (_, Left (Percent x :: Double
x)) = Double
xDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
parent
    inner _ ((_, nat :: Double
nat), Left Preferred) = Double
nat
    inner _ ((min :: Double
min, _), Left Min) = Double
min
    inner fr :: Double
fr ((_, nat :: Double
nat), Left Auto) = Double -> Double -> Double
forall a. Ord a => a -> a -> a
Prelude.min Double
nat Double
fr
    inner fr :: Double
fr (_, Right x :: Double
x) = Double
xDouble -> Double -> Double
forall a. Num a => a -> a -> a
*Double
fr

-- | Compute the position of all children within the grid.
trackPosition :: Track Double -> [GridItem'] -> [Double]
trackPosition :: Track Double -> [GridItem'] -> [Double]
trackPosition self :: Track Double
self childs :: [GridItem']
childs = (GridItem' -> Double) -> [GridItem'] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map GridItem' -> Double
gridCellPosition [GridItem']
childs
  where
    gridCellPosition :: GridItem' -> Double
gridCellPosition child :: GridItem'
child = Int -> Double
track (GridItem' -> Int
cellStart GridItem'
child) Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double -> Alignment -> Double
forall p. Fractional p => p -> Alignment -> p
align Double
whitespace (GridItem' -> Alignment
alignment GridItem'
child)
      where
        whitespace :: Double
whitespace = Int -> Double
track (GridItem' -> Int
cellEnd GridItem'
child) Double -> Double -> Double
forall a. Num a => a -> a -> a
- Int -> Double
track (GridItem' -> Int
cellStart GridItem'
child) Double -> Double -> Double
forall a. Num a => a -> a -> a
- GridItem' -> Double
natSize GridItem'
child
    track :: Int -> Double
track = (Int -> [Either Double Double] -> Double)
-> [Either Double Double] -> Int -> Double
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> [Either Double Double] -> Double
forall a p a.
(Enum a, Eq a, Num p, Num a) =>
a -> [Either a p] -> p
track' ([Either Double Double] -> Int -> Double)
-> [Either Double Double] -> Int -> Double
forall a b. (a -> b) -> a -> b
$ Track Double -> [Either Double Double]
forall x. Track x -> [Either x Double]
cells Track Double
self
    track' :: a -> [Either a p] -> p
track' ix :: a
ix (size :: Either a p
size:sizes :: [Either a p]
sizes) = p -> Either a p -> p
forall b a. b -> Either a b -> b
fromRight 0 Either a p
size p -> p -> p
forall a. Num a => a -> a -> a
+ a -> [Either a p] -> p
track' (a -> a
forall a. Enum a => a -> a
pred a
ix) [Either a p]
sizes
    track' 0 _ = 0
    track' ix :: a
ix [] = String -> p -> p
forall a. String -> a -> a
trace "WARNING! Malformed input table!" 0
    align :: p -> Alignment -> p
align _ Start = 0
    align excess :: p
excess Mid = p
excessp -> p -> p
forall a. Fractional a => a -> a -> a
/2
    align excess :: p
excess End = p
excess
-- Compute the maximum size along an axis of a child, for it to be sized to.
cellSize :: CastDouble x => Track x -> GridItem' -> Double
cellSize :: Track x -> GridItem' -> Double
cellSize self :: Track x
self child :: GridItem'
child = Int -> Double
track (GridItem' -> Int
cellEnd GridItem'
child) Double -> Double -> Double
forall a. Num a => a -> a -> a
- Int -> Double
track (GridItem' -> Int
cellStart GridItem'
child)
  where
    track :: Int -> Double
track = (Int -> [Either x Double] -> Double)
-> [Either x Double] -> Int -> Double
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> [Either x Double] -> Double
forall a a a.
(CastDouble a, Enum a, Eq a, Num a) =>
a -> [Either a a] -> Double
track' ([Either x Double] -> Int -> Double)
-> [Either x Double] -> Int -> Double
forall a b. (a -> b) -> a -> b
$ Track x -> [Either x Double]
forall x. Track x -> [Either x Double]
cells Track x
self
    track' :: a -> [Either a a] -> Double
track' ix :: a
ix (size :: Either a a
size:sizes :: [Either a a]
sizes) =
        (a -> Double
forall a. CastDouble a => a -> Double
toDouble (a -> Double) -> a -> Double
forall a b. (a -> b) -> a -> b
$ a -> Either a a -> a
forall b a. b -> Either a b -> b
fromRight (Double -> a
forall a. CastDouble a => Double -> a
fromDouble 0) Either a a
size) Double -> Double -> Double
forall a. Num a => a -> a -> a
+ a -> [Either a a] -> Double
track' (a -> a
forall a. Enum a => a -> a
pred a
ix) [Either a a]
sizes
    track' 0 _ = 0
    track' ix :: a
ix [] = String -> Double -> Double
forall a. String -> a -> a
trace "WARNING! Malformed input table!" 0
-- | Compute the maximum size as a PaddedBox of a child, for it to be sized to.
gridItemBox :: (CastDouble x, CastDouble y) => Grid y x -> GridItem -> PaddedBox Double Double
gridItemBox :: Grid y x -> GridItem -> PaddedBox Double Double
gridItemBox (Size cols :: Track x
cols rows :: Track y
rows) cell :: GridItem
cell =
    Size Double Double -> PaddedBox Double Double
forall m n. (Zero m, Zero n) => Size m n -> PaddedBox m n
size2box (Track x -> GridItem' -> Double
forall x. CastDouble x => Track x -> GridItem' -> Double
cellSize Track x
cols (GridItem -> GridItem'
forall m n. Size m n -> n
inline GridItem
cell) Double -> Double -> Size Double Double
forall m n. n -> m -> Size m n
`Size` Track y -> GridItem' -> Double
forall x. CastDouble x => Track x -> GridItem' -> Double
cellSize Track y
rows (GridItem -> GridItem'
forall m n. Size m n -> m
block GridItem
cell))
  where
    size2box :: Size m n -> PaddedBox m n
size2box size :: Size m n
size = PaddedBox m n
forall a. Zero a => a
zero { min :: Size m n
B.min = Size m n
size, max :: Size m n
B.max = Size m n
size, size :: Size m n
B.size = Size m n
size }
-- | Compute the position of all children in a grid.
gridPosition :: Grid Double Double -> [GridItem] -> [(Double, Double)]
gridPosition :: Grid Double Double -> [GridItem] -> [(Double, Double)]
gridPosition (Size cols :: Track Double
cols rows :: Track Double
rows) childs :: [GridItem]
childs =
    Track Double -> [GridItem'] -> [Double]
trackPosition Track Double
rows ((GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> n
inline [GridItem]
childs) [Double] -> [Double] -> [(Double, Double)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` Track Double -> [GridItem'] -> [Double]
trackPosition Track Double
cols ((GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> m
block [GridItem]
childs)
-- | Compute the track sizes & child positions along a single axis.
trackLayout :: Double -> Double -> Track Length -> [GridItem'] ->
        (Track Double, [(Double, GridItem')])
trackLayout :: Double
-> Double
-> Track Length
-> [GridItem']
-> (Track Double, [(Double, GridItem')])
trackLayout parent :: Double
parent width :: Double
width self :: Track Length
self childs :: [GridItem']
childs = (Track Double
self', [Double] -> [GridItem'] -> [(Double, GridItem')]
forall a b. [a] -> [b] -> [(a, b)]
zip [Double]
positions [GridItem']
childs)
  where
    positions :: [Double]
positions = Track Double -> [GridItem'] -> [Double]
trackPosition Track Double
self' [GridItem']
childs
    self' :: Track Double
self' = Track Length
self {
        cells :: [Either Double Double]
cells = (Double -> Either Double Double)
-> [Double] -> [Either Double Double]
forall a b. (a -> b) -> [a] -> [b]
map Double -> Either Double Double
forall a b. a -> Either a b
Left [Double]
sizes,
        trackMins :: [Double]
trackMins = [Double]
mins, trackNats :: [Double]
trackNats = [Double]
nats,
        gap :: Double
gap = Double -> Length -> Double
lowerLength Double
width (Length -> Double) -> Length -> Double
forall a b. (a -> b) -> a -> b
$ Track Length -> Length
forall x. Track x -> x
gap Track Length
self
      }
    sizes :: [Double]
sizes = Double -> Track Length -> [Double]
sizeTrackMaxs Double
parent Track Length
self { trackMins :: [Double]
trackMins = [Double]
mins, trackNats :: [Double]
trackNats = [Double]
nats }
    mins :: [Double]
mins = Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackMins Double
parent Track Length
self [GridItem']
childs
    nats :: [Double]
nats = Double -> Track Length -> [GridItem'] -> [Double]
sizeTrackNats Double
parent Track Length
self [GridItem']
childs
-- | Compute the track sizes & child positions along both axes.
gridLayout :: Size Double Double -> Grid Length Length -> [GridItem] ->
        (Grid Double Double, [((Double, Double), GridItem)])
gridLayout :: Size Double Double
-> Grid Length Length
-> [GridItem]
-> (Grid Double Double, [((Double, Double), GridItem)])
gridLayout parent :: Size Double Double
parent (Size cols :: Track Length
cols rows :: Track Length
rows) childs :: [GridItem]
childs = (Grid Double Double
self', [(Double, Double)] -> [GridItem] -> [((Double, Double), GridItem)]
forall a b. [a] -> [b] -> [(a, b)]
zip [(Double, Double)]
positions [GridItem]
childs)
  where
    positions :: [(Double, Double)]
positions = Grid Double Double -> [GridItem] -> [(Double, Double)]
gridPosition Grid Double Double
self' [GridItem]
childs
    self' :: Grid Double Double
self' = Track Double -> Track Double -> Grid Double Double
forall m n. n -> m -> Size m n
Size Track Double
cols' { gap :: Double
gap = Double -> Length -> Double
lowerLength Double
width (Length -> Double) -> Length -> Double
forall a b. (a -> b) -> a -> b
$ Track Length -> Length
forall x. Track x -> x
gap Track Length
cols } Track Double
rows'
    (rows' :: Track Double
rows', _) = Double
-> Double
-> Track Length
-> [GridItem']
-> (Track Double, [(Double, GridItem')])
trackLayout (Size Double Double -> Double
forall m n. Size m n -> m
block Size Double Double
parent) Double
width Track Length
rows ([GridItem'] -> (Track Double, [(Double, GridItem')]))
-> [GridItem'] -> (Track Double, [(Double, GridItem')])
forall a b. (a -> b) -> a -> b
$ (GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> m
block [GridItem]
childs
    width :: Double
width = (Double -> Double) -> Track Double -> Double
forall n. (n -> Double) -> Track n -> Double
trackNat Double -> Double
forall a. a -> a
id Track Double
cols'
    (cols' :: Track Double
cols', _) = Double
-> Double
-> Track Length
-> [GridItem']
-> (Track Double, [(Double, GridItem')])
trackLayout (Size Double Double -> Double
forall m n. Size m n -> n
inline Size Double Double
parent) 0 Track Length
cols ([GridItem'] -> (Track Double, [(Double, GridItem')]))
-> [GridItem'] -> (Track Double, [(Double, GridItem')])
forall a b. (a -> b) -> a -> b
$ (GridItem -> GridItem') -> [GridItem] -> [GridItem']
forall a b. (a -> b) -> [a] -> [b]
map GridItem -> GridItem'
forall m n. Size m n -> n
inline [GridItem]
childs

-- | Utility for associate an index with each item in a list.
enumerate :: [b] -> [(Int, b)]
enumerate = [Int] -> [b] -> [(Int, b)]
forall a b. [a] -> [b] -> [(a, b)]
zip [0..]

-- | Utility for summing the divisor used to compute the fr unit.
countFRs :: [Either Length a] -> a
countFRs (Left Auto:rest :: [Either Length a]
rest) = a -> a
forall a. Enum a => a -> a
succ (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ [Either Length a] -> a
countFRs [Either Length a]
rest
countFRs (Right x :: a
x:rest :: [Either Length a]
rest) = a
x a -> a -> a
forall a. Num a => a -> a -> a
+ [Either Length a] -> a
countFRs [Either Length a]
rest
countFRs (_:rest :: [Either Length a]
rest) = [Either Length a] -> a
countFRs [Either Length a]
rest
countFRs [] = 0