aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/CSS.hs
diff options
context:
space:
mode:
authorOphir Lifshitz <hangfromthefloor@gmail.com>2015-07-24 02:53:17 -0400
committerOphir Lifshitz <hangfromthefloor@gmail.com>2015-07-24 02:53:17 -0400
commit7ef8700734ea8caae083e372b51cfe7bf2c51f9b (patch)
tree62fb2ab77fe8825044e473f705a267ebe4e493d2 /src/Text/Pandoc/CSS.hs
parent8390d935d8af944690736b7f2da5f2a58d97351b (diff)
downloadpandoc-7ef8700734ea8caae083e372b51cfe7bf2c51f9b.tar.gz
HTML Reader: Parse <ol> type, class, and inline list-style(-type) CSS
Diffstat (limited to 'src/Text/Pandoc/CSS.hs')
-rw-r--r--src/Text/Pandoc/CSS.hs35
1 files changed, 35 insertions, 0 deletions
diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs
new file mode 100644
index 000000000..32a5ea129
--- /dev/null
+++ b/src/Text/Pandoc/CSS.hs
@@ -0,0 +1,35 @@
+module Text.Pandoc.CSS ( foldOrElse,
+ pickStyleAttrProps
+ )
+where
+
+import Text.Pandoc.Shared (trim)
+import Text.Parsec
+import Text.Parsec.String
+import Control.Applicative ((<*))
+
+ruleParser :: Parser (String, String)
+ruleParser = do
+ p <- many1 (noneOf ":") <* char ':'
+ v <- many1 (noneOf ":;") <* char ';' <* spaces
+ return (trim p, trim v)
+
+styleAttrParser :: Parser [(String, String)]
+styleAttrParser = do
+ p <- many1 ruleParser
+ return p
+
+orElse :: Eq a => a -> a -> a -> a
+orElse v x y = if v == x then y else x
+
+foldOrElse :: Eq a => a -> [a] -> a
+foldOrElse v xs = foldr (orElse v) v xs
+
+eitherToMaybe :: Either a b -> Maybe b
+eitherToMaybe (Right x) = Just x
+eitherToMaybe _ = Nothing
+
+pickStyleAttrProps :: [String] -> String -> Maybe String
+pickStyleAttrProps lookupProps styleAttr = do
+ styles <- eitherToMaybe $ parse styleAttrParser "" styleAttr
+ foldOrElse Nothing $ map (flip lookup styles) lookupProps