Skip to content

Commit 96c9eab

Browse files
committed
ScheduledMerges: more trace messages
These messages helped with troubleshooting #755
1 parent 6cad45a commit 96c9eab

File tree

4 files changed

+145
-78
lines changed

4 files changed

+145
-78
lines changed

lsm-tree.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1147,6 +1147,7 @@ library prototypes
11471147
, bytestring
11481148
, containers
11491149
, contra-tracer
1150+
, primitive
11501151
, QuickCheck
11511152
, transformers
11521153

@@ -1168,6 +1169,8 @@ test-suite prototypes-test
11681169
, containers
11691170
, contra-tracer
11701171
, lsm-tree:prototypes
1172+
, mtl
1173+
, primitive
11711174
, QuickCheck
11721175
, quickcheck-dynamic
11731176
, quickcheck-lockstep

src-prototypes/ScheduledMerges.hs

Lines changed: 99 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@
2727
module ScheduledMerges (
2828
-- * Main API
2929
LSM,
30+
TableId (..),
3031
LSMConfig (..),
3132
Key (K), Value (V), resolveValue, Blob (B),
3233
new,
@@ -100,25 +101,35 @@ module ScheduledMerges (
100101
import Prelude hiding (lookup)
101102

102103
import Data.Foldable (for_, toList, traverse_)
104+
import Data.Functor.Contravariant
103105
import Data.Map.Strict (Map)
104106
import qualified Data.Map.Strict as Map
105107
import Data.Maybe (catMaybes)
108+
import Data.Primitive.Types
106109
import Data.STRef
107110

108111
import qualified Control.Exception as Exc (assert)
109112
import Control.Monad (foldM, forM, when)
110113
import Control.Monad.ST
111114
import qualified Control.Monad.Trans.Except as E
112-
import Control.Tracer (Tracer, contramap, traceWith)
115+
import Control.Tracer
113116
import GHC.Stack (HasCallStack, callStack)
114117

115118
import Text.Printf (printf)
116119

117120
import qualified Test.QuickCheck as QC
118121

119-
data LSM s = LSMHandle !(STRef s Counter)
120-
!LSMConfig
121-
!(STRef s (LSMContent s))
122+
data LSM s = LSMHandle {
123+
tableId :: !TableId
124+
, _tableCounter :: !(STRef s Counter)
125+
, _tableConfig :: !LSMConfig
126+
, _tableContents :: !(STRef s (LSMContent s))
127+
}
128+
129+
-- | Identifiers for 'LSM' tables
130+
newtype TableId = TableId Int
131+
deriving stock (Show, Eq, Ord)
132+
deriving newtype (Enum, Prim)
122133

123134
-- | Configuration options for individual LSM tables.
124135
data LSMConfig = LSMConfig {
@@ -960,8 +971,8 @@ suppliedCreditMergingRun (MergingRun _ d ref) =
960971
-- LSM handle
961972
--
962973

963-
new :: ST s (LSM s)
964-
new = newWith conf
974+
new :: Tracer (ST s) Event -> TableId -> ST s (LSM s)
975+
new tr tid = newWith tr tid conf
965976
where
966977
-- 4 was the default for both the max write buffer size and size ratio
967978
-- before they were made configurable
@@ -970,16 +981,17 @@ new = newWith conf
970981
, configSizeRatio = 4
971982
}
972983

973-
newWith :: LSMConfig -> ST s (LSM s)
974-
newWith conf
984+
newWith :: Tracer (ST s) Event -> TableId -> LSMConfig -> ST s (LSM s)
985+
newWith tr tid conf
975986
| configMaxWriteBufferSize conf <= 0 =
976987
error "newWith: configMaxWriteBufferSize should be positive"
977988
| configSizeRatio conf <= 1 =
978989
error "newWith: configSizeRatio should be larger than 1"
979990
| otherwise = do
991+
traceWith tr $ NewTableEvent tid conf
980992
c <- newSTRef 0
981993
lsm <- newSTRef (LSMContent Map.empty [] NoUnion)
982-
pure (LSMHandle c conf lsm)
994+
pure (LSMHandle tid c conf lsm)
983995

984996
inserts :: Tracer (ST s) Event -> LSM s -> [(Key, Value, Maybe Blob)] -> ST s ()
985997
inserts tr lsm kvbs = updates tr lsm [ (k, Insert v b) | (k, v, b) <- kvbs ]
@@ -1009,7 +1021,8 @@ updates :: Tracer (ST s) Event -> LSM s -> [(Key, Entry)] -> ST s ()
10091021
updates tr lsm = mapM_ (uncurry (update tr lsm))
10101022

10111023
update :: Tracer (ST s) Event -> LSM s -> Key -> Entry -> ST s ()
1012-
update tr (LSMHandle scr conf lsmr) k entry = do
1024+
update tr (LSMHandle tid scr conf lsmr) k entry = do
1025+
traceWith tr $ UpdateEvent tid k entry
10131026
sc <- readSTRef scr
10141027
content@(LSMContent wb ls unionLevel) <- readSTRef lsmr
10151028
modifySTRef' scr (+1)
@@ -1018,15 +1031,15 @@ update tr (LSMHandle scr conf lsmr) k entry = do
10181031
let wb' = Map.insertWith combine k entry wb
10191032
if bufferSize wb' >= maxWriteBufferSize conf
10201033
then do
1021-
ls' <- increment tr sc conf (bufferToRun wb') ls unionLevel
1034+
ls' <- increment (LevelEvent tid >$< tr) sc conf (bufferToRun wb') ls unionLevel
10221035
let content' = LSMContent Map.empty ls' unionLevel
10231036
invariant conf content'
10241037
writeSTRef lsmr content'
10251038
else
10261039
writeSTRef lsmr (LSMContent wb' ls unionLevel)
10271040

10281041
supplyMergeCredits :: LSM s -> NominalCredit -> ST s ()
1029-
supplyMergeCredits (LSMHandle scr conf lsmr) credits = do
1042+
supplyMergeCredits (LSMHandle _ scr conf lsmr) credits = do
10301043
content@(LSMContent _ ls _) <- readSTRef lsmr
10311044
modifySTRef' scr (+1)
10321045
supplyCreditsLevels credits ls
@@ -1038,22 +1051,24 @@ data LookupResult v b =
10381051
deriving stock (Eq, Show)
10391052

10401053
lookups :: LSM s -> [Key] -> ST s [LookupResult Value Blob]
1041-
lookups (LSMHandle _ _conf lsmr) ks = do
1054+
lookups (LSMHandle _ _ _conf lsmr) ks = do
10421055
LSMContent wb ls ul <- readSTRef lsmr
10431056
runs <- concat <$> flattenLevels ls
10441057
traverse (doLookup wb runs ul) ks
10451058

1046-
lookup :: LSM s -> Key -> ST s (LookupResult Value Blob)
1047-
lookup (LSMHandle _ _conf lsmr) k = do
1059+
lookup :: Tracer (ST s) Event -> LSM s -> Key -> ST s (LookupResult Value Blob)
1060+
lookup tr (LSMHandle tid _ _conf lsmr) k = do
1061+
traceWith tr $ LookupEvent tid k
10481062
LSMContent wb ls ul <- readSTRef lsmr
10491063
runs <- concat <$> flattenLevels ls
10501064
doLookup wb runs ul k
10511065

1052-
duplicate :: LSM s -> ST s (LSM s)
1053-
duplicate (LSMHandle _scr conf lsmr) = do
1066+
duplicate :: Tracer (ST s) Event -> TableId -> LSM s -> ST s (LSM s)
1067+
duplicate tr childTid (LSMHandle parentTid _scr conf lsmr) = do
1068+
traceWith tr $ DuplicateEvent childTid parentTid
10541069
scr' <- newSTRef 0
10551070
lsmr' <- newSTRef =<< readSTRef lsmr
1056-
pure (LSMHandle scr' conf lsmr')
1071+
pure (LSMHandle childTid scr' conf lsmr')
10571072
-- it's that simple here, because we share all the pure value and all the
10581073
-- STRefs and there's no ref counting to be done
10591074

@@ -1064,9 +1079,12 @@ duplicate (LSMHandle _scr conf lsmr) = do
10641079
-- merge that can be performed incrementally (somewhat similar to a thunk).
10651080
--
10661081
-- The more merge work remains, the more expensive are lookups on the table.
1067-
unions :: [LSM s] -> ST s (LSM s)
1068-
unions lsms = do
1069-
(confs, trees) <- fmap unzip $ forM lsms $ \(LSMHandle _ conf lsmr) ->
1082+
unions :: Tracer (ST s) Event -> TableId -> [LSM s] -> ST s (LSM s)
1083+
unions tr childTid lsms = do
1084+
traceWith tr $
1085+
let parentTids = fmap tableId lsms
1086+
in UnionsEvent childTid parentTids
1087+
(confs, trees) <- fmap unzip $ forM lsms $ \(LSMHandle _ _ conf lsmr) ->
10701088
(conf,) <$> (contentToMergingTree =<< readSTRef lsmr)
10711089
-- Check that the configurations are equal
10721090
conf <- case confs of
@@ -1081,7 +1099,7 @@ unions lsms = do
10811099
Union tree <$> newSTRef debt
10821100
lsmr <- newSTRef (LSMContent Map.empty [] unionLevel)
10831101
c <- newSTRef 0
1084-
pure (LSMHandle c conf lsmr)
1102+
pure (LSMHandle childTid c conf lsmr)
10851103

10861104
-- | The /current/ upper bound on the number of 'UnionCredits' that have to be
10871105
-- supplied before a 'union' is completed.
@@ -1097,7 +1115,7 @@ newtype UnionDebt = UnionDebt Debt
10971115
-- | Return the current union debt. This debt can be reduced until it is paid
10981116
-- off using 'supplyUnionCredits'.
10991117
remainingUnionDebt :: LSM s -> ST s UnionDebt
1100-
remainingUnionDebt (LSMHandle _ _conf lsmr) = do
1118+
remainingUnionDebt (LSMHandle _ _ _conf lsmr) = do
11011119
LSMContent _ _ ul <- readSTRef lsmr
11021120
UnionDebt <$> case ul of
11031121
NoUnion -> pure 0
@@ -1123,7 +1141,7 @@ newtype UnionCredits = UnionCredits Credit
11231141
-- a union has finished. In particular, if the returned number of credits is
11241142
-- non-negative, then the union is finished.
11251143
supplyUnionCredits :: LSM s -> UnionCredits -> ST s UnionCredits
1126-
supplyUnionCredits (LSMHandle scr conf lsmr) (UnionCredits credits)
1144+
supplyUnionCredits (LSMHandle _ scr conf lsmr) (UnionCredits credits)
11271145
| credits <= 0 = pure (UnionCredits 0)
11281146
| otherwise = do
11291147
content@(LSMContent _ _ ul) <- readSTRef lsmr
@@ -1399,7 +1417,7 @@ depositNominalCredit (NominalDebt nominalDebt)
13991417
-- Updates
14001418
--
14011419

1402-
increment :: forall s. Tracer (ST s) Event
1420+
increment :: forall s. Tracer (ST s) (EventAt EventDetail)
14031421
-> Counter
14041422
-> LSMConfig
14051423
-> Run -> Levels s -> UnionLevel s -> ST s (Levels s)
@@ -1411,19 +1429,21 @@ increment tr sc conf run0 ls0 ul = do
14111429

14121430
go :: Int -> [Run] -> Levels s -> ST s (Levels s)
14131431
go !ln incoming [] = do
1414-
let mergePolicy = mergePolicyForLevel ln [] ul
14151432
traceWith tr' AddLevelEvent
1433+
let mergePolicy = mergePolicyForLevel ln [] ul
14161434
ir <- newLevelMerge tr' conf ln mergePolicy (mergeTypeFor []) incoming
14171435
pure (Level ir [] : [])
14181436
where
14191437
tr' = contramap (EventAt sc ln) tr
14201438

14211439
go !ln incoming (Level ir rs : ls) = do
14221440
r <- case ir of
1423-
Single r -> pure r
1441+
Single r -> do
1442+
traceWith tr' $ SingleRunCompletedEvent r
1443+
pure r
14241444
Merging mergePolicy _ _ mr -> do
14251445
r <- expectCompletedMergingRun mr
1426-
traceWith tr' MergeCompletedEvent {
1446+
traceWith tr' LevelMergeCompletedEvent {
14271447
mergePolicy,
14281448
mergeType = let MergingRun mt _ _ = mr in mt,
14291449
mergeSize = runSize r
@@ -1436,6 +1456,8 @@ increment tr sc conf run0 ls0 ul = do
14361456
-- If r is still too small for this level then keep it and merge again
14371457
-- with the incoming runs.
14381458
LevelTiering | runTooSmallForLevel LevelTiering conf ln r -> do
1459+
traceWith tr' $ RunTooSmallForLevelEvent LevelTiering ln r
1460+
14391461
ir' <- newLevelMerge tr' conf ln LevelTiering (mergeTypeFor ls) (incoming ++ [r])
14401462
pure (Level ir' rs : ls)
14411463

@@ -1444,29 +1466,37 @@ increment tr sc conf run0 ls0 ul = do
14441466
-- as a bundle and move them down to the level below. We start a merge
14451467
-- for the new incoming runs. This level is otherwise empty.
14461468
LevelTiering | levelIsFullTiering conf ln incoming resident -> do
1469+
traceWith tr' $ LevelIsFullEvent LevelTiering
1470+
14471471
ir' <- newLevelMerge tr' conf ln LevelTiering MergeMidLevel incoming
14481472
ls' <- go (ln+1) resident ls
14491473
pure (Level ir' [] : ls')
14501474

14511475
-- This tiering level is not yet full. We move the completed merged run
14521476
-- into the level proper, and start the new merge for the incoming runs.
14531477
LevelTiering -> do
1478+
traceWith tr' $ LevelIsNotFullEvent LevelTiering
1479+
14541480
ir' <- newLevelMerge tr' conf ln LevelTiering (mergeTypeFor ls) incoming
1455-
traceWith tr' (AddRunEvent (length resident))
1481+
traceWith tr' (AddRunEvent resident)
14561482
pure (Level ir' resident : ls)
14571483

14581484
-- The final level is using levelling. If the existing completed merge
14591485
-- run is too large for this level, we promote the run to the next
14601486
-- level and start merging the incoming runs into this (otherwise
14611487
-- empty) level .
14621488
LevelLevelling | levelIsFullLevelling conf ln incoming r -> do
1489+
traceWith tr' $ LevelIsFullEvent LevelLevelling
1490+
14631491
assert (null rs && null ls) $ pure ()
14641492
ir' <- newLevelMerge tr' conf ln LevelTiering MergeMidLevel incoming
14651493
ls' <- go (ln+1) [r] []
14661494
pure (Level ir' [] : ls')
14671495

14681496
-- Otherwise we start merging the incoming runs into the run.
14691497
LevelLevelling -> do
1498+
traceWith tr' $ LevelIsNotFullEvent LevelLevelling
1499+
14701500
assert (null rs && null ls) $ pure ()
14711501
ir' <- newLevelMerge tr' conf ln LevelLevelling (mergeTypeFor ls)
14721502
(incoming ++ [r])
@@ -1479,17 +1509,19 @@ newLevelMerge :: Tracer (ST s) EventDetail
14791509
-> LSMConfig
14801510
-> Int -> MergePolicyForLevel -> LevelMergeType
14811511
-> [Run] -> ST s (IncomingRun s)
1482-
newLevelMerge _ _ _ _ _ [r] = pure (Single r)
1512+
newLevelMerge tr _ _ _ _ [r] = do
1513+
traceWith tr $ NewSingleRunEvent r
1514+
pure (Single r)
14831515
newLevelMerge tr conf@LSMConfig{..} level mergePolicy mergeType rs = do
1484-
assertST (length rs `elem` [configSizeRatio, configSizeRatio + 1])
14851516
mergingRun@(MergingRun _ physicalDebt _) <- newMergingRun mergeType rs
1486-
assertWithMsgM $ leq (totalDebt physicalDebt) maxPhysicalDebt
1487-
traceWith tr MergeStartedEvent {
1517+
traceWith tr NewLevelMergeEvent {
14881518
mergePolicy,
14891519
mergeType,
1490-
mergeDebt = totalDebt physicalDebt,
1491-
mergeRunsSize = map runSize rs
1520+
mergeDebt = totalDebt physicalDebt,
1521+
mergeRuns = rs
14921522
}
1523+
assertST (length rs `elem` [configSizeRatio, configSizeRatio + 1])
1524+
assertWithMsgM $ leq (totalDebt physicalDebt) maxPhysicalDebt
14931525
nominalCreditVar <- newSTRef (NominalCredit 0)
14941526
pure (Merging mergePolicy nominalDebt nominalCreditVar mergingRun)
14951527
where
@@ -1766,7 +1798,7 @@ data MTree r = MLeaf r
17661798
deriving stock (Eq, Foldable, Functor, Show)
17671799

17681800
allLevels :: LSM s -> ST s (Buffer, [[Run]], Maybe (MTree Run))
1769-
allLevels (LSMHandle _ _conf lsmr) = do
1801+
allLevels (LSMHandle _ _ _conf lsmr) = do
17701802
LSMContent wb ls ul <- readSTRef lsmr
17711803
rs <- flattenLevels ls
17721804
tree <- case ul of
@@ -1836,7 +1868,7 @@ type LevelRepresentation =
18361868
[Run])
18371869

18381870
dumpRepresentation :: LSM s -> ST s Representation
1839-
dumpRepresentation (LSMHandle _ _conf lsmr) = do
1871+
dumpRepresentation (LSMHandle _ _ _conf lsmr) = do
18401872
LSMContent wb ls ul <- readSTRef lsmr
18411873
levels <- mapM dumpLevel ls
18421874
tree <- case ul of
@@ -1877,7 +1909,15 @@ representationShape (wb, levels, tree) =
18771909

18781910
-- TODO: these events are incomplete, in particular we should also trace what
18791911
-- happens in the union level.
1880-
type Event = EventAt EventDetail
1912+
data Event =
1913+
NewTableEvent TableId LSMConfig
1914+
| UpdateEvent TableId Key Entry
1915+
| LookupEvent TableId Key
1916+
| DuplicateEvent TableId TableId
1917+
| UnionsEvent TableId [TableId]
1918+
| LevelEvent TableId (EventAt EventDetail)
1919+
deriving stock Show
1920+
18811921
data EventAt e = EventAt {
18821922
eventAtStep :: Counter,
18831923
eventAtLevel :: Int,
@@ -1886,21 +1926,27 @@ data EventAt e = EventAt {
18861926
deriving stock Show
18871927

18881928
data EventDetail =
1889-
AddLevelEvent
1890-
| AddRunEvent {
1891-
runsAtLevel :: Int
1892-
}
1893-
| MergeStartedEvent {
1894-
mergePolicy :: MergePolicyForLevel,
1895-
mergeType :: LevelMergeType,
1896-
mergeDebt :: Debt,
1897-
mergeRunsSize :: [Int]
1898-
}
1899-
| MergeCompletedEvent {
1900-
mergePolicy :: MergePolicyForLevel,
1901-
mergeType :: LevelMergeType,
1902-
mergeSize :: Int
1903-
}
1929+
AddLevelEvent
1930+
| AddRunEvent {
1931+
runsAtLevel :: [Run]
1932+
}
1933+
| NewLevelMergeEvent {
1934+
mergePolicy :: MergePolicyForLevel,
1935+
mergeType :: LevelMergeType,
1936+
mergeDebt :: Debt,
1937+
mergeRuns :: [Run]
1938+
}
1939+
| NewSingleRunEvent Run
1940+
| LevelMergeCompletedEvent {
1941+
mergePolicy :: MergePolicyForLevel,
1942+
mergeType :: LevelMergeType,
1943+
mergeSize :: Int
1944+
}
1945+
| SingleRunCompletedEvent Run
1946+
1947+
| RunTooSmallForLevelEvent MergePolicyForLevel Int Run
1948+
| LevelIsFullEvent MergePolicyForLevel
1949+
| LevelIsNotFullEvent MergePolicyForLevel
19041950
deriving stock Show
19051951

19061952
-------------------------------------------------------------------------------

0 commit comments

Comments
 (0)