Skip to content

Commit d43b910

Browse files
committed
Introduce classes for indexes and their accumulators
1 parent 504f43a commit d43b910

File tree

15 files changed

+354
-264
lines changed

15 files changed

+354
-264
lines changed

lsm-tree.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,7 @@ library
130130
Database.LSMTree.Internal.CRC32C
131131
Database.LSMTree.Internal.Cursor
132132
Database.LSMTree.Internal.Entry
133+
Database.LSMTree.Internal.Index
133134
Database.LSMTree.Internal.Index.Compact
134135
Database.LSMTree.Internal.Index.CompactAcc
135136
Database.LSMTree.Internal.Index.Ordinary
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.Index.CompactAcc (IndexCompactAcc)
15-
import qualified Database.LSMTree.Internal.Index.CompactAcc as IndexCompact
16-
(appendMulti, appendSingle)
17-
import Database.LSMTree.Internal.Index.OrdinaryAcc (IndexOrdinaryAcc)
18-
import qualified Database.LSMTree.Internal.Index.OrdinaryAcc 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 #-}
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)

src/Database/LSMTree/Internal/Index/Compact.hs

Lines changed: 36 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -6,10 +6,10 @@ module Database.LSMTree.Internal.Index.Compact (
66
-- $compact
77
IndexCompact (..)
88
-- * Queries
9-
, search
9+
, Index.search
10+
, Index.sizeInPages
1011
, countClashes
1112
, hasClashes
12-
, sizeInPages
1313
-- * Non-incremental serialisation
1414
, toLBS
1515
-- * Incremental serialisation
@@ -18,7 +18,7 @@ module Database.LSMTree.Internal.Index.Compact (
1818
, finalLBS
1919
, word64VectorToChunk
2020
-- * Deserialisation
21-
, fromSBS
21+
, Index.fromSBS
2222
) where
2323

2424
import Control.DeepSeq (NFData (..))
@@ -48,6 +48,9 @@ import Database.LSMTree.Internal.ByteString (byteArrayFromTo)
4848
import Database.LSMTree.Internal.Chunk (Chunk (Chunk))
4949
import qualified Database.LSMTree.Internal.Chunk as Chunk (toByteString)
5050
import Database.LSMTree.Internal.Entry (NumEntries (..))
51+
import Database.LSMTree.Internal.Index (Index)
52+
import qualified Database.LSMTree.Internal.Index as Index (fromSBS, search,
53+
sizeInPages)
5154
import Database.LSMTree.Internal.Page
5255
import Database.LSMTree.Internal.Serialise
5356
import Database.LSMTree.Internal.Unsliced
@@ -378,13 +381,13 @@ instance NFData IndexCompact where
378381
Queries
379382
-------------------------------------------------------------------------------}
380383

381-
-- | Searches for a page span that contains a key–value pair with the given key.
382-
--
383-
-- If there is indeed such a pair, the result is the corresponding page span; if
384-
-- there is no such pair, the result is an arbitrary but valid page span.
385-
--
386-
-- See [an informal description of the search algorithm](#search-descr) for more
387-
-- details about the search algorithm.
384+
{-|
385+
For a specification of this operation, see the documentation of [its
386+
polymorphic version]('Index.search').
387+
388+
See [an informal description of the search algorithm](#search-descr) for
389+
more details about the search algorithm.
390+
-}
388391
search :: SerialisedKey -> IndexCompact -> PageSpan
389392
-- One way to think of the search algorithm is that it starts with the full page
390393
-- number interval, and shrinks it to a minimal interval that contains the
@@ -443,7 +446,10 @@ countClashes = Map.size . icTieBreaker
443446
hasClashes :: IndexCompact -> Bool
444447
hasClashes = not . Map.null . icTieBreaker
445448

446-
-- | The number of pages within the index.
449+
{-|
450+
For a specification of this operation, see the documentation of [its
451+
polymorphic version]('Index.sizeInPages').
452+
-}
447453
sizeInPages :: IndexCompact -> NumPages
448454
sizeInPages = NumPages . toEnum . VU.length . icPrimary
449455

@@ -548,13 +554,10 @@ putPaddingTo64 written
548554
Deserialisation
549555
-------------------------------------------------------------------------------}
550556

551-
-- | The input bytestring must be 64 bit aligned and exactly contain the
552-
-- serialised compact index, with no leading or trailing space.
553-
-- It is directly used as the backing memory for the compact index.
554-
--
555-
-- Also note that the implementation reads values in little-endian byte order.
556-
-- If the file has been serialised in big-endian order, the mismatch will be
557-
-- detected by looking at the type–version indicator.
557+
{-|
558+
For a specification of this operation, see the documentation of [its
559+
polymorphic version]('Index.fromSBS').
560+
-}
558561
fromSBS :: ShortByteString -> Either String (NumEntries, IndexCompact)
559562
fromSBS (SBS ba') = do
560563
let ba = ByteArray ba'
@@ -675,6 +678,21 @@ checkedBitVec off len ba
675678
| otherwise =
676679
Nothing
677680

681+
{-------------------------------------------------------------------------------
682+
Type class instantiation
683+
-------------------------------------------------------------------------------}
684+
685+
instance Index IndexCompact where
686+
687+
search :: SerialisedKey -> IndexCompact -> PageSpan
688+
search = search
689+
690+
sizeInPages :: IndexCompact -> NumPages
691+
sizeInPages = sizeInPages
692+
693+
fromSBS :: ShortByteString -> Either String (NumEntries, IndexCompact)
694+
fromSBS = fromSBS
695+
678696
{-------------------------------------------------------------------------------
679697
Vector extras
680698
-------------------------------------------------------------------------------}

0 commit comments

Comments
 (0)