{-# LANGUAGE OverloadedStrings #-}
-- | Infrastructure for parsing & desugaring text related CSS properties.
module Graphics.Layout.Inline.CSS(CSSInline(..), applyFontInline) where
import Data.CSS.Syntax.Tokens (Token(..))
import Stylist (PropertyParser(..))
import qualified Data.Text as Txt
import Data.Text.Internal (Text(..))
import Data.Text.ParagraphLayout.Rich
import Data.Text.Glyphize (Direction(..))
import Graphics.Layout.CSS.Font (Font'(..), hbUnit)
import Data.Char (isSpace)
-- | Document text with Balkón styling options, CSS stylable.
data CSSInline = CSSInline Txt.Text TextOptions
instance PropertyParser CSSInline where
temp = CSSInline "" $ defaultTextOptions DirLTR
inherit (CSSInline _ opts) = CSSInline "" opts
priority _ = ["direction"] -- To inform logical spacing in caller!
longhand _ (CSSInline _ o) "content" [Ident "initial"] = Just $ CSSInline "" o
longhand _ (CSSInline _ opts) "content" toks
| all isString toks =
Just $ CSSInline (Txt.concat [x | String x <- toks]) opts
where
isString (String _) = True
isString _ = False
longhand _ (CSSInline t o) "-argo-lang" [Ident kw]
| kw `elem` ["initial", "auto"] = Just $ CSSInline t o {textLanguage=""}
longhand _ (CSSInline txt opts) "-argo-lang" [String x] =
Just $ CSSInline txt opts { textLanguage = Txt.unpack x }
longhand _ (CSSInline txt opts) "direction" [Ident "ltr"] =
Just $ CSSInline txt opts { textDirection = DirLTR }
longhand _ (CSSInline txt opts) "direction" [Ident "rtl"] =
Just $ CSSInline txt opts { textDirection = DirRTL }
longhand _ (CSSInline txt opts) "direction" [Ident "initial"] =
Just $ CSSInline txt opts { textDirection = DirLTR }
longhand _ _ _ _ = Nothing
applyFontInline :: TextOptions -> Font' -> TextOptions
applyFontInline opts font = opts {
textFont = hbFont font,
textLineHeight = Absolute $ toEnum $ fromEnum $ lineheight font * hbUnit
}