{-# LANGUAGE LambdaCase #-}
module Data.Acid.Repair
( repairFile
, repairEvents
, repairCheckpoints
) where
import qualified Data.Acid.Archive as Archive
import Data.Acid.Local (mkEventsLogKey, mkCheckpointsLogKey)
import Data.Acid.Log (LogKey)
import qualified Data.Acid.Log as Log
import qualified Data.ByteString.Lazy as Lazy
import Data.List (sort)
import System.Directory
import System.FilePath.Posix
import System.IO (hClose, openTempFile)
repairEntries :: Lazy.ByteString -> Lazy.ByteString
repairEntries :: ByteString -> ByteString
repairEntries =
[ByteString] -> ByteString
Archive.packEntries ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Entries -> [ByteString]
Archive.entriesToListNoFail (Entries -> [ByteString])
-> (ByteString -> Entries) -> ByteString -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Entries
Archive.readEntries
repairFile :: FilePath -> IO ()
repairFile :: FilePath -> IO ()
repairFile FilePath
fp = do
broken <- FilePath -> IO ByteString
Lazy.readFile FilePath
fp
let repaired = ByteString -> ByteString
repairEntries ByteString
broken
(tmp, temph) <- openTempFile (takeDirectory fp) (takeFileName fp)
hClose temph
Lazy.writeFile tmp repaired
dropFile fp
renameFile tmp fp
repairLogs :: LogKey object -> IO ()
repairLogs :: forall object. LogKey object -> IO ()
repairLogs LogKey object
identifier = do
logFiles <- LogKey object -> IO [(Int, FilePath)]
forall object. LogKey object -> IO [(Int, FilePath)]
Log.findLogFiles LogKey object
identifier
let sorted = [(Int, FilePath)] -> [(Int, FilePath)]
forall a. Ord a => [a] -> [a]
sort [(Int, FilePath)]
logFiles
(_eventIds, files) = unzip sorted
broken_files <- mapM needsRepair files
repair $ map snd $ dropWhile (\(Bool
b,FilePath
_) -> Bool -> Bool
not Bool
b) $ zip broken_files files
where
repair :: [FilePath] -> IO ()
repair [] = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
repair (FilePath
file:[FilePath]
rest) = do
(FilePath -> IO ()) -> [FilePath] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ FilePath -> IO ()
dropFile ([FilePath] -> [FilePath]
forall a. [a] -> [a]
reverse [FilePath]
rest)
FilePath -> IO ()
repairFile FilePath
file
dropFile :: FilePath -> IO ()
dropFile :: FilePath -> IO ()
dropFile FilePath
fp = do
bak <- FilePath -> IO FilePath
findNext (FilePath
fp FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".bak")
renameFile fp bak
repairEvents
:: FilePath
-> IO ()
repairEvents :: FilePath -> IO ()
repairEvents FilePath
directory =
LogKey (Tagged ByteString) -> IO ()
forall object. LogKey object -> IO ()
repairLogs (FilePath
-> SerialisationLayer (ZonkAny 0) -> LogKey (Tagged ByteString)
forall object.
FilePath -> SerialisationLayer object -> LogKey (Tagged ByteString)
mkEventsLogKey FilePath
directory SerialisationLayer (ZonkAny 0)
forall {a}. a
noserialisation)
where
noserialisation :: a
noserialisation =
FilePath -> a
forall a. HasCallStack => FilePath -> a
error FilePath
"Repair.repairEvents: the serialisation layer shouldn't be forced"
repairCheckpoints
:: FilePath
-> IO ()
repairCheckpoints :: FilePath -> IO ()
repairCheckpoints FilePath
directory = do
let checkpointLogKey :: LogKey (Checkpoint object)
checkpointLogKey = FilePath -> SerialisationLayer object -> LogKey (Checkpoint object)
forall object.
FilePath -> SerialisationLayer object -> LogKey (Checkpoint object)
mkCheckpointsLogKey FilePath
directory SerialisationLayer object
forall {a}. a
noserialisation
checkpointFiles <- LogKey (Checkpoint (ZonkAny 1)) -> IO [(Int, FilePath)]
forall object. LogKey object -> IO [(Int, FilePath)]
Log.findLogFiles LogKey (Checkpoint (ZonkAny 1))
forall {object}. LogKey (Checkpoint object)
checkpointLogKey
let (_eventIds, files) = unzip checkpointFiles
mapM_ repairFile files
where
noserialisation :: a
noserialisation =
FilePath -> a
forall a. HasCallStack => FilePath -> a
error FilePath
"Repair.repairCheckpoints: the serialisation layer shouldn't be forced"
needsRepair :: FilePath -> IO Bool
needsRepair :: FilePath -> IO Bool
needsRepair FilePath
fp = do
contents <- FilePath -> IO ByteString
Lazy.readFile FilePath
fp
let entries = ByteString -> Entries
Archive.readEntries ByteString
contents
return $ entriesNeedRepair entries
where
entriesNeedRepair :: Entries -> Bool
entriesNeedRepair Archive.Fail{} = Bool
True
entriesNeedRepair Entries
Archive.Done = Bool
False
entriesNeedRepair (Archive.Next ByteString
_ Entries
rest) = Entries -> Bool
entriesNeedRepair Entries
rest
findNext :: FilePath -> IO (FilePath)
findNext :: FilePath -> IO FilePath
findNext FilePath
fp = Int -> IO FilePath
go Int
0
where
go :: Int -> IO FilePath
go Int
n =
let next :: FilePath
next = FilePath -> Int -> FilePath
fileWithSuffix FilePath
fp Int
n in
FilePath -> IO Bool
doesFileExist FilePath
next IO Bool -> (Bool -> IO FilePath) -> IO FilePath
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
False -> FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
next
Bool
True -> Int -> IO FilePath
go (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
fileWithSuffix :: FilePath -> Int -> FilePath
fileWithSuffix :: FilePath -> Int -> FilePath
fileWithSuffix FilePath
fp Int
i =
if Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then FilePath
fp
else FilePath
fp FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
i