Skip to content

Commit 6876398

Browse files
committed
Rename table merge to table union in the public API
"Table union" seems to be more appropriate than "table merge", since "merge" is often used in the LSM-Tree literature to mean "run merges". The table union semantics are also similar to `Map.union` from the well known `Data.Map` module, so just from the name it should be more obvious at a glance what the semantics of "table union" are. The semantics of table union are made a little more specific in the haddocks.
1 parent 637fec5 commit 6876398

File tree

7 files changed

+44
-41
lines changed

7 files changed

+44
-41
lines changed

src/Database/LSMTree/Monoidal.hs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -100,8 +100,8 @@ module Database.LSMTree.Monoidal (
100100
-- * Persistence
101101
, duplicate
102102

103-
-- * Merging tables
104-
, merge
103+
-- * Table union
104+
, union
105105

106106
-- * Concurrency
107107
-- $concurrency
@@ -652,30 +652,33 @@ duplicate :: forall m k v.
652652
duplicate (Internal.MonoidalTable t) = Internal.MonoidalTable <$> Internal.duplicate t
653653

654654
{-------------------------------------------------------------------------------
655-
Merging tables
655+
Table union
656656
-------------------------------------------------------------------------------}
657657

658-
{-# SPECIALISE merge ::
658+
{-# SPECIALISE union ::
659659
ResolveValue v
660660
=> Table IO k v
661661
-> Table IO k v
662662
-> IO (Table IO k v) #-}
663-
-- | Merge full tables, creating a new table.
663+
-- | Union two full tables, creating a new table.
664+
--
665+
-- A good mental model of this operation is @'Data.Map.unionWith' (<>)@ on
666+
-- @'Data.Map.Map' k v@.
664667
--
665668
-- Multiple tables of the same type but with different configuration parameters
666-
-- can live in the same session. However, 'merge' only works for tables that
669+
-- can live in the same session. However, 'union' only works for tables that
667670
-- have the same key\/value types and configuration parameters.
668671
--
669-
-- NOTE: merging tables creates a new table, but does not close
670-
-- the tables that were used as inputs.
671-
merge :: forall m k v.
672+
-- NOTE: unioning tables creates a new table, but does not close the tables that
673+
-- were used as inputs.
674+
union :: forall m k v.
672675
( IOLike m
673676
, ResolveValue v
674677
)
675678
=> Table m k v
676679
-> Table m k v
677680
-> m (Table m k v)
678-
merge = undefined
681+
union = undefined
679682

680683
{-------------------------------------------------------------------------------
681684
Monoidal value resolution

test/Database/LSMTree/Class/Monoidal.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module Database.LSMTree.Class.Monoidal (
1212
, withTableNew
1313
, withTableOpen
1414
, withTableDuplicate
15-
, withTableMerge
15+
, withTableUnion
1616
, withCursor
1717
, module Types
1818
) where
@@ -183,7 +183,7 @@ class (IsSession (Session h)) => IsTable h where
183183
=> h m k v
184184
-> m (h m k v)
185185

186-
merge ::
186+
union ::
187187
( IOLike m
188188
, ResolveValue v
189189
, SerialiseValue v
@@ -229,7 +229,7 @@ withTableDuplicate :: forall h m k v a.
229229
-> m a
230230
withTableDuplicate table = bracket (duplicate table) close
231231

232-
withTableMerge :: forall h m k v a.
232+
withTableUnion :: forall h m k v a.
233233
( IOLike m
234234
, IsTable h
235235
, SerialiseValue v
@@ -240,7 +240,7 @@ withTableMerge :: forall h m k v a.
240240
-> h m k v
241241
-> (h m k v -> m a)
242242
-> m a
243-
withTableMerge table1 table2 = bracket (merge table1 table2) close
243+
withTableUnion table1 table2 = bracket (table1 `union` table2) close
244244

245245
withCursor :: forall h m k v a.
246246
( IOLike m
@@ -281,4 +281,4 @@ instance IsTable R.Table where
281281
open sesh snap = R.open sesh R.configNoOverride snap
282282

283283
duplicate = R.duplicate
284-
merge = R.merge
284+
union = R.union

test/Database/LSMTree/Model/IO/Monoidal.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -72,8 +72,8 @@ instance Class.IsTable Table where
7272

7373
duplicate (Table s t) = Table s <$> runInOpenSession s (Model.duplicate t)
7474

75-
merge (Table s1 t1) (Table _s2 t2) =
76-
Table s1 <$> runInOpenSession s1 (Model.merge Model.getResolve t1 t2)
75+
union (Table s1 t1) (Table _s2 t2) =
76+
Table s1 <$> runInOpenSession s1 (Model.union Model.getResolve t1 t2)
7777

7878
convLookupResult :: Model.LookupResult v b -> Class.LookupResult v
7979
convLookupResult = \case

test/Database/LSMTree/Model/Session.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -71,8 +71,8 @@ module Database.LSMTree.Model.Session (
7171
, listSnapshots
7272
-- * Multiple writable tables
7373
, duplicate
74-
-- * Table merge
75-
, merge
74+
-- * Table union
75+
, union
7676
) where
7777

7878
import Control.Monad (when)
@@ -602,10 +602,10 @@ guardCursorIsOpen Cursor{..} =
602602
pure (fromJust $ fromSomeCursor c)
603603

604604
{-------------------------------------------------------------------------------
605-
Merging tables
605+
Table union
606606
-------------------------------------------------------------------------------}
607607

608-
merge ::
608+
union ::
609609
( MonadState Model m
610610
, MonadError Err m
611611
, C k v b
@@ -614,7 +614,7 @@ merge ::
614614
-> Table k v b
615615
-> Table k v b
616616
-> m (Table k v b)
617-
merge r th1 th2 = do
617+
union r th1 th2 = do
618618
(_, t1) <- guardTableIsOpen th1
619619
(_, t2) <- guardTableIsOpen th2
620-
newTableWith TableConfig $ Model.merge r t1 t2
620+
newTableWith TableConfig $ Model.union r t1 t2

test/Database/LSMTree/Model/Table.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -36,8 +36,8 @@ module Database.LSMTree.Model.Table (
3636
, snapshot
3737
-- * Multiple writable tables
3838
, duplicate
39-
-- * Table merge
40-
, merge
39+
-- * Table union
40+
, union
4141
-- * Testing
4242
, size
4343
) where
@@ -343,12 +343,12 @@ readCursor n c =
343343
--
344344
-- Multiple tables of the same type but with different configuration parameters
345345
-- can live in the same session. However, some operations, like
346-
merge ::
346+
union ::
347347
ResolveSerialisedValue v
348348
-> Table k v b
349349
-> Table k v b
350350
-> Table k v b
351-
merge r (Table xs) (Table ys) =
351+
union r (Table xs) (Table ys) =
352352
Table (Map.unionWith f xs ys)
353353
where
354354
f (v1, bMay1) (v2, bMay2) =

test/Test/Database/LSMTree/Class/Monoidal.hs

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,7 @@ tests = testGroup "Test.Database.LSMTree.Class.Monoidal"
9898
, testProperty' "snapshot-nochanges" $ prop_snapshotNoChanges tbl
9999
, testProperty' "snapshot-nochanges2" $ prop_snapshotNoChanges2 tbl
100100
, testProperty' "lookup-mupsert" $ prop_lookupUpdate tbl
101-
, testProperty' "merge" $ prop_merge tbl
101+
, testProperty' "merge" $ prop_union tbl
102102
]
103103

104104
-------------------------------------------------------------------------------
@@ -450,33 +450,33 @@ prop_lookupUpdate h ups k v1 v2 = ioProperty $ do
450450
return $ res === V.singleton (Found (resolve v2 v1))
451451

452452
-------------------------------------------------------------------------------
453-
-- implement classic QC tests for monoidal table merges
453+
-- implement classic QC tests for monoidal table unions
454454
-------------------------------------------------------------------------------
455455

456-
prop_merge :: forall h.
456+
prop_union :: forall h.
457457
IsTable h
458458
=> Proxy h -> [(Key, Update Value)] -> [(Key, Update Value)]
459459
-> [Key] -> Property
460-
prop_merge h ups1 ups2 (V.fromList -> testKeys) = ioProperty $ do
460+
prop_union h ups1 ups2 (V.fromList -> testKeys) = ioProperty $ do
461461
withTableNew h ups1 $ \s hdl1 -> do
462462
Class.withTableNew s (testTableConfig h) $ \hdl2 -> do
463463
updates hdl2 $ V.fromList ups2
464464

465-
-- merge them.
466-
Class.withTableMerge hdl1 hdl2 $ \hdl3 -> do
465+
-- union them.
466+
Class.withTableUnion hdl1 hdl2 $ \hdl3 -> do
467467

468-
-- results in parts and the merge table
468+
-- results in parts and the union table
469469
res1 <- lookups hdl1 testKeys
470470
res2 <- lookups hdl2 testKeys
471471
res3 <- lookups hdl3 testKeys
472472

473-
let mergeResult :: LookupResult Value -> LookupResult Value -> LookupResult Value
474-
mergeResult r@NotFound NotFound = r
475-
mergeResult NotFound r@(Found _) = r
476-
mergeResult r@(Found _) NotFound = r
477-
mergeResult (Found v1) (Found v2) = Found (resolve v1 v2)
473+
let unionResult :: LookupResult Value -> LookupResult Value -> LookupResult Value
474+
unionResult r@NotFound NotFound = r
475+
unionResult NotFound r@(Found _) = r
476+
unionResult r@(Found _) NotFound = r
477+
unionResult (Found v1) (Found v2) = Found (resolve v1 v2)
478478

479-
return $ V.zipWith mergeResult res1 res2 == res3
479+
return $ V.zipWith unionResult res1 res2 == res3
480480

481481
-------------------------------------------------------------------------------
482482
-- implement classic QC tests for snapshots

test/Test/Database/LSMTree/Class/Normal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -559,7 +559,7 @@ prop_updatesMayInvalidateBlobRefs h ups k1 v1 blob1 ups' = monadicIO $ do
559559
{- Not applicable -}
560560

561561
-------------------------------------------------------------------------------
562-
-- implement classic QC tests for monoidal table merges
562+
-- implement classic QC tests for monoidal table unions
563563
-------------------------------------------------------------------------------
564564

565565
{- Not applicable -}

0 commit comments

Comments
 (0)