Skip to content

Commit 51a20a1

Browse files
clyringBodigrim
authored andcommitted
Make D.B.Lazy.zipWith properly lazy (#668)
* Make D.B.Lazy.zipWith properly lazy As a bonus, the new code is easier to read and doesn't trigger a spurious incomplete-pattern-match warning. (Or finding the bug can be seen as a bonus for cleaning up that messy code.) Fixes #667. * Lazy.zipWith: evaluate the 'unsafeHead' calls eagerly
1 parent 69d9862 commit 51a20a1

File tree

3 files changed

+45
-11
lines changed

3 files changed

+45
-11
lines changed

Data/ByteString/Lazy.hs

Lines changed: 18 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
21
{-# OPTIONS_HADDOCK prune #-}
32
{-# LANGUAGE Trustworthy #-}
43

@@ -1095,6 +1094,7 @@ splitWith p (Chunk c0 cs0) = comb [] (S.splitWith p c0) cs0
10951094
comb acc [s] Empty = [revChunks (s:acc)]
10961095
comb acc [s] (Chunk c cs) = comb (s:acc) (S.splitWith p c) cs
10971096
comb acc (s:ss) cs = revChunks (s:acc) : comb [] ss cs
1097+
comb _ [] _ = error "Strict splitWith returned [] for nonempty input"
10981098
{-# INLINE splitWith #-}
10991099

11001100
-- | /O(n)/ Break a 'ByteString' into pieces separated by the byte
@@ -1122,6 +1122,7 @@ split w (Chunk c0 cs0) = comb [] (S.split w c0) cs0
11221122
comb acc [s] Empty = [revChunks (s:acc)]
11231123
comb acc [s] (Chunk c cs) = comb (s:acc) (S.split w c) cs
11241124
comb acc (s:ss) cs = revChunks (s:acc) : comb [] ss cs
1125+
comb _ [] _ = error "Strict split returned [] for nonempty input"
11251126
{-# INLINE split #-}
11261127

11271128
-- | The 'group' function takes a ByteString and returns a list of
@@ -1441,16 +1442,22 @@ zipWith _ Empty _ = []
14411442
zipWith _ _ Empty = []
14421443
zipWith f (Chunk a as) (Chunk b bs) = go a as b bs
14431444
where
1444-
go x xs y ys = f (S.unsafeHead x) (S.unsafeHead y)
1445-
: to (S.unsafeTail x) xs (S.unsafeTail y) ys
1446-
1447-
to x Empty _ _ | S.null x = []
1448-
to _ _ y Empty | S.null y = []
1449-
to x xs y ys | not (S.null x)
1450-
&& not (S.null y) = go x xs y ys
1451-
to x xs _ (Chunk y' ys) | not (S.null x) = go x xs y' ys
1452-
to _ (Chunk x' xs) y ys | not (S.null y) = go x' xs y ys
1453-
to _ (Chunk x' xs) _ (Chunk y' ys) = go x' xs y' ys
1445+
-- This loop is written in a slightly awkward way but ensures we
1446+
-- don't have to allocate any 'Chunk' objects to pass to a recursive
1447+
-- call. We have in some sense performed SpecConstr manually.
1448+
go !x xs !y ys = let
1449+
-- Creating a thunk for reading one byte would
1450+
-- be wasteful, so we evaluate these eagerly.
1451+
-- See also #558 for a similar issue with uncons.
1452+
!xHead = S.unsafeHead x
1453+
!yHead = S.unsafeHead y
1454+
in f xHead yHead : to (S.unsafeTail x) xs (S.unsafeTail y) ys
1455+
1456+
to !x xs !y ys
1457+
| Chunk x' xs' <- chunk x xs
1458+
, Chunk y' ys' <- chunk y ys
1459+
= go x' xs' y' ys'
1460+
| otherwise = []
14541461

14551462
-- | A specialised version of `zipWith` for the common case of a
14561463
-- simultaneous map over two ByteStrings, to build a 3rd.

tests/Properties/ByteString.hs

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
-- License : BSD-style
55

66
{-# LANGUAGE CPP #-}
7+
78
{-# LANGUAGE AllowAmbiguousTypes #-}
89
{-# LANGUAGE ViewPatterns #-}
910
{-# LANGUAGE ScopedTypeVariables #-}
@@ -603,6 +604,16 @@ tests =
603604
\f x y -> (B.zipWith f x y :: [Int]) === zipWith f (B.unpack x) (B.unpack y)
604605
, testProperty "packZipWith" $
605606
\f x y -> B.unpack (B.packZipWith ((toElem .) . f) x y) === zipWith ((toElem .) . f) (B.unpack x) (B.unpack y)
607+
# ifdef BYTESTRING_LAZY
608+
-- Don't use (===) in these laziness tests:
609+
-- We don't want printing the test case to fail!
610+
, testProperty "zip is lazy" $ lazyZipTest $
611+
\x y -> B.zip x y == zip (B.unpack x) (B.unpack y)
612+
, testProperty "zipWith is lazy" $ \f -> lazyZipTest $
613+
\x y -> (B.zipWith f x y :: [Int]) == zipWith f (B.unpack x) (B.unpack y)
614+
, testProperty "packZipWith is lazy" $ \f -> lazyZipTest $
615+
\x y -> B.unpack (B.packZipWith ((toElem .) . f) x y) == zipWith ((toElem .) . f) (B.unpack x) (B.unpack y)
616+
# endif
606617
, testProperty "unzip" $
607618
\(fmap (toElem *** toElem) -> xs) -> (B.unpack *** B.unpack) (B.unzip xs) === unzip xs
608619
#endif
@@ -797,3 +808,17 @@ readIntegerUnsigned xs = case readMaybe ys of
797808
where
798809
(ys, zs) = span isDigit xs
799810
#endif
811+
812+
#ifdef BYTESTRING_LAZY
813+
lazyZipTest
814+
:: Testable prop
815+
=> (BYTESTRING_TYPE -> BYTESTRING_TYPE -> prop)
816+
-> BYTESTRING_TYPE -> BYTESTRING_TYPE -> Property
817+
lazyZipTest fun = \x0 y0 -> let
818+
msg = "Input chunks are: " ++ show (B.toChunks x0, B.toChunks y0)
819+
(x, y) | B.length x0 <= B.length y0
820+
= (x0, y0 <> error "too strict")
821+
| otherwise
822+
= (x0 <> error "too strict", y0)
823+
in counterexample msg (fun x y)
824+
#endif

tests/QuickCheckUtils.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,8 @@ instance Arbitrary L.ByteString where
5656
(sizedByteString
5757
(n `div` numChunks))
5858

59+
shrink = map L.fromChunks . shrink . L.toChunks
60+
5961
instance CoArbitrary L.ByteString where
6062
coarbitrary s = coarbitrary (L.unpack s)
6163

0 commit comments

Comments
 (0)