Skip to content

Commit ded9fc5

Browse files
committed
Add tests for min/max bounds on (un)spent credits
And check max run size (2^40-1, or about 1 trillion)
1 parent 64d0a31 commit ded9fc5

File tree

4 files changed

+76
-4
lines changed

4 files changed

+76
-4
lines changed

lsm-tree.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -366,6 +366,7 @@ test-suite lsm-tree-test
366366
Test.Database.LSMTree.Internal.Index.Ordinary
367367
Test.Database.LSMTree.Internal.Lookup
368368
Test.Database.LSMTree.Internal.Merge
369+
Test.Database.LSMTree.Internal.MergingRun
369370
Test.Database.LSMTree.Internal.MergingTree
370371
Test.Database.LSMTree.Internal.Monkey
371372
Test.Database.LSMTree.Internal.PageAcc

src/Database/LSMTree/Internal/MergingRun.hs

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,8 @@ module Database.LSMTree.Internal.MergingRun (
2323
, Credits (..)
2424
, CreditThreshold (..)
2525
, SuppliedCredits (..)
26+
, SpentCredits (..)
27+
, UnspentCredits (..)
2628

2729
-- * Concurrency
2830
-- $concurrency
@@ -32,16 +34,18 @@ module Database.LSMTree.Internal.MergingRun (
3234
, MergingRunState (..)
3335
, MergeKnownCompleted (..)
3436
, CreditsVar (..)
37+
, pattern CreditsPair
3538
) where
3639

3740
import Control.ActionRegistry
3841
import Control.Concurrent.Class.MonadMVar.Strict
3942
import Control.DeepSeq (NFData (..))
43+
import Control.Exception (ErrorCall (..))
4044
import Control.Monad (when)
4145
import Control.Monad.Class.MonadST (MonadST)
4246
import Control.Monad.Class.MonadSTM (MonadSTM (..))
4347
import Control.Monad.Class.MonadThrow (MonadCatch (bracketOnError),
44-
MonadMask)
48+
MonadMask, MonadThrow (throwIO))
4549
import Control.Monad.Primitive
4650
import Control.RefCount
4751
import Data.Bits
@@ -183,6 +187,10 @@ unsafeNew ::
183187
-> MergeKnownCompleted
184188
-> MergingRunState m h
185189
-> m (Ref (MergingRun m h))
190+
unsafeNew _ mergeNumEntries _ _
191+
| SpentCredits (numEntriesToTotalDebt mergeNumEntries) > maxBound
192+
= throwIO (ErrorCall "MergingRun.new: run size exceeds maximum of 2^40")
193+
186194
unsafeNew mergeNumRuns mergeNumEntries knownCompleted state = do
187195
mergeCreditsVar <- CreditsVar <$> newPrimVar 0
188196
case state of
@@ -340,6 +348,7 @@ newtype SuppliedCredits = SuppliedCredits Credits
340348
-- spent (by some thread calling 'supplyCredits').
341349
--
342350
newtype SpentCredits = SpentCredits Credits
351+
deriving newtype (Eq, Ord)
343352

344353
-- | 40 bit unsigned number
345354
instance Bounded SpentCredits where
@@ -355,6 +364,7 @@ instance Bounded SpentCredits where
355364
-- current unspent credits being negative for a time.
356365
--
357366
newtype UnspentCredits = UnspentCredits Credits
367+
deriving newtype (Eq, Ord)
358368

