[commit: packages/binary] master: Inline the Alternative functions. (4042fb5)
git at git.haskell.org
git at git.haskell.org
Sat Feb 4 21:17:46 UTC 2017
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/4042fb5243872a4f75fd6fe1a6f6941708993660
>---------------------------------------------------------------
commit 4042fb5243872a4f75fd6fe1a6f6941708993660
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date: Mon May 30 21:21:19 2016 +0200
Inline the Alternative functions.
The related benchmarks in benchmarks/Get.hs become 20% faster.
>---------------------------------------------------------------
4042fb5243872a4f75fd6fe1a6f6941708993660
src/Data/Binary/Get/Internal.hs | 4 ++++
1 file changed, 4 insertions(+)
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index b9a0818..c2ebcff 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -259,18 +259,22 @@ getBytes = getByteString
-- | /Since: 0.7.0.0/
instance Alternative Get where
empty = C $ \inp _ks -> Fail inp "Data.Binary.Get(Alternative).empty"
+ {-# INLINE empty #-}
(<|>) f g = do
(decoder, bs) <- runAndKeepTrack f
case decoder of
Done inp x -> C $ \_ ks -> ks inp x
Fail _ _ -> pushBack bs >> g
_ -> error "Binary: impossible"
+ {-# INLINE (<|>) #-}
some p = (:) <$> p <*> many p
+ {-# INLINE some #-}
many p = do
v <- (Just <$> p) <|> pure Nothing
case v of
Nothing -> pure []
Just x -> (:) x <$> many p
+ {-# INLINE many #-}
-- | Run a decoder and keep track of all the input it consumes.
-- Once it's finished, return the final decoder (always 'Done' or 'Fail'),
More information about the ghc-commits
mailing list