Skip to content

Commit 11738bd

Browse files
authored
Merge pull request #466 from IntersectMBO/jdral/proper-snapshot-impl
Proper snapshot implementation
2 parents 70a4296 + ffd6e60 commit 11738bd

File tree

17 files changed

+949
-935
lines changed

17 files changed

+949
-935
lines changed

lsm-tree.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,7 @@ library
155155
Database.LSMTree.Internal.Serialise
156156
Database.LSMTree.Internal.Serialise.Class
157157
Database.LSMTree.Internal.Snapshot
158+
Database.LSMTree.Internal.Snapshot.Codec
158159
Database.LSMTree.Internal.UniqCounter
159160
Database.LSMTree.Internal.Unsliced
160161
Database.LSMTree.Internal.Vector
@@ -371,7 +372,7 @@ test-suite lsm-tree-test
371372
Test.Database.LSMTree.Internal.RunReaders
372373
Test.Database.LSMTree.Internal.Serialise
373374
Test.Database.LSMTree.Internal.Serialise.Class
374-
Test.Database.LSMTree.Internal.Snapshot
375+
Test.Database.LSMTree.Internal.Snapshot.Codec
375376
Test.Database.LSMTree.Internal.Vector
376377
Test.Database.LSMTree.Internal.Vector.Growing
377378
Test.Database.LSMTree.Model.Table