359369
-- | 24 bit signed number
360370
instance Bounded UnspentCredits where
@@ -386,11 +396,13 @@ pattern CreditsPair sc uc <- (unpackCreditsPair -> (sc, uc))
386396
#endif
387397
{-# COMPLETE CreditsPair #-}
388398

389-
-- TODO: test pack/unpack round trip with the minBound & maxBounds
390-
391399
{-# INLINE packCreditsPair #-}
392400
packCreditsPair :: SpentCredits -> UnspentCredits -> Int
393-
packCreditsPair (SpentCredits (Credits sc)) (UnspentCredits (Credits uc)) =
401+
packCreditsPair spent@(SpentCredits (Credits sc))
402+
unspent@(UnspentCredits (Credits uc)) =
403+
assert (spent >= minBound && spent <= maxBound) $
404+
assert (unspent >= minBound && unspent <= maxBound) $
405+
394406
sc `unsafeShiftL` 24
395407
.|. (uc .&. 0xffffff)
396408

test/Main.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import qualified Test.Database.LSMTree.Internal.Index.Compact
1717
import qualified Test.Database.LSMTree.Internal.Index.Ordinary
1818
import qualified Test.Database.LSMTree.Internal.Lookup
1919
import qualified Test.Database.LSMTree.Internal.Merge
20+
import qualified Test.Database.LSMTree.Internal.MergingRun
2021
import qualified Test.Database.LSMTree.Internal.MergingTree
2122
import qualified Test.Database.LSMTree.Internal.Monkey
2223
import qualified Test.Database.LSMTree.Internal.PageAcc
@@ -59,6 +60,7 @@ main = do
5960
, Test.Database.LSMTree.Internal.Entry.tests
6061
, Test.Database.LSMTree.Internal.Lookup.tests
6162
, Test.Database.LSMTree.Internal.Merge.tests
63+
, Test.Database.LSMTree.Internal.MergingRun.tests
6264
, Test.Database.LSMTree.Internal.MergingTree.tests
6365
, Test.Database.LSMTree.Internal.Monkey.tests
6466
, Test.Database.LSMTree.Internal.PageAcc.tests
Lines changed: 57 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
{-# OPTIONS_GHC -Wno-orphans #-}
2+
3+
module Test.Database.LSMTree.Internal.MergingRun (tests) where
4+
5+
import Database.LSMTree.Internal.MergingRun
6+
import Test.QuickCheck
7+
import Test.Tasty
8+
import Test.Tasty.QuickCheck
9+
10+
tests :: TestTree
11+
tests = testGroup "Test.Database.LSMTree.Internal.MergingRun"
12+
[ testProperty "prop_CreditsPair" prop_CreditsPair
13+
]
14+
15+
-- | The representation of CreditsPair should round trip properly. This is
16+
-- non-trivial because it uses a packed bit the representation.
17+
--
18+
prop_CreditsPair :: SpentCredits -> UnspentCredits -> Property
19+
prop_CreditsPair spentCredits unspentCredits =
20+
tabulate "bounds" [spentCreditsBound, unspentCreditsBound] $
21+
let cp :: Int
22+
!cp = CreditsPair spentCredits unspentCredits
23+
in case cp of
24+
CreditsPair spentCredits' unspentCredits' ->
25+
(spentCredits, unspentCredits) === (spentCredits', unspentCredits')
26+
where
27+
spentCreditsBound
28+
| spentCredits == minBound = "spentCredits == minBound"
29+
| spentCredits == maxBound = "spentCredits == maxBound"
30+
| otherwise = "spentCredits == other"
31+
32+
unspentCreditsBound
33+
| unspentCredits == minBound = "unspentCredits == minBound"
34+
| unspentCredits == maxBound = "unspentCredits == maxBound"
35+
| otherwise = "unspentCredits == other"
36+
37+
deriving newtype instance Enum SpentCredits
38+
deriving newtype instance Enum UnspentCredits
39+
40+
deriving stock instance Show Credits
41+
deriving stock instance Show SpentCredits
42+
deriving stock instance Show UnspentCredits
43+
44+
instance Arbitrary SpentCredits where
45+
arbitrary =
46+
frequency [ (1, pure minBound)
47+
, (1, pure maxBound)
48+
, (10, arbitraryBoundedEnum)
49+
]
50+
51+
instance Arbitrary UnspentCredits where
52+
arbitrary =
53+
frequency [ (1, pure minBound)
54+
, (1, pure maxBound)
55+
, (10, arbitraryBoundedEnum)
56+
]
57+

0 commit comments

Comments
 (0)