summaryrefslogtreecommitdiff
path: root/Logs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2022-09-23 13:10:49 -0400
committerJoey Hess <joeyh@joeyh.name>2022-09-23 13:12:17 -0400
commit8718125ae4417c12a3754dcbff328bc4a49aec77 (patch)
treed237cff5eee6ad0629824f022ca8b19573689475 /Logs
parent4822121728cd1177f9be157d588dc530568d38a3 (diff)
refactor the restage runner
Sponsored-by: Dartmouth College's DANDI project
Diffstat (limited to 'Logs')
-rw-r--r--Logs/Restage.hs51
1 files changed, 51 insertions, 0 deletions
diff --git a/Logs/Restage.hs b/Logs/Restage.hs
new file mode 100644
index 0000000000..75bba857c9
--- /dev/null
+++ b/Logs/Restage.hs
@@ -0,0 +1,51 @@
+{- git-annex restage log file
+ -
+ - Copyright 2022 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
+{-# LANGUAGE OverloadedStrings #-}
+
+module Logs.Restage where
+
+import Annex.Common
+import Git.FilePath
+import Logs.File
+
+import qualified Data.ByteString.Lazy as L
+
+-- | Log a file whose pointer needs to be restaged in git.
+-- The content of the file may not be a pointer, if it is populated with
+-- the annex content. The InodeCache is used to verify that the file
+-- still contains the content, and it's still safe to restage its pointer.
+writeRestageLog :: TopFilePath -> InodeCache -> Annex ()
+writeRestageLog f ic = do
+ logf <- fromRepo gitAnnexRestageLog
+ lckf <- fromRepo gitAnnexRestageLock
+ appendLogFile logf lckf $ L.fromStrict $
+ encodeBS (showInodeCache ic) <> ":" <> getTopFilePath f
+
+-- | Streams the content of the restage log, and then empties the log at
+-- the end.
+--
+-- If the action is interrupted or throws an exception, the log file is
+-- left unchanged.
+--
+-- Locking is used to prevent new items being added to the log while this
+-- is running.
+streamSmudged :: (TopFilePath -> InodeCache -> Annex ()) -> Annex ()
+streamSmudged a = do
+ logf <- fromRepo gitAnnexRestageLog
+ lckf <- fromRepo gitAnnexRestageLock
+ streamLogFile (fromRawFilePath logf) lckf $ \l ->
+ case parse l of
+ Nothing -> noop
+ Just (k, f) -> a f ic
+ where
+ parse l =
+ let (ics, f) = separate (== ':') l
+ in do
+ ic <- readInodeCache ics
+ return (asTopFilePath (toRawFilePath f), ic)
+