~alcinnz/CatTrap

4a889fbb97d8e3d9cc396daf37199d2fe990a62b — Adrian Cochrane 5 months ago cdc3503
Improve documentation & naming for flexbox.
4 files changed, 91 insertions(+), 34 deletions(-)

M Graphics/Layout.hs
M Graphics/Layout/Flex.hs
M Graphics/Layout/Flex/CSS.hs
M test/Test.hs
M Graphics/Layout.hs => Graphics/Layout.hs +1 -1
@@ 58,7 58,7 @@ data LayoutItem m n x =
    | LayoutConst x (PaddedBox m n) [LayoutItem m n x]
    -- | Children of a `LayoutInline` or `LayoutInline'`.
    | LayoutSpan (FragmentTree (UserData m n x))
    | LayoutFlex x (FlexParent (LayoutItem m n x) m)
    | LayoutFlex x (Flex (LayoutItem m n x) m)
    deriving (Show, Eq)
-- | An empty box.
nullLayout :: (PropertyParser x, Zero m, Zero n) => LayoutItem m n x

M Graphics/Layout/Flex.hs => Graphics/Layout/Flex.hs +63 -24
@@ 1,4 1,11 @@
module Graphics.Layout.Flex where
-- | Layout formula positioning children horizontally or vertically, with or without wrapping.
module Graphics.Layout.Flex(
        Flex(..), FlexChild(..), Direction(..), FlexWrapping(..), Justification(..), Alignment(..),
        flexMap, flexResolve, flexMaxBasis, flexSumBasis, flexWrap, flexRowSize, flexRowsSize,
        justifyOffset, justifySpacing, flexJustify, alignOffset,
        outerMinMain, outerMain, outerMaxMain, outerMinCross, outerCross, outerMaxCross,
        innerMinMain, innerMain, innerMaxMain, innerMinCross, innerCross, innerMaxCross,
        flexGetBox, flexSplit, flexPosition) where

import Graphics.Layout.Box as B (Length(..), lowerLength, Size(..), PaddedBox(..),
        maxWidth, width, minWidth, maxHeight, height, minHeight, CastDouble(..), Zero(..))


@@ 6,17 13,28 @@ import Data.List (intersperse)
import GHC.Real (infinity)
import Data.Maybe (fromMaybe)

