aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Compat
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Compat')
-rw-r--r--src/Text/Pandoc/Compat/Monoid.hs20
-rw-r--r--src/Text/Pandoc/Compat/TagSoupEntity.hs15
2 files changed, 35 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Compat/Monoid.hs b/src/Text/Pandoc/Compat/Monoid.hs
new file mode 100644
index 000000000..cb7ea2527
--- /dev/null
+++ b/src/Text/Pandoc/Compat/Monoid.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE CPP #-}
+module Text.Pandoc.Compat.Monoid ( Monoid(..)
+ , (<>)
+ ) where
+
+#if MIN_VERSION_base(4,5,0)
+import Data.Monoid ((<>), Monoid(..))
+#else
+import Data.Monoid (mappend, Monoid(..))
+#endif
+
+#if MIN_VERSION_base(4,5,0)
+#else
+infixr 6 <>
+
+-- | An infix synonym for 'mappend'.
+(<>) :: Monoid m => m -> m -> m
+(<>) = mappend
+{-# INLINE (<>) #-}
+#endif
diff --git a/src/Text/Pandoc/Compat/TagSoupEntity.hs b/src/Text/Pandoc/Compat/TagSoupEntity.hs
new file mode 100644
index 000000000..80985aef9
--- /dev/null
+++ b/src/Text/Pandoc/Compat/TagSoupEntity.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE CPP #-}
+module Text.Pandoc.Compat.TagSoupEntity (lookupEntity
+ ) where
+
+import qualified Text.HTML.TagSoup.Entity as TE
+
+lookupEntity :: String -> Maybe Char
+#if MIN_VERSION_tagsoup(0,13,0)
+lookupEntity = str2chr . TE.lookupEntity
+ where str2chr :: Maybe String -> Maybe Char
+ str2chr (Just [c]) = Just c
+ str2chr _ = Nothing
+#else
+lookupEntity = TE.lookupEntity
+#endif