Skip to content

Commit 545d583

Browse files
committed
prototype: add property test for union
1 parent df54c14 commit 545d583

File tree

3 files changed

+104
-39
lines changed

3 files changed

+104
-39
lines changed

prototypes/ScheduledMerges.hs

Lines changed: 54 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ module ScheduledMerges (
2828
new,
2929
LookupResult (..),
3030
lookup, lookups,
31+
Op,
3132
Update (..),
3233
update, updates,
3334
insert, inserts,
@@ -42,7 +43,9 @@ module ScheduledMerges (
4243
supplyUnionCredits,
4344

4445
-- * Test and trace
46+
MTree (..),
4547
logicalValue,
48+
Representation,
4649
dumpRepresentation,
4750
representationShape,
4851
Event,
@@ -65,6 +68,7 @@ import Control.Monad.ST
6568
import Control.Tracer (Tracer, contramap, traceWith)
6669
import GHC.Stack (HasCallStack, callStack)
6770

71+
import qualified Test.QuickCheck as QC
6872

6973
data LSM s = LSMHandle !(STRef s Counter)
7074
!(STRef s (LSMContent s))
@@ -1171,11 +1175,11 @@ expectCompletedMergingTree (MergingTree ref) = do
11711175
-- Measurements
11721176
--
11731177

1174-
data MTree = MLeaf Run
1175-
| MNode MergeType [MTree]
1176-
deriving stock Show
1178+
data MTree r = MLeaf r
1179+
| MNode MergeType [MTree r]
1180+
deriving stock (Eq, Foldable, Functor, Show)
11771181

1178-
allLevels :: LSM s -> ST s (Buffer, [[Run]], Maybe MTree)
1182+
allLevels :: LSM s -> ST s (Buffer, [[Run]], Maybe (MTree Run))
11791183
allLevels (LSMHandle _ lsmr) = do
11801184
LSMContent wb ls ul <- readSTRef lsmr
11811185
rs <- flattenLevels ls
@@ -1202,7 +1206,7 @@ flattenMergingRun (MergingRun _ ref) = do
12021206
CompletedMerge r -> return [r]
12031207
OngoingMerge _ rs _ -> return rs
12041208

1205-
flattenTree :: MergingTree s -> ST s MTree
1209+
flattenTree :: MergingTree s -> ST s (MTree Run)
12061210
flattenTree (MergingTree ref) = do
12071211
mts <- readSTRef ref
12081212
case mts of
@@ -1228,22 +1232,29 @@ logicalValue lsm = do
12281232
mergeRuns :: MergeType -> [Run] -> Run
12291233
mergeRuns = mergek
12301234

1231-
mergeTree :: MTree -> Run
1235+
mergeTree :: MTree Run -> Run
12321236
mergeTree (MLeaf r) = r
12331237
mergeTree (MNode mt ts) = mergeRuns mt (map mergeTree ts)
12341238

12351239
justInsert (Insert v b) = Just (v, b)
12361240
justInsert Delete = Nothing
12371241
justInsert (Mupsert v) = Just (v, Nothing)
12381242

1239-
-- TODO: Consider MergingTree, or just remove this function? It's unused.
1240-
dumpRepresentation :: LSM s
1241-
-> ST s [(Maybe (MergePolicy, MergeType, MergingRunState), [Run])]
1243+
type Representation = (Run, [LevelRepresentation], Maybe (MTree Run))
1244+
1245+
type LevelRepresentation =
1246+
(Maybe (MergePolicy, MergeType, MergingRunState), [Run])
1247+
1248+
dumpRepresentation :: LSM s -> ST s Representation
12421249
dumpRepresentation (LSMHandle _ lsmr) = do
1243-
LSMContent wb ls _ <- readSTRef lsmr
1244-
((Nothing, [wb]) :) <$> mapM dumpLevel ls
1250+
LSMContent wb ls ul <- readSTRef lsmr
1251+
levels <- mapM dumpLevel ls
1252+
tree <- case ul of
1253+
NoUnion -> return Nothing
1254+
Union t _ -> Just <$> flattenTree t
1255+
return (wb, levels, tree)
12451256

1246-
dumpLevel :: Level s -> ST s (Maybe (MergePolicy, MergeType, MergingRunState), [Run])
1257+
dumpLevel :: Level s -> ST s LevelRepresentation
12471258
dumpLevel (Level (Single r) rs) =
12481259
return (Nothing, (r:rs))
12491260
dumpLevel (Level (Merging mp (MergingRun mt ref)) rs) = do
@@ -1253,14 +1264,17 @@ dumpLevel (Level (Merging mp (MergingRun mt ref)) rs) = do
12531264
-- For each level:
12541265
-- 1. the runs involved in an ongoing merge
12551266
-- 2. the other runs (including completed merge)
1256-
representationShape :: [(Maybe (MergePolicy, MergeType, MergingRunState), [Run])]
1257-
-> [([Int], [Int])]
1258-
representationShape =
1259-
map $ \(mmr, rs) ->
1267+
representationShape :: Representation
1268+
-> (Int, [([Int], [Int])], Maybe (MTree Int))
1269+
representationShape (wb, levels, tree) =
1270+
(summaryRun wb, map summaryLevel levels, fmap (fmap summaryRun) tree)
1271+
where
1272+
summaryLevel (mmr, rs) =
12601273
let (ongoing, complete) = summaryMR mmr
12611274
in (ongoing, complete <> map summaryRun rs)
1262-
where
1275+
12631276
summaryRun = runSize
1277+
12641278
summaryMR = \case
12651279
Nothing -> ([], [])
12661280
Just (_, _, CompletedMerge r) -> ([], [summaryRun r])
@@ -1297,3 +1311,26 @@ data EventDetail =
12971311
mergeSize :: Int
12981312
}
12991313
deriving stock Show
1314+
1315+
-------------------------------------------------------------------------------
1316+
-- Arbitrary
1317+
--
1318+
1319+
instance QC.Arbitrary Key where
1320+
arbitrary = K <$> QC.arbitrarySizedNatural
1321+
shrink (K v) = K <$> QC.shrink v
1322+
1323+
instance QC.Arbitrary Value where
1324+
arbitrary = V <$> QC.arbitrarySizedNatural
1325+
shrink (V v) = V <$> QC.shrink v
1326+
1327+
instance QC.Arbitrary Blob where
1328+
arbitrary = B <$> QC.arbitrarySizedNatural
1329+
shrink (B v) = B <$> QC.shrink v
1330+
1331+
instance (QC.Arbitrary v, QC.Arbitrary b) => QC.Arbitrary (Update v b) where
1332+
arbitrary = QC.frequency
1333+
[ (3, Insert <$> QC.arbitrary <*> QC.arbitrary)
1334+
, (1, Mupsert <$> QC.arbitrary)
1335+
, (1, pure Delete)
1336+
]

prototypes/ScheduledMergesTest.hs

Lines changed: 50 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,13 +10,17 @@ import Data.STRef
1010

1111
import ScheduledMerges as LSM
1212

13+
import qualified Test.QuickCheck as QC
14+
import Test.QuickCheck (Property)
1315
import Test.Tasty
1416
import Test.Tasty.HUnit (HasCallStack, testCase)
17+
import Test.Tasty.QuickCheck (testProperty, (=/=), (===))
1518

1619
tests :: TestTree
17-
tests = testGroup "Unit tests"
18-
[ testCase "regression_empty_run" test_regression_empty_run
19-
, testCase "merge_again_with_incoming" test_merge_again_with_incoming
20+
tests = testGroup "Unit and property tests"
21+
[ testCase "test_regression_empty_run" test_regression_empty_run
22+
, testCase "test_merge_again_with_incoming" test_merge_again_with_incoming
23+
, testProperty "prop_union" prop_union
2024
]
2125

2226
-- | Results in an empty run on level 2.
@@ -157,6 +161,39 @@ test_merge_again_with_incoming =
157161
, ([16,16,16,20,80], [])
158162
]
159163

164+
-------------------------------------------------------------------------------
165+
-- properties
166+
--
167+
168+
-- | Supplying enough credits for the remaining debt completes the union merge.
169+
prop_union :: [[(LSM.Key, LSM.Op)]] -> Property
170+
prop_union kopss = length (filter (not . null) kopss) > 1 QC.==>
171+
QC.ioProperty $ runWithTracer $ \tr ->
172+
stToIO $ do
173+
ts <- traverse (mkTable tr) kopss
174+
t <- LSM.unions ts
175+
176+
debt <- LSM.remainingUnionDebt t
177+
_ <- LSM.supplyUnionCredits t debt
178+
debt' <- LSM.remainingUnionDebt t
179+
180+
rep <- dumpRepresentation t
181+
return $ QC.counterexample (show (debt, debt')) $ QC.conjoin
182+
[ debt =/= 0
183+
, debt' === 0
184+
, hasUnionWith isCompleted rep
185+
]
186+
where
187+
isCompleted = \case
188+
MLeaf{} -> True
189+
MNode{} -> False
190+
191+
mkTable :: Tracer (ST s) Event -> [(LSM.Key, LSM.Op)] -> ST s (LSM s)
192+
mkTable tr ks = do
193+
t <- LSM.new
194+
LSM.updates tr t ks
195+
return t
196+
160197
-------------------------------------------------------------------------------
161198
-- tracing and expectations on LSM shape
162199
--
@@ -180,10 +217,19 @@ instance Exception TracedException where
180217

181218
expectShape :: HasCallStack => LSM s -> Int -> [([Int], [Int])] -> ST s ()
182219
expectShape lsm expectedWb expectedLevels = do
183-
let expected = ([], [expectedWb]) : expectedLevels
220+
let expected = (expectedWb, expectedLevels, Nothing)
184221
shape <- representationShape <$> dumpRepresentation lsm
185222
when (shape /= expected) $
186223
error $ unlines
187224
[ "expected shape: " <> show expected
188225
, "actual shape: " <> show shape
189226
]
227+
228+
hasUnionWith :: (MTree Int -> Bool) -> Representation -> Property
229+
hasUnionWith p rep = do
230+
let (_, _, shape) = representationShape rep
231+
QC.counterexample "expected suitable Union" $
232+
QC.counterexample (show shape) $
233+
case shape of
234+
Nothing -> False
235+
Just t -> p t

prototypes/ScheduledMergesTestQLS.hs

Lines changed: 0 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,5 @@
11
{-# LANGUAGE TypeFamilies #-}
22

3-
{-# OPTIONS_GHC -Wno-orphans #-}
4-
53
module ScheduledMergesTestQLS (tests) where
64

75
import Control.Monad.ST
@@ -393,19 +391,3 @@ runModel action ctx m =
393391

394392
lookUpKeyVar :: ModelVar Model Key -> Key
395393
lookUpKeyVar var = case lookupVar ctx var of MInsert k -> k
396-
397-
-------------------------------------------------------------------------------
398-
-- Instances
399-
--
400-
401-
instance Arbitrary Key where
402-
arbitrary = K <$> arbitrarySizedNatural
403-
shrink (K v) = K <$> shrink v
404-
405-
instance Arbitrary Value where
406-
arbitrary = V <$> arbitrarySizedNatural
407-
shrink (V v) = V <$> shrink v
408-
409-
instance Arbitrary Blob where
410-
arbitrary = B <$> arbitrarySizedNatural
411-
shrink (B v) = B <$> shrink v

0 commit comments

Comments
 (0)