src/Database/LSMTree/Common.hs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -205,9 +205,6 @@ class Labellable a where
205205
-- Exceptions:
206206
--
207207
-- * Deleting a snapshot that doesn't exist is an error.
208-
--
209-
-- TODO: this function currently has a temporary implementation until we have
210-
-- proper snapshots.
211208
deleteSnapshot ::
212209
IOLike m
213210
=> Session m
@@ -219,9 +216,6 @@ deleteSnapshot (Internal.Session' sesh) = Internal.deleteSnapshot sesh
219216
Session IO
220217
-> IO [Internal.SnapshotName] #-}
221218
-- | List snapshots by name.
222-
--
223-
-- TODO: this function currently has a temporary implementation until we have
224-
-- proper snapshots.
225219
listSnapshots ::
226220
IOLike m
227221
=> Session m

src/Database/LSMTree/Internal.hs

Lines changed: 79 additions & 78 deletions
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,6 @@ import Control.Monad.Primitive
8080
import Control.TempRegistry
8181
import Control.Tracer
8282
import Data.Arena (ArenaManager, newArenaManager)
83-
import Data.Char (isNumber)
8483
import Data.Foldable
8584
import Data.Functor.Compose (Compose (..))
8685
import Data.Kind
@@ -111,6 +110,7 @@ import qualified Database.LSMTree.Internal.RunReaders as Readers
111110
import Database.LSMTree.Internal.Serialise (SerialisedBlob (..),
112111
SerialisedKey, SerialisedValue)
113112
import Database.LSMTree.Internal.Snapshot
113+
import Database.LSMTree.Internal.Snapshot.Codec
114114
import Database.LSMTree.Internal.UniqCounter
115115
import qualified Database.LSMTree.Internal.WriteBuffer as WB
116116
import qualified Database.LSMTree.Internal.WriteBufferBlobs as WBB
@@ -397,15 +397,15 @@ openSession tr hfs hbio dir = do
397397
where
398398
root = Paths.SessionRoot dir
399399
lockFilePath = Paths.lockFile root
400-
activeDirPath = Paths.activeDir root
400+
activeDirPath = Paths.getActiveDir (Paths.activeDir root)
401401
snapshotsDirPath = Paths.snapshotsDir root
402402

403403
acquireLock = try @m @FsError $ FS.tryLockFile hbio lockFilePath FS.ExclusiveLock
404404

405405
releaseLock lockFile = forM_ (Compose lockFile) $ \lockFile' -> FS.hUnlock lockFile'
406406

407-
mkSession lockFile x = do
408-
counterVar <- newUniqCounter x
407+
mkSession lockFile = do
408+
counterVar <- newUniqCounter 0
409409
openTablesVar <- newMVar Map.empty
410410
openCursorsVar <- newMVar Map.empty
411411
sessionVar <- RW.new $ SessionOpen $ SessionEnv {
@@ -423,29 +423,22 @@ openSession tr hfs hbio dir = do
423423
traceWith tr TraceNewSession
424424
FS.createDirectory hfs activeDirPath
425425
FS.createDirectory hfs snapshotsDirPath
426-
mkSession sessionFileLock 0
426+
mkSession sessionFileLock
427427

428428
restoreSession sessionFileLock = do
429429
traceWith tr TraceRestoreSession
430430
-- If the layouts are wrong, we throw an exception, and the lock file
431431
-- is automatically released by bracketOnError.
432432
checkTopLevelDirLayout
433+
434+
-- Clear the active directory by removing the directory and recreating
435+
-- it again.
436+
FS.removeDirectoryRecursive hfs activeDirPath
437+
`finally` FS.createDirectoryIfMissing hfs False activeDirPath
438+
433439
checkActiveDirLayout
434440
checkSnapshotsDirLayout
435-
-- TODO: remove once we have proper snapshotting. Before that, we must
436-
-- prevent name clashes with runs that are still present in the active
437-
-- directory by starting the unique counter at a strictly higher number
438-
-- than the name of any run in the active directory. When we do
439-
-- snapshoting properly, then we'll hard link files into the active
440-
-- directory under new names/numbers, and so session counters will
441-
-- always be able to start at 0.
442-
files <- FS.listDirectory hfs activeDirPath
443-
let (x :: Int) | Set.null files = 0
444-
-- TODO: read is not very robust, but it is only a
445-
-- temporary solution
446-
| otherwise = maximum [ read (takeWhile isNumber f)
447-
| f <- Set.toList files ]
448-
mkSession sessionFileLock (fromIntegral x)
441+
mkSession sessionFileLock
449442

450443
-- Check that the active directory and snapshots directory exist. We assume
451444
-- the lock file already exists at this point.
@@ -459,12 +452,10 @@ openSession tr hfs hbio dir = do
459452
FS.doesDirectoryExist hfs snapshotsDirPath >>= \b ->
460453
unless b $ throwIO (SessionDirMalformed (FS.mkFsErrorPath hfs snapshotsDirPath))
461454

462-
-- Nothing to check: runs are verified when loading a table, not when
463-
-- a session is restored.
464-
--
465-
-- TODO: when we implement proper snapshotting, the files in the active
466-
-- directory should be ignored and cleaned up.
467-
checkActiveDirLayout = pure ()
455+
-- The active directory should be empty
456+
checkActiveDirLayout = do
457+
contents <- FS.listDirectory hfs activeDirPath
458+
unless (Set.null contents) $ throwIO (SessionDirMalformed (FS.mkFsErrorPath hfs activeDirPath))
468459

469460
-- Nothing to check: snapshots are verified when they are loaded, not when a
470461
-- session is restored.
@@ -1062,7 +1053,7 @@ readCursorWhile resolve keyIsWanted n Cursor {..} fromEntry = do
10621053
-> SnapshotLabel
10631054
-> SnapshotTableType
10641055
-> Table IO h
1065-
-> IO Int #-}
1056+
-> IO () #-}
10661057
-- | See 'Database.LSMTree.Normal.createSnapshot''.
10671058
createSnapshot ::
10681059
(MonadFix m, MonadMask m, MonadMVar m, MonadST m, MonadSTM m)
@@ -1071,59 +1062,62 @@ createSnapshot ::
10711062
-> SnapshotLabel
10721063
-> SnapshotTableType
10731064
-> Table m h
1074-
-> m Int
1065+
-> m ()
10751066
createSnapshot resolve snap label tableType t = do
10761067
traceWith (tableTracer t) $ TraceSnapshot snap
10771068
let conf = tableConfig t
1078-
withOpenTable t $ \thEnv -> do
1079-
let hfs = tableHasFS thEnv
1080-
1081-
-- Guard that the snapshot does not exist already
1082-
let snapDir = Paths.namedSnapshotDir (tableSessionRoot thEnv) snap
1083-
doesSnapshotExist <-
1084-
FS.doesDirectoryExist (tableHasFS thEnv) (Paths.getNamedSnapshotDir snapDir)
1085-
if doesSnapshotExist then
1086-
throwIO (ErrSnapshotExists snap)
1087-
else
1088-
-- we assume the snapshots directory already exists, so we just have to
1089-
-- create the directory for this specific snapshot.
1090-
FS.createDirectory hfs (Paths.getNamedSnapshotDir snapDir)
1091-
1092-
-- For the temporary implementation it is okay to just flush the buffer
1093-
-- before taking the snapshot.
1094-
content <- modifyWithTempRegistry
1095-
(RW.unsafeAcquireWriteAccess (tableContent thEnv))
1096-
(atomically . RW.unsafeReleaseWriteAccess (tableContent thEnv))
1097-
$ \reg content -> do
1098-
-- TODO: When we flush the buffer here, it might be underfull, which
1099-
-- could mess up the scheduling. The conservative approach is to supply
1100-
-- credits as if the buffer was full, and then flush the (possibly)
1101-
-- underfull buffer. However, note that this bit of code
1102-
-- here is probably going to change anyway because of #392
1103-
supplyCredits conf (Credit $ unNumEntries $ case confWriteBufferAlloc conf of AllocNumEntries x -> x) (tableLevels content)
1104-
content' <- flushWriteBuffer
1105-
(TraceMerge `contramap` tableTracer t)
1106-
conf
1107-
resolve
1108-
hfs
1109-
(tableHasBlockIO thEnv)
1110-
(tableSessionRoot thEnv)
1111-
(tableSessionUniqCounter thEnv)
1112-
reg
1113-
content
1114-
pure (content', content')
1115-
-- At this point, we've flushed the write buffer but we haven't created the
1116-
-- snapshot file yet. If an asynchronous exception happens beyond this
1117-
-- point, we'll take that loss, as the inner state of the table is still
1118-
-- consistent.
1119-
1120-
snappedLevels <- snapLevels (tableLevels content)
1121-
let snapMetaData = SnapshotMetaData label tableType (tableConfig t) snappedLevels
1122-
SnapshotMetaDataFile contentPath = Paths.snapshotMetaDataFile snapDir
1123-
SnapshotMetaDataChecksumFile checksumPath = Paths.snapshotMetaDataChecksumFile snapDir
1124-
writeFileSnapshotMetaData hfs contentPath checksumPath snapMetaData
1125-
1126-
pure $! numSnapRuns snappedLevels
1069+
withOpenTable t $ \thEnv ->
1070+
withTempRegistry $ \reg -> do -- TODO: use the temp registry for all side effects
1071+
let hfs = tableHasFS thEnv
1072+
1073+
-- Guard that the snapshot does not exist already
1074+
let snapDir = Paths.namedSnapshotDir (tableSessionRoot thEnv) snap
1075+
doesSnapshotExist <-
1076+
FS.doesDirectoryExist (tableHasFS thEnv) (Paths.getNamedSnapshotDir snapDir)
1077+
if doesSnapshotExist then
1078+
throwIO (ErrSnapshotExists snap)
1079+
else
1080+
-- we assume the snapshots directory already exists, so we just have to
1081+
-- create the directory for this specific snapshot.
1082+
FS.createDirectory hfs (Paths.getNamedSnapshotDir snapDir)
1083+
1084+
-- For the temporary implementation it is okay to just flush the buffer
1085+
-- before taking the snapshot.
1086+
content <- modifyWithTempRegistry
1087+
(RW.unsafeAcquireWriteAccess (tableContent thEnv))
1088+
(atomically . RW.unsafeReleaseWriteAccess (tableContent thEnv))
1089+
$ \innerReg content -> do
1090+
-- TODO: When we flush the buffer here, it might be underfull, which
1091+
-- could mess up the scheduling. The conservative approach is to supply
1092+
-- credits as if the buffer was full, and then flush the (possibly)
1093+
-- underfull buffer. However, note that this bit of code
1094+
-- here is probably going to change anyway because of #392
1095+
supplyCredits conf (Credit $ unNumEntries $ case confWriteBufferAlloc conf of AllocNumEntries x -> x) (tableLevels content)
1096+
content' <- flushWriteBuffer
1097+
(TraceMerge `contramap` tableTracer t)
1098+
conf
1099+
resolve
1100+
hfs
1101+
(tableHasBlockIO thEnv)
1102+
(tableSessionRoot thEnv)
1103+
(tableSessionUniqCounter thEnv)
1104+
innerReg
1105+
content
1106+
pure (content', content')
1107+
-- At this point, we've flushed the write buffer but we haven't created the
1108+
-- snapshot file yet. If an asynchronous exception happens beyond this
1109+
-- point, we'll take that loss, as the inner state of the table is still
1110+
-- consistent.
1111+
1112+
-- Convert to snapshot format
1113+
snapLevels <- toSnapLevels (tableLevels content)
1114+
-- Hard link runs into the named snapshot directory
1115+
snapLevels' <- snapshotRuns reg snapDir snapLevels
1116+
1117+
let snapMetaData = SnapshotMetaData label tableType (tableConfig t) snapLevels'
1118+
SnapshotMetaDataFile contentPath = Paths.snapshotMetaDataFile snapDir
1119+
SnapshotMetaDataChecksumFile checksumPath = Paths.snapshotMetaDataChecksumFile snapDir
1120+
writeFileSnapshotMetaData hfs contentPath checksumPath snapMetaData
11271121

11281122
{-# SPECIALISE openSnapshot ::
11291123
Session IO h
@@ -1161,7 +1155,7 @@ openSnapshot sesh label tableType override snap resolve = do
11611155
Left e -> throwIO (ErrSnapshotDeserialiseFailure e snap)
11621156
Right x -> pure x
11631157

1164-
let SnapshotMetaData label' tableType' conf snappedLevels = snapMetaData
1158+
let SnapshotMetaData label' tableType' conf snapLevels = snapMetaData
11651159

11661160
unless (tableType == tableType') $
11671161
throwIO (ErrSnapshotWrongTableType snap tableType tableType')
@@ -1177,7 +1171,14 @@ openSnapshot sesh label tableType override snap resolve = do
11771171
<- allocateTemp reg
11781172
(WBB.new hfs blobpath)
11791173
WBB.removeReference
1180-
tableLevels <- openLevels reg hfs hbio conf (sessionUniqCounter seshEnv) (sessionRoot seshEnv) resolve snappedLevels
1174+
1175+
let actDir = Paths.activeDir (sessionRoot seshEnv)
1176+
1177+
-- Hard link runs into the active directory,
1178+
snapLevels' <- openRuns reg hfs hbio conf (sessionUniqCounter seshEnv) snapDir actDir snapLevels
1179+
-- Convert from the snapshot format, restoring merge progress in the process
1180+
tableLevels <- fromSnapLevels reg hfs hbio conf (sessionUniqCounter seshEnv) resolve actDir snapLevels'
1181+
11811182
tableCache <- mkLevelsCache reg tableLevels
11821183
newWith reg sesh seshEnv conf' am $! TableContent {
11831184
tableWriteBuffer = WB.empty

src/Database/LSMTree/Internal/BlobFile.hs

Lines changed: 3 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -2,14 +2,12 @@ module Database.LSMTree.Internal.BlobFile (
22
BlobFile (..)
33
, BlobSpan (..)
44
, removeReference
5-
, RemoveFileOnClose (..)
65
, openBlobFile
76
, readBlob
87
, writeBlob
98
) where
109

1110
import Control.DeepSeq (NFData (..))
12-
import Control.Monad (unless)
1311
import Control.Monad.Class.MonadThrow (MonadMask, MonadThrow)
1412
import Control.Monad.Primitive (PrimMonad)
1513
import Control.RefCount (RefCounter)
@@ -55,31 +53,20 @@ removeReference ::
5553
removeReference BlobFile{blobFileRefCounter} =
5654
RC.removeReference blobFileRefCounter
5755

58-
-- | TODO: this hack can be removed once snapshots are done properly and so
59-
-- runs can delete their files on close.
60-
data RemoveFileOnClose = RemoveFileOnClose | DoNotRemoveFileOnClose
61-
deriving stock Eq
62-
6356
-- | Open the given file to make a 'BlobFile'. The finaliser will close and
6457
-- delete the file.
65-
--
66-
-- TODO: Temporarily we have a 'RemoveFileOnClose' flag, which can be removed
67-
-- once 'Run' no longer needs it, when snapshots are implemented.
68-
--
69-
{-# SPECIALISE openBlobFile :: HasFS IO h -> FS.FsPath -> FS.OpenMode -> RemoveFileOnClose -> IO (BlobFile IO h) #-}
58+
{-# SPECIALISE openBlobFile :: HasFS IO h -> FS.FsPath -> FS.OpenMode -> IO (BlobFile IO h) #-}
7059
openBlobFile ::
7160
PrimMonad m
7261
=> HasFS m h
7362
-> FS.FsPath
7463
-> FS.OpenMode
75-
-> RemoveFileOnClose
7664
-> m (BlobFile m h)
77-
openBlobFile fs path mode remove = do
65+
openBlobFile fs path mode = do
7866
blobFileHandle <- FS.hOpen fs path mode
7967
let finaliser = do
8068
FS.hClose fs blobFileHandle
81-
unless (remove == DoNotRemoveFileOnClose) $
82-
FS.removeFile fs (FS.handlePath blobFileHandle)
69+
FS.removeFile fs (FS.handlePath blobFileHandle)
8370
blobFileRefCounter <- RC.mkRefCounter1 (Just finaliser)
8471
return BlobFile {
8572
blobFileHandle,

src/Database/LSMTree/Internal/CRC32C.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,8 +41,6 @@ module Database.LSMTree.Internal.CRC32C (
4141
readChecksumsFile,
4242
writeChecksumsFile,
4343
writeChecksumsFile',
44-
45-
hexdigitsToInt
4644
) where
4745

4846
import Control.Monad

src/Database/LSMTree/Internal/Paths.hs

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Database.LSMTree.Internal.Paths (
22
SessionRoot (..)
33
, lockFile
4+
, ActiveDir (..)
45
, activeDir
56
, runPath
67
, snapshotsDir
@@ -62,11 +63,13 @@ newtype SessionRoot = SessionRoot { getSessionRoot :: FsPath }
6263
lockFile :: SessionRoot -> FsPath
6364
lockFile (SessionRoot dir) = dir </> mkFsPath ["lock"]
6465

65-
activeDir :: SessionRoot -> FsPath
66-
activeDir (SessionRoot dir) = dir </> mkFsPath ["active"]
66+
newtype ActiveDir = ActiveDir { getActiveDir :: FsPath }
67+
68+
activeDir :: SessionRoot -> ActiveDir
69+
activeDir (SessionRoot dir) = ActiveDir (dir </> mkFsPath ["active"])
6770

6871
runPath :: SessionRoot -> RunNumber -> RunFsPaths
69-
runPath root = RunFsPaths (activeDir root)
72+
runPath root = RunFsPaths (getActiveDir (activeDir root))
7073

7174
snapshotsDir :: SessionRoot -> FsPath
7275
snapshotsDir (SessionRoot dir) = dir </> mkFsPath ["snapshots"]
@@ -146,7 +149,7 @@ mkSnapshotName s
146149
-- | The file name for a table's write buffer blob file
147150
tableBlobPath :: SessionRoot -> Unique -> FsPath
148151
tableBlobPath session n =
149-
activeDir session </> mkFsPath [show (uniqueToWord64 n)] <.> "wbblobs"
152+
getActiveDir (activeDir session) </> mkFsPath [show (uniqueToWord64 n)] <.> "wbblobs"
150153

151154
{-------------------------------------------------------------------------------
152155
Run paths

0 commit comments

Comments
 (0)