[commit: packages/bytestring] master: Fix unfoldrN to call the predicate at most n times. (8c3c7f3)
git at git.haskell.org
git at git.haskell.org
Fri Jan 23 22:43:46 UTC 2015
Repository : ssh://git@git.haskell.org/bytestring
On branch : master
Link : http://git.haskell.org/packages/bytestring.git/commitdiff/8c3c7f34ddc03089b1150c7c188fcaf72ef483de
>---------------------------------------------------------------
commit 8c3c7f34ddc03089b1150c7c188fcaf72ef483de
Author: Duncan Coutts <duncan at community.haskell.org>
Date: Sun Dec 14 16:19:24 2014 +0000
Fix unfoldrN to call the predicate at most n times.
As a consequence unfoldrN 0 (const Nothing) 0 is now ("", Just 0) where
before it was ("", Nothing). The other tests still pass.
This fixes issue #11.
>---------------------------------------------------------------
8c3c7f34ddc03089b1150c7c188fcaf72ef483de
Data/ByteString.hs | 14 +++++++-------
1 file changed, 7 insertions(+), 7 deletions(-)
diff --git a/Data/ByteString.hs b/Data/ByteString.hs
index 5240930..acd0a0f 100644
--- a/Data/ByteString.hs
+++ b/Data/ByteString.hs
@@ -825,13 +825,13 @@ unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
unfoldrN i f x0
| i < 0 = (empty, Just x0)
| otherwise = unsafePerformIO $ createAndTrim' i $ \p -> go p x0 0
- where go !p !x !n =
- case f x of
- Nothing -> return (0, n, Nothing)
- Just (w,x')
- | n == i -> return (0, n, Just x)
- | otherwise -> do poke p w
- go (p `plusPtr` 1) x' (n+1)
+ where
+ go !p !x !n
+ | n == i = return (0, n, Just x)
+ | otherwise = case f x of
+ Nothing -> return (0, n, Nothing)
+ Just (w,x') -> do poke p w
+ go (p `plusPtr` 1) x' (n+1)
{-# INLINE unfoldrN #-}
-- ---------------------------------------------------------------------
More information about the ghc-commits
mailing list