Skip to content

Commit 8198819

Browse files
recursion-ninjadcoutts
authored andcommitted
Improve Snapshot Arbitrary generator and shrinker
Create less large arbitrary values as well as more quickly shrink to minimal counterexample cases.
1 parent 508d499 commit 8198819

File tree

1 file changed

+76
-44
lines changed
  • test/Test/Database/LSMTree/Internal/Snapshot

1 file changed

+76
-44
lines changed

test/Test/Database/LSMTree/Internal/Snapshot/Codec.hs

Lines changed: 76 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Codec.CBOR.Write
1010
import Control.DeepSeq (NFData)
1111
import qualified Data.ByteString.Lazy as BSL
1212
import Data.Proxy
13+
import qualified Data.Text as Text
1314
import Data.Typeable
1415
import qualified Data.Vector as V
1516
import Database.LSMTree.Extras.Generators ()
@@ -212,7 +213,15 @@ instance Arbitrary SnapshotMetaData where
212213
[ SnapshotMetaData a' b' c' d' e' f'
213214
| (a', b', c', d', e', f') <- shrink (a, b, c, d, e, f)]
214215

215-
deriving newtype instance Arbitrary SnapshotLabel
216+
instance Arbitrary SnapshotLabel where
217+
-- Ensure that the labeling string is not excessively long.
218+
-- If too long, negatively effects the number of shrinks required to reach the
219+
-- minimum example value.
220+
arbitrary = do
221+
prefix <- arbitraryPrintableChar
222+
suffix <- vectorOfUpTo 3 arbitraryPrintableChar
223+
pure . SnapshotLabel . Text.pack $ prefix : suffix
224+
shrink (SnapshotLabel txt) = SnapshotLabel <$> shrink txt
216225

217226
instance Arbitrary SnapshotTableType where
218227
arbitrary = elements [SnapNormalTable, SnapMonoidalTable]
@@ -278,19 +287,20 @@ instance Arbitrary MergeSchedule where
278287
-------------------------------------------------------------------------------}
279288

280289
instance Arbitrary r => Arbitrary (SnapLevels r) where
281-
arbitrary = do
282-
n <- chooseInt (0, 10)
283-
SnapLevels . V.fromList <$> vector n
290+
arbitrary = SnapLevels <$> arbitraryShortVector
284291
shrink (SnapLevels x) = SnapLevels . V.fromList <$> shrink (V.toList x)
285292

286293
instance Arbitrary r => Arbitrary (SnapLevel r) where
287294
arbitrary = SnapLevel <$> arbitrary <*> arbitraryShortVector
288295
shrink (SnapLevel a b) = [SnapLevel a' b' | (a', b') <- shrink (a, b)]
289296

290297
arbitraryShortVector :: Arbitrary a => Gen (V.Vector a)
291-
arbitraryShortVector = do
292-
n <- chooseInt (0, 5)
293-
V.fromList <$> vector n
298+
arbitraryShortVector = V.fromList <$> vectorOfUpTo 5 arbitrary
299+
300+
vectorOfUpTo :: Int -> Gen a -> Gen [a]
301+
vectorOfUpTo maxlen gen = do
302+
len <- chooseInt (0, maxlen)
303+
vectorOf len gen
294304

