From 0cbb811f3d306f33299c2122c3ccc8f77642884c Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Fri, 16 Mar 2018 08:20:12 -0700
Subject: Extensions: Semigroup instance for Extensions with base >= 4.9.

---
 src/Text/Pandoc/Extensions.hs | 17 +++++++++++++----
 1 file changed, 13 insertions(+), 4 deletions(-)

(limited to 'src/Text')

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
-- 
cgit v1.2.3