[commit: packages/bytestring] master, revert-46-patch-1, wip/nix-local-build: Define Semigroup instances for base>=4.9 (21b18ec)
git at git.haskell.org
git at git.haskell.org
Tue May 3 22:43:51 UTC 2016
Repository : ssh://git@git.haskell.org/bytestring
On branches: master,revert-46-patch-1,wip/nix-local-build
Link : http://git.haskell.org/packages/bytestring.git/commitdiff/21b18ec8707211c58321d96b07d0d1fcce98930d
>---------------------------------------------------------------
commit 21b18ec8707211c58321d96b07d0d1fcce98930d
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Sat Nov 28 21:39:19 2015 +0100
Define Semigroup instances for base>=4.9
See https://github.com/ekmett/semigroups/issues/56 for more details
>---------------------------------------------------------------
21b18ec8707211c58321d96b07d0d1fcce98930d
Data/ByteString/Builder/Internal.hs | 13 +++++++++++++
Data/ByteString/Internal.hs | 12 ++++++++++++
Data/ByteString/Lazy/Internal.hs | 12 ++++++++++++
Data/ByteString/Short/Internal.hs | 12 ++++++++++++
4 files changed, 49 insertions(+)
diff --git a/Data/ByteString/Builder/Internal.hs b/Data/ByteString/Builder/Internal.hs
index 90512e7..f5a2509 100644
--- a/Data/ByteString/Builder/Internal.hs
+++ b/Data/ByteString/Builder/Internal.hs
@@ -130,6 +130,9 @@ module Data.ByteString.Builder.Internal (
import Control.Arrow (second)
+#if MIN_VERSION_base(4,9,0)
+import Data.Semigroup (Semigroup((<>)))
+#endif
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
import Control.Applicative (Applicative(..),(<$>))
@@ -399,11 +402,21 @@ empty = Builder (\cont -> (\range -> cont range))
append :: Builder -> Builder -> Builder
append (Builder b1) (Builder b2) = Builder $ b1 . b2
+#if MIN_VERSION_base(4,9,0)
+instance Semigroup Builder where
+ {-# INLINE (<>) #-}
+ (<>) = append
+#endif
+
instance Monoid Builder where
{-# INLINE mempty #-}
mempty = empty
{-# INLINE mappend #-}
+#if MIN_VERSION_base(4,9,0)
+ mappend = (<>)
+#else
mappend = append
+#endif
{-# INLINE mconcat #-}
mconcat = foldr mappend mempty
diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs
index 02ba01e..2565a49 100644
--- a/Data/ByteString/Internal.hs
+++ b/Data/ByteString/Internal.hs
@@ -89,6 +89,9 @@ import Foreign.C.Types (CInt, CSize, CULong)
#endif
import Foreign.C.String (CString)
+#if MIN_VERSION_base(4,9,0)
+import Data.Semigroup (Semigroup((<>)))
+#endif
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (Monoid(..))
#endif
@@ -150,9 +153,18 @@ instance Eq ByteString where
instance Ord ByteString where
compare = compareBytes
+#if MIN_VERSION_base(4,9,0)
+instance Semigroup ByteString where
+ (<>) = append
+#endif
+
instance Monoid ByteString where
mempty = PS nullForeignPtr 0 0
+#if MIN_VERSION_base(4,9,0)
+ mappend = (<>)
+#else
mappend = append
+#endif
mconcat = concat
instance NFData ByteString where
diff --git a/Data/ByteString/Lazy/Internal.hs b/Data/ByteString/Lazy/Internal.hs
index 2d71732..964f23b 100644
--- a/Data/ByteString/Lazy/Internal.hs
+++ b/Data/ByteString/Lazy/Internal.hs
@@ -51,6 +51,9 @@ import qualified Data.ByteString as S (length, take, drop)
import Data.Word (Word8)
import Foreign.Storable (Storable(sizeOf))
+#if MIN_VERSION_base(4,9,0)
+import Data.Semigroup (Semigroup((<>)))
+#endif
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (Monoid(..))
#endif
@@ -77,9 +80,18 @@ instance Eq ByteString where
instance Ord ByteString where
compare = cmp
+#if MIN_VERSION_base(4,9,0)
+instance Semigroup ByteString where
+ (<>) = append
+#endif
+
instance Monoid ByteString where
mempty = Empty
+#if MIN_VERSION_base(4,9,0)
+ mappend = (<>)
+#else
mappend = append
+#endif
mconcat = concat
instance NFData ByteString where
diff --git a/Data/ByteString/Short/Internal.hs b/Data/ByteString/Short/Internal.hs
index 1946271..15308d6 100644
--- a/Data/ByteString/Short/Internal.hs
+++ b/Data/ByteString/Short/Internal.hs
@@ -40,6 +40,9 @@ import Data.ByteString.Internal (ByteString(..), accursedUnutterablePerformIO)
import Data.Typeable (Typeable)
import Data.Data (Data(..), mkNoRepType)
+#if MIN_VERSION_base(4,9,0)
+import Data.Semigroup (Semigroup((<>)))
+#endif
import Data.Monoid (Monoid(..))
import Data.String (IsString(..))
import Control.DeepSeq (NFData(..))
@@ -131,9 +134,18 @@ instance Eq ShortByteString where
instance Ord ShortByteString where
compare = compareBytes
+#if MIN_VERSION_base(4,9,0)
+instance Semigroup ShortByteString where
+ (<>) = append
+#endif
+
instance Monoid ShortByteString where
mempty = empty
+#if MIN_VERSION_base(4,9,0)
+ mappend = (<>)
+#else
mappend = append
+#endif
mconcat = concat
instance NFData ShortByteString where
More information about the ghc-commits
mailing list