Skip to content

Commit daae939

Browse files
committed
Implement differenceBySorted API
1 parent 3b29249 commit daae939

File tree

3 files changed

+95
-6
lines changed

3 files changed

+95
-6
lines changed

src/Streamly/Internal/Data/Stream/IsStream/Top.hs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ module Streamly.Internal.Data.Stream.IsStream.Top
3030
, intersectBy
3131
, intersectBySorted
3232
, differenceBy
33-
, mergeDifferenceBy
33+
, differenceBySorted
3434
, unionBy
3535
, unionBySorted
3636

@@ -567,11 +567,14 @@ differenceBy eq s1 s2 =
567567
--
568568
-- Space: O(1)
569569
--
570-
-- /Unimplemented/
571-
{-# INLINE mergeDifferenceBy #-}
572-
mergeDifferenceBy :: -- (IsStream t, Monad m) =>
570+
-- /Pre-release/
571+
{-# INLINE differenceBySorted #-}
572+
differenceBySorted :: (IsStream t, MonadIO m) =>
573573
(a -> a -> Ordering) -> t m a -> t m a -> t m a
574-
mergeDifferenceBy _eq _s1 _s2 = undefined
574+
differenceBySorted eq s1 =
575+
IsStream.fromStreamD
576+
. StreamD.differenceBySorted eq (IsStream.toStreamD s1)
577+
. IsStream.toStreamD
575578

576579
-- | This is essentially an append operation that appends all the extra
577580
-- occurrences of elements from the second stream that are not already present

src/Streamly/Internal/Data/Stream/StreamD/Nesting.hs

Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -144,6 +144,7 @@ module Streamly.Internal.Data.Stream.StreamD.Nesting
144144
, splitInnerBySuffix
145145
, intersectBySorted
146146
, unionBySorted
147+
, differenceBySorted
147148
)
148149
where
149150

@@ -3038,3 +3039,67 @@ unionBySorted cmp (Stream stepa ta) (Stream stepb tb) =
30383039
)
30393040

30403041
step _ (_, _, _, _, _, _, _) = return Stop
3042+
3043+
-------------------------------------------------------------------------------
3044+
-- Difference of sorted streams -----------------------------------------------
3045+
-------------------------------------------------------------------------------
3046+
{-# INLINE_NORMAL differenceBySorted #-}
3047+
differenceBySorted :: (Monad m) =>
3048+
(a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a
3049+
differenceBySorted cmp (Stream stepa ta) (Stream stepb tb) =
3050+
Stream step (Just ta, Just tb, Nothing, Nothing, Nothing)
3051+
3052+
where
3053+
{-# INLINE_LATE step #-}
3054+
3055+
-- one of the values is missing, and the corresponding stream is running
3056+
step gst (Just sa, sb, Nothing, b, Nothing) = do
3057+
r <- stepa gst sa
3058+
return $ case r of
3059+
Yield a sa' -> Skip (Just sa', sb, Just a, b, Nothing)
3060+
Skip sa' -> Skip (Just sa', sb, Nothing, b, Nothing)
3061+
Stop -> Skip (Nothing, sb, Nothing, b, Nothing)
3062+
3063+
step gst (sa, Just sb, a, Nothing, Nothing) = do
3064+
r <- stepb gst sb
3065+
return $ case r of
3066+
Yield b sb' -> Skip (sa, Just sb', a, Just b, Nothing)
3067+
Skip sb' -> Skip (sa, Just sb', a, Nothing, Nothing)
3068+
Stop -> Skip (sa, Nothing, a, Nothing, Nothing)
3069+
3070+
-- Matching element
3071+
step gst (Just sa, Just sb, Nothing, _, Just _) = do
3072+
r1 <- stepa gst sa
3073+
r2 <- stepb gst sb
3074+
return $ case r1 of
3075+
Yield a sa' ->
3076+
case r2 of
3077+
Yield c sb' ->
3078+
Skip (Just sa', Just sb', Just a, Just c, Nothing)
3079+
Skip sb' ->
3080+
Skip (Just sa', Just sb', Just a, Just a, Nothing)
3081+
Stop ->
3082+
Yield a (Just sa', Just sb, Nothing, Nothing, Just a)
3083+
Skip sa' ->
3084+
case r2 of
3085+
Yield c sb' ->
3086+
Skip (Just sa', Just sb', Just c, Just c, Nothing)
3087+
Skip sb' ->
3088+
Skip (Just sa', Just sb', Nothing, Nothing, Nothing)
3089+
Stop ->
3090+
Stop
3091+
Stop ->
3092+
Stop
3093+
3094+
-- both the values are available
3095+
step _ (sa, sb, Just a, Just b, Nothing) = do
3096+
let res = cmp a b
3097+
return $ case res of
3098+
GT -> Skip (sa, sb, Just a, Nothing, Nothing)
3099+
LT -> Yield a (sa, sb, Nothing, Just b, Nothing)
3100+
EQ -> Skip (sa, sb, Nothing, Just b, Just b)
3101+
3102+
-- one of the values is missing, corresponding stream is done
3103+
step _ (sa, Nothing, Just a, Nothing, Nothing) =
3104+
return $ Yield a (sa, Nothing, Nothing, Nothing , Nothing)
3105+
step _ (_, _, _, _, _) = return Stop

test/Streamly/Test/Data/Stream/Top.hs

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module Main (main)
22
where
33

4-
import Data.List (intersect, sort, union)
4+
import Data.List (intersect, sort, union, (\\))
55
import Test.QuickCheck
66
( Gen
77
, Property
@@ -64,6 +64,26 @@ unionBySorted =
6464
(S.fromList ls1)
6565
let v2 = sort $ union ls0 ls1
6666
assert (v1 == v2)
67+
68+
differenceBySorted :: Property
69+
differenceBySorted =
70+
forAll (listOf (chooseInt (min_value, max_value))) $ \ls0 ->
71+
forAll (listOf (chooseInt (min_value, max_value))) $ \ls1 ->
72+
monadicIO $ action (sort ls0) (sort ls1)
73+
74+
where
75+
76+
action ls0 ls1 = do
77+
v1 <-
78+
run
79+
$ S.toList
80+
$ Top.differenceBySorted
81+
compare
82+
(S.fromList ls0)
83+
(S.fromList ls1)
84+
let v2 = ls0 \\ ls1
85+
assert (v1 == sort v2)
86+
6787
-------------------------------------------------------------------------------
6888
moduleName :: String
6989
moduleName = "Data.Stream.Top"
@@ -74,3 +94,4 @@ main = hspec $ do
7494
-- intersect
7595
prop "intersectBySorted" Main.intersectBySorted
7696
prop "unionBySorted" Main.unionBySorted
97+
prop "differenceBySorted" Main.differenceBySorted

0 commit comments

Comments
 (0)