[commit: packages/binary] master: Remove INLINEs from GBinary/GSum methods (48c0296)

git at git.haskell.org git at git.haskell.org
Sun Dec 14 17:55:36 UTC 2014


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

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

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

commit 48c02966512a67b018fcdf093fab8d34bddf9a69
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Sep 25 22:07:13 2014 +0200

    Remove INLINEs from GBinary/GSum methods
    
    These interact very badly with GHC 7.9.x's simplifier
    
    See also
    
     - https://ghc.haskell.org/trac/ghc/ticket/9630 and
    
     - https://ghc.haskell.org/trac/ghc/ticket/9583


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

48c02966512a67b018fcdf093fab8d34bddf9a69
 src/Data/Binary/Generic.hs | 6 ------
 1 file changed, 6 deletions(-)

diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs
index 03ce711..a2eb6ea 100644
--- a/src/Data/Binary/Generic.hs
+++ b/src/Data/Binary/Generic.hs
@@ -72,13 +72,11 @@ instance ( GSum     a, GSum     b
          | otherwise = sizeError "encode" size
       where
         size = unTagged (sumSize :: Tagged (a :+: b) Word64)
-    {-# INLINE gput #-}
 
     gget | GETSUM(Word8) | GETSUM(Word16) | GETSUM(Word32) | GETSUM(Word64)
          | otherwise = sizeError "decode" size
       where
         size = unTagged (sumSize :: Tagged (a :+: b) Word64)
-    {-# INLINE gget #-}
 
 sizeError :: Show size => String -> size -> error
 sizeError s size =
@@ -102,7 +100,6 @@ instance (GSum a, GSum b, GBinary a, GBinary b) => GSum (a :+: b) where
         where
           sizeL = size `shiftR` 1
           sizeR = size - sizeL
-    {-# INLINE getSum #-}
 
     putSum !code !size s = case s of
                              L1 x -> putSum code           sizeL x
@@ -110,14 +107,11 @@ instance (GSum a, GSum b, GBinary a, GBinary b) => GSum (a :+: b) where
         where
           sizeL = size `shiftR` 1
           sizeR = size - sizeL
-    {-# INLINE putSum #-}
 
 instance GBinary a => GSum (C1 c a) where
     getSum _ _ = gget
-    {-# INLINE getSum #-}
 
     putSum !code _ x = put code *> gput x
-    {-# INLINE putSum #-}
 
 ------------------------------------------------------------------------
 



More information about the ghc-commits mailing list