~alcinnz/CatTrap

0759cd2eef8ded9713f67084152d393d58e3e55b — Adrian Cochrane 1 year, 4 months ago 074d5d9
Build testable gridlayout function, fix syntax errors.
1 files changed, 52 insertions(+), 10 deletions(-)

M Graphics/Layout/Grid.hs
M Graphics/Layout/Grid.hs => Graphics/Layout/Grid.hs +52 -10
@@ 7,9 7,11 @@ import Graphics.Layout.Box as B

data Grid m n = Grid {
    rows :: [(Name, Either m Double)],
    rowBounds :: [(Double, Double)],
    columns :: [(Name, Either n Double)],
    colBounds :: [(Double, Double)],
    gap :: Size m n,
    gridBox :: PaddedBox m n
    containerSize :: Size m n -- wrap in a Flow box to get padding, etc.
}
data GridItem m n = GridItem {
    startRow :: Int, endRow :: Int, startCol :: Int, endCol :: Int,


@@ 35,8 37,12 @@ verifyGrid self childs = and [
    width = length $ columns self
    height = length $ rows self

{-gridEstWidth :: Grid y Length -> [GridItem y Double] -> Double-}
gridMinWidths :: Double -> Grid y Length -> [GridItem y Double] -> (Double, [Double])
gridEstWidth :: Grid b Length -> [GridItem y Double] -> Double
gridEstWidth self childs = fst $ gridMaxWidths zeroBox self $ zip mins nats
  where
    mins = snd $ gridMinWidths 0 self childs
    nats = snd $ gridNatWidths 0 self childs
gridMinWidths :: Double -> Grid b Length -> [GridItem y Double] -> (Double, [Double])
gridMinWidths parent self childs =
    (sum $ intersperse (lowerLength parent $ inline $ gap self) ret, ret)
  where


@@ 47,7 53,7 @@ gridMinWidths parent self childs =
        maximum $ (0:) $ map (inline . size . gridItemBox) $ cellsForCol childs ix
    colMinWidth (ix, _) =
        maximum $ (0:) $ map (inline . B.min . gridItemBox) $ cellsForCol childs ix
gridNatWidths :: Double -> Grid y Length -> [GridItem y Double] -> (Double, [Double])
gridNatWidths :: Double -> Grid b Length -> [GridItem y Double] -> (Double, [Double])
gridNatWidths parent self childs =
    (sum $ intersperse (lowerLength parent $ inline $ gap self) ret, ret)
  where


@@ 58,12 64,13 @@ gridNatWidths parent self childs =
        maximum $ (0:) $ map (inline . B.min . gridItemBox) $ cellsForCol childs ix
    colNatWidth (ix, _) =
        maximum $ (0:) $ map (inline . size . gridItemBox) $ cellsForCol childs ix
gridMaxWidths :: PaddedBox y Double -> Grid y Length -> [(Double, Double)] -> (Double, [Double])
gridMaxWidths :: PaddedBox b Double -> Grid y Length -> [(Double, Double)] -> (Double, [Double])
gridMaxWidths parent self subwidths =
    (sum $ intersperse (lowerLength outerwidth $ inline $ gap self) ret, ret)
  where
    ret = map (colMaxWidth fr) $ zip subwidths $ map snd $ columns self
    fr = (outerwidth - estimate)/(countFRs $ map snd $ columns self)
    fr = Prelude.max 0 fr'
    fr' = (outerwidth - estimate)/(countFRs $ map snd $ columns self)
    outerwidth = inline $ size parent
    estimate = sum $ intersperse (lowerLength outerwidth $ inline $ gap self) $
        map (colMaxWidth 0) $ zip subwidths $ map snd $ columns self


@@ 73,7 80,7 @@ gridMaxWidths parent self subwidths =
    colMaxWidth _ ((min, _), Left Min) = min
    colMaxWidth fr (_, Left Auto) = fr
    colMaxWidth fr (_, Right x) = x*fr
gridWidths :: PaddedBox y Double -> Grid y Length -> [(Double, Double)] -> (Double, [Double])
gridWidths :: PaddedBox b Double -> Grid y Length -> [(Double, Double)] -> (Double, [Double])
gridWidths parent self subwidths =
    (sum $ intersperse (lowerLength outerwidth $ inline $ gap self) ret, ret)
  where


@@ 90,6 97,11 @@ gridWidths parent self subwidths =
    colWidth' fr (_, Left Auto) = fr
    colWidth' fr (_, Right x) = x*fr

gridEstHeight :: Grid Length Double -> [GridItem Double Double] -> Double
gridEstHeight self childs = fst $ gridMaxHeights zeroBox self $ zip mins nats
  where
    mins = snd $ gridMinHeights 0 self childs
    nats = snd $ gridNatHeights 0 self childs
gridNatHeights :: Double -> Grid Length Double -> [GridItem Double Double] -> (Double, [Double])
gridNatHeights parent self childs =
    (sum $ intersperse (lowerLength parent $ block $ gap self) ret, ret)


@@ 165,9 177,39 @@ gridPosition self childs = map gridCellPosition childs
    align _ Start = 0
    align excess Mid = excess/2
    align excess End = excess
{-gridLayout :: PaddedBox Double Double -> Grid Length Length ->
        [GridItem Length Length] -> Bool ->
        (Grid Double Double, [(Size Double Double, GridItem Double Double)])-}
gridLayout :: PaddedBox Double Double -> Grid Length Length ->
        [GridItem Double Double] -> Bool ->
        (Grid Double Double, [(Size Double Double, GridItem Double Double)])
gridLayout parent self childs paginate = (self', zip positions childs)
  where
    positions = gridPosition self' childs
    self' = self {
        rows = zip (map fst $ rows self) $ map Left rows',
        rowBounds = rowBounds',
        columns = zip (map fst $ rows self) $ map Left cols',
        colBounds = colBounds',
        gap = Size (lowerLength width' gapX) (lowerLength width' gapY),
        containerSize = Size width' height'
      }
    Size gapX gapY = gap self

    (height', rows') = gridHeights parent self0 rowBounds'
    rowBounds' = zip rowMins rowNats
    (_, rowMins) = gridMinHeights estHeight self0 childs
    (_, rowNats) = gridNatHeights estHeight self0 childs
    estHeight = gridEstHeight self0 childs

    self0 = self {
        columns = zip (map fst $ columns self) $ map Left cols',
        rowBounds = rowBounds',
        gap = Size (lowerLength width' gapX) gapY,
        containerSize = let Size _ y = containerSize self in Size width' y
      }
    (width', cols') = gridWidths parent self colBounds'
    colBounds' = zip colMins colNats
    (_, colMins) = gridMinWidths estWidth self childs
    (_, colNats) = gridNatWidths estWidth self childs
    estWidth = gridEstWidth self childs

enumerate = zip [0..]