{-# LANGUAGE OverloadedStrings, ViewPatterns #-} -- | Infrastructure for parsing & desugaring text related CSS properties. module Graphics.Layout.Inline.CSS( CSSInline(..), Default(..), UnicodeBidi(..), applyFontInline, applyBidi) where import Data.CSS.Syntax.Tokens (Token(..)) import Stylist (PropertyParser(..)) import qualified Data.Text as Txt import Data.Text (Text) import Data.Text.ParagraphLayout.Rich import Data.Text.Glyphize (Direction(..)) import Graphics.Layout.CSS.Font (Font'(..), hbUnit) import Data.Char (isSpace) import Debug.Trace (trace) -- To report unexpected cases. -- | Document text with Balkón styling options, CSS stylable. data CSSInline = CSSInline Txt.Text TextOptions UnicodeBidi -- | To what degree is the text direction isolated? data UnicodeBidi = BdNormal | BdEmbed | BdOverride | BdIsolate | BdIsolateOverride | BdPlainText deriving (Eq, Ord, Enum, Read, Show) instance PropertyParser CSSInline where temp = CSSInline "" (defaultTextOptions DirLTR) BdNormal inherit (CSSInline _ opts _) = CSSInline "" opts BdNormal priority _ = ["direction"] -- To inform logical spacing in caller! longhand _ (CSSInline _ opts bidi) "content" [Ident "initial"] = Just $ CSSInline "" opts bidi longhand _ (CSSInline _ opts bidi) "content" toks | all isString toks = Just $ CSSInline (Txt.concat [x | String x <- toks]) opts bidi where isString (String _) = True isString _ = False longhand _ (CSSInline t o b) "-argo-lang" [Ident kw] | kw `elem` ["initial", "auto"] = Just $ CSSInline t o {textLanguage=""} b longhand _ (CSSInline txt opts bidi) "-argo-lang" [String x] = Just $ CSSInline txt opts { textLanguage = Txt.unpack x } bidi longhand _ (CSSInline txt opts bidi) "direction" [Ident "ltr"] = Just $ CSSInline txt opts { textDirection = DirLTR } bidi longhand _ (CSSInline txt opts bidi) "direction" [Ident "rtl"] = Just $ CSSInline txt opts { textDirection = DirRTL } bidi longhand _ (CSSInline txt opts bidi) "direction" [Ident "initial"] = Just $ CSSInline txt opts { textDirection = DirLTR } bidi longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "initial"] = Just $ CSSInline txt opts BdNormal longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "normal"] = Just $ CSSInline txt opts BdNormal longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "embed"] = Just $ CSSInline txt opts BdEmbed longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "isolate"] = Just $ CSSInline txt opts BdIsolate longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "bidi-override"] = Just $ CSSInline txt opts BdOverride longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "isolate-override"] = Just $ CSSInline txt opts BdIsolateOverride longhand _ (CSSInline txt opts _) "unicode-bidi" [Ident "plaintext"] = Just $ CSSInline txt opts BdPlainText longhand _ _ _ _ = Nothing applyFontInline :: TextOptions -> Font' -> TextOptions applyFontInline opts font = opts { textFont = hbFont font, textLineHeight = Absolute $ toEnum $ fromEnum $ lineheight font * hbUnit } -- | Apply Bidi chars around the inline text. FIXME: Handle the tree! applyBidi :: Default d => CSSInline -> [InnerNode Text d] -> [InnerNode Text d] applyBidi (CSSInline _ _ BdNormal) txt = txt applyBidi (CSSInline _ (textDirection -> DirLTR) BdEmbed) txt = chLREmbed:txt+:chPopDir applyBidi (CSSInline _ (textDirection -> DirRTL) BdEmbed) txt = chRLEmbed:txt+:chPopDir applyBidi (CSSInline _ (textDirection -> DirLTR) BdIsolate) txt = chLRIsolate:txt+:chPopDirIsolate applyBidi (CSSInline _ (textDirection -> DirRTL) BdIsolate) txt = chRLIsolate:txt+:chPopDirIsolate applyBidi (CSSInline _ (textDirection -> DirLTR) BdOverride) txt = chLROverride:txt+:chPopDir applyBidi (CSSInline _ (textDirection -> DirRTL) BdOverride) txt = chRLOverride:txt+:chPopDir applyBidi (CSSInline _ (textDirection -> DirLTR) BdIsolateOverride) txt = ch1stStrongIsolate:chLROverride:txt+:chPopDir+:chPopDirIsolate applyBidi (CSSInline _ (textDirection -> DirRTL) BdIsolateOverride) txt = ch1stStrongIsolate:chRLOverride:txt+:chPopDir+:chPopDirIsolate applyBidi (CSSInline _ _ BdPlainText) txt = ch1stStrongIsolate:txt+:chPopDirIsolate applyBidi (CSSInline _ (textDirection -> dir) _) txt = trace ("Unexpected direction! " ++ show dir) txt a +: b = a ++ [b] chLREmbed, chRLEmbed, chLROverride, chRLOverride, chPopDir, chLRIsolate, chRLIsolate, ch1stStrongIsolate, chPopDirIsolate :: Default a => InnerNode Text a chLREmbed = leaf '\x202A' chRLEmbed = leaf '\x202B' chLROverride = leaf '\x202D' chRLOverride = leaf '\x202E' chPopDir = leaf '\x202C' chLRIsolate = leaf '\x2066' chRLIsolate = leaf '\x2067' ch1stStrongIsolate = leaf '\x2068' chPopDirIsolate = leaf '\x2069' leaf ch = TextSequence def $ Txt.singleton ch class Default a where def :: a