aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/CSS.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/CSS.hs')
-rw-r--r--src/Text/Pandoc/CSS.hs13
1 files changed, 7 insertions, 6 deletions
diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs
index 660ec1b12..47a96b468 100644
--- a/src/Text/Pandoc/CSS.hs
+++ b/src/Text/Pandoc/CSS.hs
@@ -19,17 +19,18 @@ module Text.Pandoc.CSS ( foldOrElse
where
import Prelude
+import qualified Data.Text as T
import Text.Pandoc.Shared (trim)
import Text.Parsec
-import Text.Parsec.String
+import Text.Parsec.Text
-ruleParser :: Parser (String, String)
+ruleParser :: Parser (T.Text, T.Text)
ruleParser = do
p <- many1 (noneOf ":") <* char ':'
v <- many1 (noneOf ":;") <* optional (char ';') <* spaces
- return (trim p, trim v)
+ return (trim $ T.pack p, trim $ T.pack v)
-styleAttrParser :: Parser [(String, String)]
+styleAttrParser :: Parser [(T.Text, T.Text)]
styleAttrParser = many1 ruleParser
orElse :: Eq a => a -> a -> a -> a
@@ -44,7 +45,7 @@ eitherToMaybe _ = Nothing
-- | takes a list of keys/properties and a CSS string and
-- returns the corresponding key-value-pairs.
-pickStylesToKVs :: [String] -> String -> [(String, String)]
+pickStylesToKVs :: [T.Text] -> T.Text -> [(T.Text, T.Text)]
pickStylesToKVs props styleAttr =
case parse styleAttrParser "" styleAttr of
Left _ -> []
@@ -52,7 +53,7 @@ pickStylesToKVs props styleAttr =
-- | takes a list of key/property synonyms and a CSS string and maybe
-- returns the value of the first match (in order of the supplied list)
-pickStyleAttrProps :: [String] -> String -> Maybe String
+pickStyleAttrProps :: [T.Text] -> T.Text -> Maybe T.Text
pickStyleAttrProps lookupProps styleAttr = do
styles <- eitherToMaybe $ parse styleAttrParser "" styleAttr
foldOrElse Nothing $ map (`lookup` styles) lookupProps