data FlexParent a b = FlexParent {
-- | Parameters to flexbox layout
data Flex a b = Flex {
    -- | On which axis to position children
    direction :: Direction,
    -- | Whether to reverse each row
    reverseRows :: Bool,
    -- | Whether to wrap children to multiple lines
    wrap :: FlexWrapping,
    -- | How to justify children within lines
    justify :: Justification,
    alignLines :: Maybe Justification, -- `Nothing` is "stretch"
    -- | How to justify lines within the flexbox. Nothing is CSS "stretch".
    alignLines :: Maybe Justification,
    -- | Gap between children
    baseGap :: b,
    -- | Gap between lines
    crossGap :: b,
    children :: [[FlexChild a b]], -- 2D list to store lines once split.
    pageWidth :: Double -- Pagination argument
    -- | The children to layout, 2D list so as to store lines once split.
    children :: [[FlexChild a b]],
    -- | How wide to consider the page when paginating.
    pageWidth :: Double
} deriving (Eq, Show, Read)
-- | Properties for positioning a child of a flexbox
data FlexChild a b = FlexChild {
    grow :: Double,
    shrink :: Double,


@@ 25,15 43,20 @@ data FlexChild a b = FlexChild {
    flexInner :: a
} deriving (Eq, Show, Read)

-- | Which axis to position children along
data Direction = Row | Column deriving (Eq, Show, Read)
-- | Whether to wrap or reverse the wrapped lines
data FlexWrapping = NoWrap | Wrap | WrapReverse deriving (Eq, Show, Read)
-- | How to position lines within a flexbox, or children within a line
data Justification = JStart | JEnd | JCenter | JSpaceBetween | JSpaceAround | JSpaceEvenly
    deriving (Eq, Show, Read)
-- | How to align children along the cross-axis (opposite axis from which they're laid out)
data Alignment = AlStretch | AlStart | AlEnd | AlCenter | AlBaseline
    deriving (Eq, Show, Read)

flexMap :: (a -> b) -> FlexParent a c -> FlexParent b c
flexMap cb self = FlexParent {
-- | Apply an operation to every child
flexMap :: (a -> b) -> Flex a c -> Flex b c
flexMap cb self = Flex {
    direction = direction self, reverseRows = reverseRows self, wrap = wrap self,
    justify = justify self, alignLines = alignLines self,
    baseGap = baseGap self, crossGap = crossGap self, pageWidth = pageWidth self,


@@ 43,9 66,10 @@ flexMap cb self = FlexParent {
        flexInner = cb $ flexInner kid -- The important line!
    } | kid <- row] | row <- children self]
  }
-- | Resolve lengths in the flexbox to doubles.
flexResolve :: CastDouble b => (a -> Direction -> Double) -> Double ->
        FlexParent a b -> FlexParent a Double
flexResolve cb size self = FlexParent {
        Flex a b -> Flex a Double
flexResolve cb size self = Flex {
    direction = direction self, reverseRows = reverseRows self, wrap = wrap self,
    justify = justify self, alignLines = alignLines self,
    baseGap = toDoubleWithin size $ baseGap self,


@@ 58,14 82,17 @@ flexResolve cb size self = FlexParent {
    } | kid <- row] | row <- children self]
  }

flexMaxBasis :: FlexParent a Double -> Double
-- | The minimum size of the flexbox along `direction`, i.e. maximum size of a child.
flexMaxBasis :: Flex a Double -> Double
flexMaxBasis self = maximum [basis child | row <- children self, child <- row]
flexSumBasis :: FlexParent a Double -> Double
-- | The maximum width of each row of the flexbox.
flexSumBasis :: Flex a Double -> Double
flexSumBasis self = maximum [Prelude.sum $
        intersperse (baseGap self) $ map basis row | row <- children self]

-- | Wrap all lines to a given size reassigning overflow or underflow space.
-- NOTE: shrink propery may yield negative sizes. Caller will want to enforce min-sizes.
flexWrap :: CastDouble b => FlexParent a b -> Double -> FlexParent a b
flexWrap :: CastDouble b => Flex a b -> Double -> Flex a b
flexWrap self size
    | NoWrap <- wrap self = post self
    | Wrap <- wrap self = post self'


@@ 91,11 118,11 @@ flexWrap self size
            in (kid:kids', rest)
    splitRow [] _ = ([], [])

    post :: CastDouble b => FlexParent a b -> FlexParent a b
    post :: CastDouble b => Flex a b -> Flex a b
    post flex
        | reverseRows self = post' flex { children = map reverse $ children flex }
        | otherwise = post' flex
    post' :: CastDouble b => FlexParent a b -> FlexParent a b
    post' :: CastDouble b => Flex a b -> Flex a b
    post' flex = flex { children = map resizeRow $ children flex }
    resizeRow :: CastDouble b => [FlexChild a b] -> [FlexChild a b]
    resizeRow row


@@ 113,18 140,21 @@ flexWrap self size
        nanguard x | isNaN x = 0
            | isInfinite x = 0
            | otherwise = x
    baseGap' :: CastDouble b => FlexParent a b -> Double
    baseGap' :: CastDouble b => Flex a b -> Double
    baseGap' = toDouble . baseGap
    basis' :: CastDouble b => FlexChild a b -> Double
    basis' = toDouble . basis

-- | The cross (opposite from `direction` axis) size of a row.
flexRowSize :: (a -> Double) -> [FlexChild a b] -> Double
flexRowSize cb row = maximum $ map (cb . flexInner) row
flexRowsSize :: (a -> Double) -> FlexParent a Double -> Double
flexRowsSize cb FlexParent { crossGap = gap, children = kids } =
-- | The cross (opposite from `direction` axis) size of all rows.
flexRowsSize :: (a -> Double) -> Flex a Double -> Double
flexRowsSize cb Flex { crossGap = gap, children = kids } =
    sum $ intersperse gap $ flexRowSize cb `map` kids

justifyOffset, justifySpacing :: Double -> [Double] -> Double -> Justification -> Double
-- | How far right to shift some elements to achieve desired justification.
justifyOffset _ _ _ JStart = 0
justifyOffset outersize ks g JEnd = outersize - innersize g ks
justifyOffset outersize ks g JCenter = half $ outersize - innersize g ks


@@ 133,11 163,13 @@ justifyOffset outersize ks g JSpaceAround =
    half $ (outersize - innersize g ks)/length' ks
justifyOffset _ ks _ _ | length ks <= 1 = 0 -- No gaps to space, avoid numeric errors.
justifyOffset size ks g JSpaceEvenly = (size - innersize g ks)/(length' ks + 1)
-- | How much space to add between elements.
justifySpacing size ks g JSpaceBetween = (size - innersize g ks)/(length' ks - 1)
justifySpacing size ks g JSpaceAround = (size - innersize g ks)/length' ks
justifySpacing size ks g JSpaceEvenly = (size - innersize g ks)/(length' ks + 1)
justifySpacing _ _ _ _ = 0

-- | Position new positions for the given items according to the given justification.
flexJustify :: (a -> Double) -> Double -> [a] -> Double -> Justification -> [(Double, a)]
flexJustify cb size kids gap just = inner kids offs
  where


@@ 147,6 179,7 @@ flexJustify cb size kids gap just = inner kids offs
    inner (k:ks) start = (start, k):inner ks (start + cb k + gap)
    inner [] _ = []

-- | How far right to shift some elements to achieve desired alignment.
alignOffset :: Double -> Double -> Alignment -> Double
alignOffset _ _ AlStretch = 0 -- Needs special handling elsewhere
alignOffset _ _ AlStart = 0


@@ 154,8 187,11 @@ alignOffset outer inner AlEnd = outer - inner
alignOffset outer inner AlCenter = half $ outer - inner
alignOffset outer inner AlBaseline = half $ outer - inner -- FIXME: Implement properly!

-- | Sum given sizes with a specified gap between them.
innersize gap = sum . intersperse gap
-- | divide by 2, can be syntactically in certain circumstances.
half = (/2)
-- | length of an list, as a double.
length' :: [a] -> Double
length' = toEnum . length



@@ 195,8 231,9 @@ sizeMain self Column = block self
sizeCross self Row = block self
sizeCross self Column = inline self

-- | Compute the size bounds of a flexbox.
flexGetBox :: (Zero m, CastDouble m, Zero n, CastDouble n) =>
    (a -> PaddedBox Double Double) -> FlexParent a m -> PaddedBox m n
    (a -> PaddedBox Double Double) -> Flex a m -> PaddedBox m n
flexGetBox cb self = zero {
    B.min = flexMaxBasis self' `size` flexRowsSize (cb' innerMinCross) self',
    B.max = fromRational infinity `size` fromRational infinity,


@@ 209,9 246,10 @@ flexGetBox cb self = zero {
    cb' cb_ = flip cb_ (direction self) . cb
    self' = flexResolve (innerMain . cb) 0 self

flexSplit :: (a -> Size Double Double) -> Double -> Double -> FlexParent a Double ->
    (FlexParent a Double, FlexParent a Double)
flexSplit cb h _ self@FlexParent { direction = Row, pageWidth = w } =
-- | Split a flexbox over multiple pages.
flexSplit :: (a -> Size Double Double) -> Double -> Double -> Flex a Double ->
    (Flex a Double, Flex a Double)
flexSplit cb h _ self@Flex { direction = Row, pageWidth = w } =
    (self' { children = page0 }, self' { children = page1 })
  where
    self' = flexWrap self w


@@ 223,7 261,7 @@ flexSplit cb h _ self@FlexParent { direction = Row, pageWidth = w } =
                    start + crossGap self + flexRowSize (inline . cb) row
            in (row:rows', rest)
    splitRows _ [] = ([], [])
flexSplit cb h h' self@FlexParent { direction = Column, pageWidth = w }
flexSplit cb h h' self@Flex { direction = Column, pageWidth = w }
    | measure h = (flexWrap self h, self { children = [] })
    -- If it fits on neither page... Row-direction is more versatile!
    | not $ measure h' = flexSplit cb h h' self { direction = Row }


@@ 231,10 269,11 @@ flexSplit cb h h' self@FlexParent { direction = Column, pageWidth = w }
  where
    measure space = (block . cb) `flexRowsSize` flexWrap self space <= w

-- | Compute final position of a flexbox's children.
flexPosition :: ((Double, Double) -> a -> b) -> (a -> Size Double Double) ->
        (Double, Double) -> Size Double Double ->
        FlexParent a Double -> FlexParent b Double
flexPosition cb cb' (x,y) size self@FlexParent { direction = dir } = self {
        Flex a Double -> Flex b Double
flexPosition cb cb' (x,y) size self@Flex { direction = dir } = self {
    children = map rowPosition $ flexJustify rowsize (sizeCross size dir)
            (children self) (crossGap self) (justify self)
  } where

M Graphics/Layout/Flex/CSS.hs => Graphics/Layout/Flex/CSS.hs +21 -3
@@ 1,4 1,5 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Parse FlexBox-related CSS properties
module Graphics.Layout.Flex.CSS(CSSFlex(..), lowerFlex) where

import Data.CSS.Syntax.Tokens (Token(..), NumericValue(..))


@@ 9,21 10,37 @@ import Graphics.Layout.CSS.Length (parseLength, finalizeLength, n2f, Unitted, Fo
import Graphics.Layout.Box (Length)
import Data.Maybe (isJust)

-- | Parsed FlexBox-related CSS properties.
data CSSFlex = CSSFlex {
    -- | Parsed CSS flex-direction, axis component.
    directionCSS :: Direction,
    -- | Parsed CSS flex-direction, reversed flag
    reverseRowsCSS :: Bool,
    -- | Parsed CSS flex-wrap
    wrapCSS :: FlexWrapping,
    -- | Parsed CSS justify-content
    justifyCSS :: Maybe Justification,
    -- | Parsed CSS align-items
    alignItemsCSS :: Alignment,
    alignLinesCSS :: Maybe Justification, -- `Nothing` is "stretch"
    -- | Parsed CSS align-content, `Nothing` is "stretch"
    alignLinesCSS :: Maybe Justification,
    -- | Parsed CSS row-gap
    rowGapCSS :: Unitted,
    -- | Parsed CSS column-gap
    columnGapCSS :: Unitted,

    -- flex children
    -- | Parsed CSS order
    orderCSS :: Integer,
    -- | Parsed CSS flex-grow
    growCSS :: Double,
    -- | Parsed CSS flex-shrink
    shrinkCSS :: Double,
    -- | Parsed CSS flex-basis
    basisCSS :: Unitted,
    -- | Parsed CSS align-self
    alignSelfCSS :: Alignment,
    -- | Whether justification or alignment properties should be parsed as right-to-left or left-to-right.
    textRTL :: Bool -- Extra parameter from caller.
}



@@ 167,8 184,9 @@ instance PropertyParser CSSFlex where
    shorthand self k v | Just _ <- longhand self self k v = [(k, v)]
        | otherwise = []

lowerFlex :: CSSFlex -> Font' -> [CSSFlex] -> [a] -> [Font'] -> FlexParent a Length
lowerFlex self font kids kids' fonts' = FlexParent {
-- | Lower the Flexbox styling tree to the Layout tree.
lowerFlex :: CSSFlex -> Font' -> [CSSFlex] -> [a] -> [Font'] -> Flex a Length
lowerFlex self font kids kids' fonts' = Flex {
    direction = directionCSS self,
    reverseRows = reverseRowsCSS self,
    wrap = wrapCSS self,

M test/Test.hs => test/Test.hs +6 -6
@@ 420,7 420,7 @@ spec = do
                Flex.alignment = AlStart,
                flexInner = ()
              }
            let baseFlex = FlexParent {
            let baseFlex = Flex.Flex {
                direction = Row,
                reverseRows = False,
                wrap = NoWrap,


@@ 431,7 431,7 @@ spec = do
                Flex.children = [[(child 10) { grow = 1 }, (child 20) { shrink = 1 },
                        (child 30) { grow = 2 }, (child 40) { shrink = 2 }]],
                pageWidth = 0
              } :: FlexParent () Double
              } :: Flex.Flex () Double
            -- These test results don't look right...
            flexWrap baseFlex 50 `shouldBe` baseFlex {
                Flex.children = [[(child 10) { grow = 1 },


@@ 715,7 715,7 @@ spec = do
                Flex.alignment = align,
                flexInner = l
              }
            let baseFlex = FlexParent {
            let baseFlex = Flex.Flex {
                direction = Row,
                reverseRows = False,
                wrap = Wrap,


@@ 728,7 728,7 @@ spec = do
                        (child 30 AlEnd) { grow = 2 },
                        (child 40 AlStretch) { shrink = 2 }]],
                pageWidth = 80
              } :: FlexParent Double Double
              } :: Flex.Flex Double Double
            let self = flexWrap baseFlex 50
            self `shouldBe` baseFlex {
                Flex.children = [[(child 10 AlStart) { grow = 1 },


@@ 783,7 783,7 @@ spec = do
                grow = 0, shrink = 0, basis = l,
                Flex.alignment = align, flexInner = (pos, l)
              }
            let flex childs = FlexParent {
            let flex childs = Flex.Flex {
                direction = Row,
                reverseRows = False,
                wrap = Wrap,


@@ 797,7 797,7 @@ spec = do
            let baseFlex = flex [[(child 10 AlStart) { grow = 1 },
                    (child 20 AlCenter) { shrink = 1 },
                    (child 30 AlEnd) { grow = 2 },
                    (child 40 AlStretch) { shrink = 2 }]] :: FlexParent Double Double
                    (child 40 AlStretch) { shrink = 2 }]] :: Flex.Flex Double Double
            flexPosition (,) (\a -> Size a a) (10, 10) (Size 50 50) baseFlex `shouldBe` flex [[
                (child' 10 AlStart (10, 10)) { grow = 1 },
                (child' 20 AlCenter (22, 20)) { shrink = 1 },