[commit: packages/binary] master: Remove attempt to do clever fusion of code in applicative style. (11816f1)

git at git.haskell.org git at git.haskell.org
Sun Dec 20 22:30:43 UTC 2015


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

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

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

commit 11816f1fb2400171d018b784b9522604819b8778
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date:   Sun Dec 20 22:37:27 2015 +0100

    Remove attempt to do clever fusion of code in applicative style.
    
    Removing as it complicates binary and it's very hard for client code to
    trigger.


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

11816f1fb2400171d018b784b9522604819b8778
 src/Data/Binary/Get.hs          |  3 ---
 src/Data/Binary/Get/Internal.hs | 17 +++--------------
 2 files changed, 3 insertions(+), 17 deletions(-)

diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs
index de1a326..7773586 100644
--- a/src/Data/Binary/Get.hs
+++ b/src/Data/Binary/Get.hs
@@ -63,9 +63,6 @@
 --getTrade' = Trade '<$>' 'getWord32le' '<*>' 'getWord32le' '<*>' 'getWord16le'
 -- @
 --
--- The applicative style can sometimes result in faster code, as @binary@
--- will try to optimize the code by grouping the reads together.
---
 -- There are two kinds of ways to execute this decoder, the lazy input
 -- method and the incremental input method. Here we will use the lazy
 -- input method.
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index 2c5def9..74e8eba 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -95,10 +95,6 @@ instance Monad Get where
   (>>=) = bindG
   fail = failG
 
-returnG :: a -> Get a
-returnG a = C $ \s ks -> ks s a
-{-# INLINE [0] returnG #-}
-
 bindG :: Get a -> (a -> Get b) -> Get b
 bindG (C c) f = C $ \i ks -> c i (\i' a -> (runCont (f a)) i' ks)
 {-# INLINE bindG #-}
@@ -118,8 +114,8 @@ fmapG f m = C $ \i ks -> runCont m i (\i' a -> ks i' (f a))
 {-# INLINE fmapG #-}
 
 instance Applicative Get where
-  pure = returnG
-  {-# INLINE pure #-}
+  pure = \x -> C $ \s ks -> ks s x
+  {-# INLINE [0] pure #-}
   (<*>) = apG
   {-# INLINE (<*>) #-}
 
@@ -392,17 +388,10 @@ readN !n f = ensureN n >> unsafeReadN n f
 
 {-# RULES
 
-"<$> to <*>" forall f g.
-  (<$>) f g = returnG f <*> g
-
 "readN/readN merge" forall n m f g.
   apG (readN n f) (readN m g) = readN (n+m) (\bs -> f bs $ g (B.unsafeDrop n bs))
 
-"returnG/readN swap" [~1] forall f.
-  returnG f = readN 0 (const f)
-
-"readN 0/returnG swapback" [1] forall f.
-  readN 0 f = returnG (f B.empty) #-}
+ #-}
 
 -- | Ensure that there are at least @n@ bytes available. If not, the
 -- computation will escape with 'Partial'.



More information about the ghc-commits mailing list