295305
instance Arbitrary RunNumber where
296306
arbitrary = RunNumber <$> arbitrarySizedNatural
@@ -320,7 +330,7 @@ instance (Arbitrary t, Arbitrary r) => Arbitrary (SnapMergingRun t r) where
320330
arbitrary = oneof [
321331
SnapCompletedMerge <$> arbitrary <*> arbitrary <*> arbitrary
322332
, SnapOngoingMerge <$> arbitrary <*> arbitrary
323-
<*> arbitrary <*> arbitrary
333+
<*> arbitraryShortVector <*> arbitrary
324334
]
325335
shrink (SnapCompletedMerge a b c) =
326336
[ SnapCompletedMerge a' b' c'
@@ -388,17 +398,16 @@ deriving stock instance Show NominalCredits
388398
deriving newtype instance Arbitrary r => Arbitrary (SnapMergingTree r)
389399

390400
instance Arbitrary r => Arbitrary (SnapMergingTreeState r) where
391-
arbitrary = inductiveMergingTreeState inductiveLimit
401+
arbitrary = genMergingTreeState mergingTreeDepthLimit
392402
shrink (SnapCompletedTreeMerge a) = SnapCompletedTreeMerge <$> shrink a
393403
shrink (SnapPendingTreeMerge a) = SnapPendingTreeMerge <$> shrink a
394404
shrink (SnapOngoingTreeMerge a) = SnapOngoingTreeMerge <$> shrink a
395405

396406
instance Arbitrary r => Arbitrary (SnapPendingMerge r) where
397-
arbitrary = inductivePendingTreeMerge inductiveLimit
407+
arbitrary = genPendingTreeMerge mergingTreeDepthLimit
398408
shrink (SnapPendingUnionMerge a) = SnapPendingUnionMerge <$> shrinkList shrink a
399409
shrink (SnapPendingLevelMerge a b) =
400-
[ SnapPendingLevelMerge a' b' | a' <- shrinkList shrink a, b' <- shrink b ]
401-
410+
[ SnapPendingLevelMerge a' b' | (a', b') <- shrink (a, b)]
402411

403412
instance Arbitrary r => Arbitrary (SnapPreExistingRun r) where
404413
arbitrary = oneof [
@@ -414,35 +423,58 @@ instance Arbitrary r => Arbitrary (SnapPreExistingRun r) where
414423
-- At reach recursive call, the "gas" value decremented until it reaches zero.
415424
-- Each inductive function ensures it never create a forest of sub-trees greater
416425
-- than the /monotonically decreasing/ gas parameter it received.
417-
inductiveLimit :: Int
418-
inductiveLimit = 4
419-
420-
-- |
421-
-- Generate an 'Arbitrary', "gas-limited" 'SnapMergingTree'.
422-
inductiveSized :: Arbitrary r => Int -> Gen (SnapMergingTree r)
423-
inductiveSized = fmap SnapMergingTree . inductiveMergingTreeState
424-
425-
-- |
426-
-- Generate an 'Arbitrary', "gas-limited" 'SnapMergingTreeState'.
427-
inductiveMergingTreeState :: Arbitrary a => Int -> Gen (SnapMergingTreeState a)
428-
inductiveMergingTreeState gas = oneof [
429-
SnapCompletedTreeMerge <$> arbitrary
430-
, SnapPendingTreeMerge <$> inductivePendingTreeMerge gas
431-
, SnapOngoingTreeMerge <$> arbitrary
432-
]
433-
434-
-- |
435-
-- Generate an 'Arbitrary', "gas-limited" 'SnapPendingMerge'.
436-
inductivePendingTreeMerge :: Arbitrary a => Int -> Gen (SnapPendingMerge a)
437-
inductivePendingTreeMerge gas = oneof [
438-
SnapPendingLevelMerge <$> genPreExistings <*> genMaybeSubTree
439-
, SnapPendingUnionMerge <$> genListSubtrees
440-
]
441-
where
442-
subGen = inductiveSized . max 0 $ gas - 1
443-
-- Define custom generators to ensure that the sub-trees are less than
444-
-- or equal to the "gas" parameter.
445-
genPreExistings = genVectorsUpToBound gas arbitrary
446-
genListSubtrees = genVectorsUpToBound gas subGen
447-
genMaybeSubTree = oneof [ pure Nothing, Just <$> subGen ]
448-
genVectorsUpToBound x gen = oneof $ flip vectorOf gen <$> [ 0 .. x ]
426+
mergingTreeDepthLimit :: Int
427+
mergingTreeDepthLimit = 4
428+
429+
-- | Do not generate a number of direct child sub-trees greater than the this
430+
-- branching limit. This simplifies the topology of trees generated
431+
branchingLimit :: Int
432+
branchingLimit = 3
433+
434+
-- | Generate an 'Arbitrary', "gas-limited" 'SnapMergingTreeState~'.
435+
genMergingTreeState :: Arbitrary a => Int -> Gen (SnapMergingTreeState a)
436+
genMergingTreeState gas =
437+
let perpetualCase = [
438+
SnapCompletedTreeMerge <$> arbitrary
439+
, SnapOngoingTreeMerge <$> arbitrary
440+
]
441+
recursiveCase
442+
| gas == 0 = []
443+
| otherwise = [ SnapPendingTreeMerge <$> genPendingTreeMerge gas ]
444+
in oneof $ perpetualCase <> recursiveCase
445+
446+
-- | Generate an 'Arbitrary', "gas-limited" 'SnapPendingMerge'.
447+
genPendingTreeMerge :: Arbitrary a => Int -> Gen (SnapPendingMerge a)
448+
genPendingTreeMerge gas =
449+
oneof [
450+
SnapPendingLevelMerge <$> genPreExistings <*> genMaybeSubTree
451+
, SnapPendingUnionMerge <$> genListSubtrees
452+
]
453+
where
454+
-- Decrement the gas for the recursive calls
455+
nextGas = max 0 $ gas - 1
456+
subGen = SnapMergingTree <$> genMergingTreeState nextGas
457+
458+
-- No recursive subtrees within here, so not constrained by gas.
459+
genPreExistings = vectorOfUpTo branchingLimit arbitrary
460+
461+
-- Define custom generators to ensure that the sub-trees are less than
462+
-- or equal to the lesser of the "gas" parameter and the branching limit.
463+
genMaybeSubTree
464+
| gas == 0 = pure Nothing
465+
| otherwise = oneof [ pure Nothing, Just <$> subGen ]
466+
467+
genListSubtrees = case gas of
468+
0 -> vectorOf 0 subGen
469+
_ ->
470+
-- This frequency distribution will uniformly at random select an
471+
-- n-ary tree topology with a specified branching factor.
472+
let recursiveOptions branching = \case
473+
0 -> 1
474+
depth ->
475+
let sub = recursiveOptions branching $ depth - 1
476+
in sum $ (sub ^) <$> [ 0 .. branching ]
477+
probability e =
478+
let basis = recursiveOptions branchingLimit nextGas
479+
in (basis ^ e, vectorOf e subGen)
480+
in frequency $ probability <$> [ 0 .. branchingLimit ]

0 commit comments

Comments
 (0)