[commit: packages/binary] master: Drop redundant constraints (ebcb029)

git at git.haskell.org git at git.haskell.org
Sun Dec 20 21:16:35 UTC 2015


Repository : ssh://git@git.haskell.org/binary

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/ebcb0290a33d19d3b76b8547a58e7eefcd302548

>---------------------------------------------------------------

commit ebcb0290a33d19d3b76b8547a58e7eefcd302548
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Dec 19 11:34:52 2015 +0100

    Drop redundant constraints
    
    GHC HEAD warns about these


>---------------------------------------------------------------

ebcb0290a33d19d3b76b8547a58e7eefcd302548
 src/Data/Binary/Class.hs   | 4 ++--
 src/Data/Binary/Generic.hs | 6 ++----
 2 files changed, 4 insertions(+), 6 deletions(-)

diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs
index 2e6e19a..f94b9a2 100644
--- a/src/Data/Binary/Class.hs
+++ b/src/Data/Binary/Class.hs
@@ -268,13 +268,13 @@ instance Binary Integer where
 --
 -- Fold and unfold an Integer to and from a list of its bytes
 --
-unroll :: (Integral a, Num a, Bits a) => a -> [Word8]
+unroll :: (Integral a, Bits a) => a -> [Word8]
 unroll = unfoldr step
   where
     step 0 = Nothing
     step i = Just (fromIntegral i, i `shiftR` 8)
 
-roll :: (Integral a, Num a, Bits a) => [Word8] -> a
+roll :: (Integral a, Bits a) => [Word8] -> a
 roll   = foldl' unstep 0 . reverse
   where
     unstep a b = a `shiftL` 8 .|. fromIntegral b
diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs
index 551047e..9967f95 100644
--- a/src/Data/Binary/Generic.hs
+++ b/src/Data/Binary/Generic.hs
@@ -80,7 +80,6 @@ instance Binary a => GBinaryGet (K1 i a) where
 #define GETSUM(WORD) GUARD(WORD) = (get :: Get WORD) >>= checkGetSum (fromIntegral size)
 
 instance ( GSumPut  a, GSumPut  b
-         , GBinaryPut a, GBinaryPut b
          , SumSize    a, SumSize    b) => GBinaryPut (a :+: b) where
     gput | PUTSUM(Word8) | PUTSUM(Word16) | PUTSUM(Word32) | PUTSUM(Word64)
          | otherwise = sizeError "encode" size
@@ -88,7 +87,6 @@ instance ( GSumPut  a, GSumPut  b
         size = unTagged (sumSize :: Tagged (a :+: b) Word64)
 
 instance ( GSumGet  a, GSumGet  b
-         , GBinaryGet a, GBinaryGet b
          , SumSize    a, SumSize    b) => GBinaryGet (a :+: b) where
     gget | GETSUM(Word8) | GETSUM(Word16) | GETSUM(Word32) | GETSUM(Word64)
          | otherwise = sizeError "decode" size
@@ -113,14 +111,14 @@ class GSumGet f where
 class GSumPut f where
     putSum :: (Num w, Bits w, Binary w) => w -> w -> f a -> Put
 
-instance (GSumGet a, GSumGet b, GBinaryGet a, GBinaryGet b) => GSumGet (a :+: b) where
+instance (GSumGet a, GSumGet b) => GSumGet (a :+: b) where
     getSum !code !size | code < sizeL = L1 <$> getSum code           sizeL
                        | otherwise    = R1 <$> getSum (code - sizeL) sizeR
         where
           sizeL = size `shiftR` 1
           sizeR = size - sizeL
 
-instance (GSumPut a, GSumPut b, GBinaryPut a, GBinaryPut b) => GSumPut (a :+: b) where
+instance (GSumPut a, GSumPut b) => GSumPut (a :+: b) where
     putSum !code !size s = case s of
                              L1 x -> putSum code           sizeL x
                              R1 x -> putSum (code + sizeL) sizeR x



More information about the ghc-commits mailing list