[commit: packages/binary] master: Port ensureN to use withInputChunks. (384dd59)
git at git.haskell.org
git at git.haskell.org
Mon Jun 1 08:47:49 UTC 2015
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/384dd591258b287547023dc38c99345cdd2797a5
>---------------------------------------------------------------
commit 384dd591258b287547023dc38c99345cdd2797a5
Author: Lennart Kolmodin <kolmodin at google.com>
Date: Sat May 30 14:28:10 2015 +0200
Port ensureN to use withInputChunks.
>---------------------------------------------------------------
384dd591258b287547023dc38c99345cdd2797a5
src/Data/Binary/Get/Internal.hs | 16 ++++++----------
1 file changed, 6 insertions(+), 10 deletions(-)
diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs
index 6659727..804fde1 100644
--- a/src/Data/Binary/Get/Internal.hs
+++ b/src/Data/Binary/Get/Internal.hs
@@ -398,18 +398,14 @@ ensureN :: Int -> Get ()
ensureN !n0 = C $ \inp ks -> do
if B.length inp >= n0
then ks inp ()
- else runCont (go n0 []) inp ks
+ else runCont (withInputChunks n0 enoughChunks onSucc onFail >>= put) inp ks
where -- might look a bit funny, but plays very well with GHC's inliner.
-- GHC won't inline recursive functions, so we make ensureN non-recursive
- go !n bss0 = C $ \inp ks ->
- let n' = n - B.length inp
- bss = inp : bss0
- in if n' <= 0
- then ks (B.concat $ reverse bss) ()
- else
- prompt'
- (Fail (B.concat $ reverse bss) "not enough bytes")
- (\inp' -> runCont (go n' bss) inp' ks)
+ enoughChunks n str
+ | B.length str >= n = Right (str,B.empty)
+ | otherwise = Left (n - B.length str)
+ onSucc = B.concat
+ onFail bss = C $ \_ _ -> Fail (B.concat bss) "not enough bytes"
{-# INLINE ensureN #-}
unsafeReadN :: Int -> (B.ByteString -> a) -> Get a
More information about the ghc-commits
mailing list