Skip to content

Commit 8460319

Browse files
authored
Merge pull request #476 from IntersectMBO/jeltsch/index-type-class
Introduce classes for indexes and their accumulators
2 parents d11c709 + d43b910 commit 8460319

File tree

25 files changed

+478
-388
lines changed

25 files changed

+478
-388
lines changed

bench/macro/lsm-tree-bench-lookups.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ import Database.LSMTree.Extras.Orphans ()
2525
import Database.LSMTree.Extras.UTxO
2626
import Database.LSMTree.Internal.Entry (Entry (Insert),
2727
NumEntries (..))
28-
import Database.LSMTree.Internal.IndexCompact (IndexCompact)
28+
import Database.LSMTree.Internal.Index.Compact (IndexCompact)
2929
import Database.LSMTree.Internal.Lookup
3030
import Database.LSMTree.Internal.Paths (RunFsPaths (RunFsPaths))
3131
import Database.LSMTree.Internal.Run (Run)

bench/micro/Bench/Database/LSMTree/Internal/IndexCompact.hs renamed to bench/micro/Bench/Database/LSMTree/Internal/Index/Compact.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE TypeApplications #-}
33
{- HLINT ignore "Eta reduce" -}
44

5-
module Bench.Database.LSMTree.Internal.IndexCompact (
5+
module Bench.Database.LSMTree.Internal.Index.Compact (
66
benchmarks
77
-- * Benchmarked functions
88
, searches
@@ -25,15 +25,15 @@ import Database.LSMTree.Extras.Generators
2525
import Database.LSMTree.Extras.Index
2626
import Database.LSMTree.Extras.Random
2727
import Database.LSMTree.Extras.UTxO
28-
import Database.LSMTree.Internal.IndexCompact
29-
import Database.LSMTree.Internal.IndexCompactAcc
28+
import Database.LSMTree.Internal.Index.Compact
29+
import Database.LSMTree.Internal.Index.CompactAcc
3030
import Database.LSMTree.Internal.Serialise (SerialisedKey,
3131
serialiseKey)
3232
import System.Random
3333
import Test.QuickCheck (generate)
3434

3535
benchmarks :: Benchmark
36-
benchmarks = bgroup "Bench.Database.LSMTree.Internal.IndexCompact" [
36+
benchmarks = bgroup "Bench.Database.LSMTree.Internal.Index.Compact" [
3737
env (searchEnv 10000 1000) $ \ ~(ic, ks) ->
3838
bench "searches-10-1k" $ whnf (searches ic) ks
3939
, bgroup "construction" [

bench/micro/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
module Main (main) where
55

66
import qualified Bench.Database.LSMTree.Internal.BloomFilter
7-
import qualified Bench.Database.LSMTree.Internal.IndexCompact
7+
import qualified Bench.Database.LSMTree.Internal.Index.Compact
88
import qualified Bench.Database.LSMTree.Internal.Lookup
99
import qualified Bench.Database.LSMTree.Internal.Merge
1010
import qualified Bench.Database.LSMTree.Internal.RawPage
@@ -21,7 +21,7 @@ main = do
2121
#endif
2222
defaultMain [
2323
Bench.Database.LSMTree.Internal.BloomFilter.benchmarks
24-
, Bench.Database.LSMTree.Internal.IndexCompact.benchmarks
24+
, Bench.Database.LSMTree.Internal.Index.Compact.benchmarks
2525
, Bench.Database.LSMTree.Internal.Lookup.benchmarks
2626
, Bench.Database.LSMTree.Internal.Merge.benchmarks
2727
, Bench.Database.LSMTree.Internal.RawPage.benchmarks

lsm-tree.cabal

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -130,10 +130,11 @@ library
130130
Database.LSMTree.Internal.CRC32C
131131
Database.LSMTree.Internal.Cursor
132132
Database.LSMTree.Internal.Entry
133-
Database.LSMTree.Internal.IndexCompact
134-
Database.LSMTree.Internal.IndexCompactAcc
135-
Database.LSMTree.Internal.IndexOrdinary
136-
Database.LSMTree.Internal.IndexOrdinaryAcc
133+
Database.LSMTree.Internal.Index
134+
Database.LSMTree.Internal.Index.Compact
135+
Database.LSMTree.Internal.Index.CompactAcc
136+
Database.LSMTree.Internal.Index.Ordinary
137+
Database.LSMTree.Internal.Index.OrdinaryAcc
137138
Database.LSMTree.Internal.Lookup
138139
Database.LSMTree.Internal.Merge
139140
Database.LSMTree.Internal.MergeSchedule
@@ -356,8 +357,8 @@ test-suite lsm-tree-test
356357
Test.Database.LSMTree.Internal.Chunk
357358
Test.Database.LSMTree.Internal.CRC32C
358359
Test.Database.LSMTree.Internal.Entry
359-
Test.Database.LSMTree.Internal.IndexCompact
360-
Test.Database.LSMTree.Internal.IndexOrdinary
360+
Test.Database.LSMTree.Internal.Index.Compact
361+
Test.Database.LSMTree.Internal.Index.Ordinary
361362
Test.Database.LSMTree.Internal.Lookup
362363
Test.Database.LSMTree.Internal.Merge
363364
Test.Database.LSMTree.Internal.Monkey
@@ -452,7 +453,7 @@ benchmark lsm-tree-micro-bench
452453
main-is: Main.hs
453454
other-modules:
454455
Bench.Database.LSMTree.Internal.BloomFilter
455-
Bench.Database.LSMTree.Internal.IndexCompact
456+
Bench.Database.LSMTree.Internal.Index.Compact
456457
Bench.Database.LSMTree.Internal.Lookup
457458
Bench.Database.LSMTree.Internal.Merge
458459
Bench.Database.LSMTree.Internal.RawPage
Lines changed: 14 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,11 @@
1+
{-|
2+
Provides additional support for working with fence pointer indexes and their
3+
accumulators.
4+
-}
15
module Database.LSMTree.Extras.Index
26
(
37
Append (AppendSinglePage, AppendMultiPage),
4-
append,
5-
append'
8+
append
69
)
710
where
811

@@ -11,12 +14,8 @@ import Control.Monad.ST.Strict (ST)
1114
import Data.Foldable (toList)
1215
import Data.Word (Word32)
1316
import Database.LSMTree.Internal.Chunk (Chunk)
14-
import Database.LSMTree.Internal.IndexCompactAcc (IndexCompactAcc)
15-
import qualified Database.LSMTree.Internal.IndexCompactAcc as IndexCompact
16-
(appendMulti, appendSingle)
17-
import Database.LSMTree.Internal.IndexOrdinaryAcc (IndexOrdinaryAcc)
18-
import qualified Database.LSMTree.Internal.IndexOrdinaryAcc as IndexOrdinary
19-
(appendMulti, appendSingle)
17+
import Database.LSMTree.Internal.Index (IndexAcc, appendMulti,
18+
appendSingle)
2019
import Database.LSMTree.Internal.Serialise (SerialisedKey)
2120

2221
-- | Instruction for appending pages, to be used in conjunction with indexes.
@@ -42,31 +41,15 @@ instance NFData Append where
4241
= rnf key `seq` rnf overflowPageCount
4342

4443
{-|
45-
Add information about appended pages to an index under incremental
46-
construction.
44+
Adds information about appended pages to an index and outputs newly
45+
available chunks.
4746
48-
Internally, 'append' uses 'IndexCompact.appendSingle' and
49-
'IndexCompact.appendMulti', and the usage restrictions of those functions
50-
apply also here.
47+
See the documentation of the 'IndexAcc' class for constraints to adhere to.
5148
-}
52-
append :: Append -> IndexCompactAcc s -> ST s [Chunk]
49+
append :: IndexAcc j => Append -> j s -> ST s [Chunk]
5350
append instruction indexAcc = case instruction of
5451
AppendSinglePage minKey maxKey
55-
-> toList <$> IndexCompact.appendSingle (minKey, maxKey) indexAcc
56-
AppendMultiPage key overflowPageCount
57-
-> IndexCompact.appendMulti (key, overflowPageCount) indexAcc
58-
59-
{-|
60-
A variant of 'append' for ordinary indexes, which is only used temporarily
61-
until there is a type class of index types.
62-
63-
Internally, 'append'' uses 'IndexOrdinary.appendSingle' and
64-
'IndexOrdinary.appendMulti', and the usage restrictions of those functions
65-
apply also here.
66-
-}
67-
append' :: Append -> IndexOrdinaryAcc s -> ST s [Chunk]
68-
append' instruction indexAcc = case instruction of
69-
AppendSinglePage minKey maxKey
70-
-> toList <$> IndexOrdinary.appendSingle (minKey, maxKey) indexAcc
52+
-> toList <$> appendSingle (minKey, maxKey) indexAcc
7153
AppendMultiPage key overflowPageCount
72-
-> IndexOrdinary.appendMulti (key, overflowPageCount) indexAcc
54+
-> appendMulti (key, overflowPageCount) indexAcc
55+
{-# INLINABLE append #-}

src-extras/Database/LSMTree/Extras/NoThunks.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ import Database.LSMTree.Internal.ChecksumHandle
4040
import Database.LSMTree.Internal.Config
4141
import Database.LSMTree.Internal.CRC32C
4242
import Database.LSMTree.Internal.Entry
43-
import Database.LSMTree.Internal.IndexCompact
44-
import Database.LSMTree.Internal.IndexCompactAcc
43+
import Database.LSMTree.Internal.Index.Compact
44+
import Database.LSMTree.Internal.Index.CompactAcc
4545
import Database.LSMTree.Internal.Merge hiding (Level)
4646
import qualified Database.LSMTree.Internal.Merge as Merge
4747
import Database.LSMTree.Internal.MergeSchedule

src/Database/LSMTree/Internal/ChecksumHandle.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,8 +34,8 @@ import qualified Database.LSMTree.Internal.Chunk as Chunk (toByteString)
3434
import Database.LSMTree.Internal.CRC32C (CRC32C)
3535
import qualified Database.LSMTree.Internal.CRC32C as CRC
3636
import Database.LSMTree.Internal.Entry
37-
import Database.LSMTree.Internal.IndexCompact (IndexCompact)
38-
import qualified Database.LSMTree.Internal.IndexCompact as Index
37+
import Database.LSMTree.Internal.Index.Compact (IndexCompact)
38+
import qualified Database.LSMTree.Internal.Index.Compact as Index
3939
import Database.LSMTree.Internal.Paths (ForBlob (..), ForFilter (..),
4040
ForIndex (..), ForKOps (..))
4141
import qualified Database.LSMTree.Internal.RawBytes as RB
Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
{-# LANGUAGE TypeFamilies #-}
2+
3+
{-|
4+
Provides a common interface to different types of fence pointer indexes and
5+
their accumulators.
6+
-}
7+
module Database.LSMTree.Internal.Index
8+
(
9+
Index (search, sizeInPages, fromSBS),
10+
IndexAcc (ResultingIndex, appendSingle, appendMulti, unsafeEnd)
11+
)
12+
where
13+
14+
import Control.Monad.ST.Strict (ST)
15+
import Data.ByteString.Short (ShortByteString)
16+
import Data.Word (Word32)
17+
import Database.LSMTree.Internal.Chunk (Chunk)
18+
import Database.LSMTree.Internal.Entry (NumEntries)
19+
import Database.LSMTree.Internal.Page (NumPages, PageSpan)
20+
import Database.LSMTree.Internal.Serialise (SerialisedKey)
21+
22+
-- | The class of index types.
23+
class Index i where
24+
25+
{-|
26+
Searches for a page span that contains a key–value pair with the given
27+
key. If there is indeed such a pair, the result is the corresponding
28+
page span; if there is no such pair, the result is an arbitrary but
29+
valid page span.
30+
-}
31+
search :: SerialisedKey -> i -> PageSpan
32+
33+
-- | Yields the number of pages covered by an index.
34+
sizeInPages :: i -> NumPages
35+
36+
{-|
37+
Reads an index along with the number of entries of the respective run
38+
from a byte string.
39+
40+
The byte string must contain the serialised index exactly, with no
41+
leading or trailing space. Furthermore, its contents must be stored
42+
64-bit-aligned.
43+
44+
The contents of the byte string may be directly used as the backing
45+
memory for the constructed index. Currently, this is done for compact
46+
indexes.
47+
48+
For deserialising numbers, the endianness of the host system is used. If
49+
serialisation has been done with a different endianness, this mismatch
50+
is detected by looking at the type–version indicator.
51+
-}
52+
fromSBS :: ShortByteString -> Either String (NumEntries, i)
53+
54+
{-|
55+
The class of index accumulator types, where an index accumulator denotes an
56+
index under incremental construction.
57+
58+
Incremental index construction is only guaranteed to work correctly when the
59+
following conditions are met:
60+
61+
* The supplied key ranges do not overlap and are given in ascending order.
62+
63+
* Each supplied key is at least 8 and at most 65535 bytes long.
64+
(Currently, construction of compact indexes needs the former and
65+
construction of ordinary indexes needs the latter bound.)
66+
-}
67+
class Index (ResultingIndex j) => IndexAcc j where
68+
69+
-- | The type of indexes constructed by accumulators of a certain type
70+
type ResultingIndex j
71+
72+
{-|
73+
Adds information about a single page that fully comprises one or more
74+
key–value pairs to an index and outputs newly available chunks.
75+
76+
See the documentation of the 'IndexAcc' class for constraints to adhere
77+
to.
78+
-}
79+
appendSingle :: (SerialisedKey, SerialisedKey) -> j s -> ST s (Maybe Chunk)
80+
81+
{-|
82+
Adds information about multiple pages that together comprise a single
83+
key–value pair to an index and outputs newly available chunks.
84+
85+
The provided 'Word32' value denotes the number of /overflow/ pages, so
86+
that the number of pages that comprise the key–value pair is the
87+
successor of that number.
88+
89+
See the documentation of the 'IndexAcc' class for constraints to adhere
90+
to.
91+
-}
92+
appendMulti :: (SerialisedKey, Word32) -> j s -> ST s [Chunk]
93+
94+
{-|
95+
Returns the constructed index, along with a final chunk in case the
96+
serialised key list has not been fully output yet, thereby invalidating
97+
the index under construction. Executing @unsafeEnd index@ is only safe
98+
when @index@ is not used afterwards.
99+
-}
100+
unsafeEnd :: j s -> ST s (Maybe Chunk, ResultingIndex j)

0 commit comments

Comments
 (0)