@@ -80,7 +80,6 @@ import Control.Monad.Primitive
8080import Control.TempRegistry
8181import Control.Tracer
8282import Data.Arena (ArenaManager , newArenaManager )
83- import Data.Char (isNumber )
8483import Data.Foldable
8584import Data.Functor.Compose (Compose (.. ))
8685import Data.Kind
@@ -111,6 +110,7 @@ import qualified Database.LSMTree.Internal.RunReaders as Readers
111110import Database.LSMTree.Internal.Serialise (SerialisedBlob (.. ),
112111 SerialisedKey , SerialisedValue )
113112import Database.LSMTree.Internal.Snapshot
113+ import Database.LSMTree.Internal.Snapshot.Codec
114114import Database.LSMTree.Internal.UniqCounter
115115import qualified Database.LSMTree.Internal.WriteBuffer as WB
116116import 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''.
10671058createSnapshot ::
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 ()
10751066createSnapshot 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
0 commit comments