[commit: packages/binary] master: Fix compilation error on GHC < 8. (df9f3b7)
git at git.haskell.org
git at git.haskell.org
Tue Apr 19 20:30:46 UTC 2016
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/df9f3b7e7fb533a41c569126ddfbb65530e83835
>---------------------------------------------------------------
commit df9f3b7e7fb533a41c569126ddfbb65530e83835
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date: Tue Apr 19 17:28:56 2016 +0200
Fix compilation error on GHC < 8.
>---------------------------------------------------------------
df9f3b7e7fb533a41c569126ddfbb65530e83835
src/Data/Binary/Put.hs | 10 +++++-----
1 file changed, 5 insertions(+), 5 deletions(-)
diff --git a/src/Data/Binary/Put.hs b/src/Data/Binary/Put.hs
index b476694..cc6e414 100644
--- a/src/Data/Binary/Put.hs
+++ b/src/Data/Binary/Put.hs
@@ -115,18 +115,18 @@ instance Functor PutM where
{-# INLINE fmap #-}
instance Applicative PutM where
- pure a = Put $ PairS a mempty
+ pure a = Put $ PairS a Monoid.mempty
{-# INLINE pure #-}
m <*> k = Put $
let PairS f w = unPut m
PairS x w' = unPut k
- in PairS (f x) (w `mappend` w')
+ in PairS (f x) (w `Monoid.mappend` w')
m *> k = Put $
let PairS _ w = unPut m
PairS b w' = unPut k
- in PairS b (w `mappend` w')
+ in PairS b (w `Monoid.mappend` w')
{-# INLINE (*>) #-}
-- Standard Writer monad, with aggressive inlining
@@ -134,7 +134,7 @@ instance Monad PutM where
m >>= k = Put $
let PairS a w = unPut m
PairS b w' = unPut (k a)
- in PairS b (w `mappend` w')
+ in PairS b (w `Monoid.mappend` w')
{-# INLINE (>>=) #-}
return = pure
@@ -158,7 +158,7 @@ mappend' :: Put -> Put -> Put
mappend' m k = Put $
let PairS _ w = unPut m
PairS _ w' = unPut k
- in PairS () (w `mappend` w')
+ in PairS () (w `Monodid.mappend` w')
{-# INLINE mappend' #-}
#ifdef HAS_SEMIGROUP
More information about the ghc-commits
mailing list