aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-03-16 08:20:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-03-16 08:20:12 -0700
commit0cbb811f3d306f33299c2122c3ccc8f77642884c (patch)
tree6b8ba53e54e2b59fa91b8c9c5e33d2167b695f5a /src
parent2240c4d80b15d45b8aa4683190748fcde50eb405 (diff)
downloadpandoc-0cbb811f3d306f33299c2122c3ccc8f77642884c.tar.gz
Extensions: Semigroup instance for Extensions with base >= 4.9.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Extensions.hs17
1 files changed, 13 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 968476930..31ca0d2f4 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -1,3 +1,8 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE TemplateHaskell #-}
{-
Copyright (C) 2012-2018 John MacFarlane <jgm@berkeley.edu>
@@ -15,10 +20,6 @@ You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveGeneric #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE TemplateHaskell #-}
{- |
Module : Text.Pandoc.Extensions
@@ -59,9 +60,17 @@ import Text.Parsec
newtype Extensions = Extensions Integer
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic, ToJSON, FromJSON)
+#if MIN_VERSION_base(4,9,0)
+instance Semigroup Extensions where
+ (Extensions a) <> (Extensions b) = Extensions (a .|. b)
+instance Monoid Extensions where
+ mempty = Extensions 0
+ mappend = (<>)
+#else
instance Monoid Extensions where
mempty = Extensions 0
mappend (Extensions a) (Extensions b) = Extensions (a .|. b)
+#endif
extensionsFromList :: [Extension] -> Extensions
extensionsFromList = foldr enableExtension emptyExtensions