Skip to content

Commit 47b6ba7

Browse files
committed
WIP on union.disjoint
1 parent 0de947c commit 47b6ba7

File tree

2 files changed

+10
-6
lines changed

2 files changed

+10
-6
lines changed

benchmarks/FineGrained.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,13 +67,13 @@ bUnion =
6767
[ bgroup "disjoint" bUnionDisjoint, bgroup "overlap" [], bgroup "same" [] ]
6868

6969
bUnionDisjoint :: [Benchmark]
70-
bUnionDisjoint = [bgroup "Bytes" [], bgroup "Int" []]
70+
bUnionDisjoint = [bgroup "Bytes" [env (bytesEnv s) (bytesB s) | s <- defaultSizes], bgroup "Int" []]
7171
where
72+
bytesB s tup = bench (show s) $ whnf (\ ~(as, bs) -> HM.union as bs) tup
7273
bytesEnv s = do
7374
g <- newIOGenM defaultGen
74-
trues <- undefined s
75-
falses <- undefined s
76-
return (map (,()) trues, map (,()) falses)
75+
(trues, falses) <- Key.Bytes.genDisjoint s bytesLength g
76+
return (HM.fromList (map (,()) trues), HM.fromList (map (,()) falses))
7777

7878

7979
genInts ::

benchmarks/Key/Bytes.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22

33
module Key.Bytes where
44

5+
import Data.List
56
import Control.Monad (replicateM)
67
import Data.ByteString.Short
78
import Data.Hashable
@@ -26,13 +27,16 @@ genNBytes ::
2627
m [Bytes]
2728
genNBytes n len = replicateM n . genBytes len
2829

30+
-- | @genDisjoint n len gen@ generates @n@ 'Bytes' in total. The returned lists
31+
-- each contain roughly half of the total.
2932
genDisjoint ::
3033
(StatefulGen g m) =>
3134
Int ->
32-
Int ->
35+
Int -> -- ^ Must be positive
3336
g ->
3437
m ([Bytes], [Bytes])
35-
genDisjoint n len = undefined
38+
genDisjoint n len gen = Data.List.partition predicate <$> genNBytes n len gen
39+
where predicate (Bytes sbs) = even (Data.ByteString.Short.head sbs)
3640
{-
3741
instance Uniform Bytes where
3842
uniformM = genBytes 32

0 commit comments

Comments
 (0)