~alcinnz/CatTrap

2fe0db0f29a37143ccd694ce1aa8912b26f18408 — Adrian Cochrane 1 year, 3 months ago fdea2a5
Handle  property on containing blocks.
2 files changed, 8 insertions(+), 3 deletions(-)

M Graphics/Layout/CSS.hs
M Graphics/Layout/Inline/CSS.hs
M Graphics/Layout/CSS.hs => Graphics/Layout/CSS.hs +7 -2
@@ 89,8 89,13 @@ finalizeChilds root parent style' childs@(child:childs')
          }:blocks)) -> let (inlines', blocks') = spanInlines tail
            in (inlines ++ inlines', blocks' ++ blocks)
        ret -> ret
    flattenTree0 childs = RootBox $ Box (map (flattenTree parent) $
        enumerate childs) $ flip applyFontInline parent $ txtOpts style'
    flattenTree0 childs
        | iStyle@(CSSInline _ _ bidi) <- inlineStyles style',
            bidi `elem` [BdOverride, BdIsolateOverride] = RootBox $ Box
                (applyBidi iStyle $ map (flattenTree parent) $ enumerate childs)
                $ flip applyFontInline parent $ txtOpts style'
        | otherwise = RootBox $ Box (map (flattenTree parent) $ enumerate childs)
            $ flip applyFontInline parent $ txtOpts style'
    flattenTree p (i, StyleTree { children = child@(_:_), style = self }) =
        buildInline f i self $ map (flattenTree f) $ enumerate child
      where f = pattern2font (font self) (font' self) p root

M Graphics/Layout/Inline/CSS.hs => Graphics/Layout/Inline/CSS.hs +1 -1
@@ 1,7 1,7 @@
{-# LANGUAGE OverloadedStrings, ViewPatterns #-}
-- | Infrastructure for parsing & desugaring text related CSS properties.
module Graphics.Layout.Inline.CSS(
    CSSInline(..), Default(..), applyFontInline, applyBidi) where
    CSSInline(..), Default(..), UnicodeBidi(..), applyFontInline, applyBidi) where

import Data.CSS.Syntax.Tokens (Token(..))
import Stylist (PropertyParser(..))