summaryrefslogtreecommitdiff
path: root/Command/Fsck.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-09-25 14:16:34 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-09-25 14:16:34 -0400
commit324f16f1f0f14c3c5f457479efc9a7f22f30fd43 (patch)
treed6b1405bff9250c722e6777342808cf7af9576f0 /Command/Fsck.hs
parent19043fb8013180c0ac18e45129e0f20cb3ea7ff0 (diff)
add recordStartTime and getStartTime
Diffstat (limited to 'Command/Fsck.hs')
-rw-r--r--Command/Fsck.hs53
1 files changed, 51 insertions, 2 deletions
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index 834ca8af6..508e76966 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -7,8 +7,6 @@
module Command.Fsck where
-import System.Posix.Process (getProcessID)
-
import Common.Annex
import Command
import qualified Annex
@@ -28,6 +26,12 @@ import Config
import qualified Option
import Types.Key
+import System.Posix.Process (getProcessID)
+import Data.Time.Clock.POSIX
+import Data.Time
+import System.Posix.Types (EpochTime)
+import System.Locale
+
def :: [Command]
def = [withOptions options $ command "fsck" paramPaths seek
"check for problems"]
@@ -319,6 +323,18 @@ badContentRemote remote key = do
return $ (if ok then "dropped from " else "failed to drop from ")
++ Remote.name remote
+{- To record the time that an annexed file was last fscked, without
+ - modifying its mtime, we set the timestamp of its parent directory.
+ - Each annexed file is the only thing in its directory, so this is fine.
+ -
+ - To record that the file was fscked, the directory's sticky bit is set.
+ - (None of the normal unix behaviors of the sticky bit should matter, so
+ - we can reuse this permission bit.)
+ -
+ - Note that this relies on the parent directory being deleted when a file
+ - is dropped. That way, if it's later added back, the fsck metadata
+ - won't still be present.
+ -}
updateMetadata :: Key -> Annex Bool
updateMetadata key = do
file <- inRepo $ gitAnnexLocation key
@@ -326,3 +342,36 @@ updateMetadata key = do
liftIO $ touchFile parent
liftIO $ setSticky parent
return True
+
+{- Records the start time of an interactive fsck.
+ -
+ - To guard against time stamp damange (for example, if an annex directory
+ - is copied without -a), the fsckstate file contains a time that should
+ - be identical to its modification time. -}
+recordStartTime :: Annex ()
+recordStartTime = do
+ f <- fromRepo gitAnnexFsckState
+ liftIO $ do
+ nukeFile f
+ h <- openFile f WriteMode
+ t <- modificationTime <$> getFileStatus f
+ hPutStr h $ showTime $ realToFrac t
+ hClose h
+ where
+ showTime :: POSIXTime -> String
+ showTime = show
+
+{- Gets the incremental fsck start time. -}
+getStartTime :: Annex (Maybe EpochTime)
+getStartTime = do
+ f <- fromRepo gitAnnexFsckState
+ liftIO $ catchDefaultIO Nothing $ do
+ timestamp <- modificationTime <$> getFileStatus f
+ t <- readishTime <$> readFile f
+ return $ if Just (realToFrac timestamp) == t
+ then Just timestamp
+ else Nothing
+ where
+ readishTime :: String -> Maybe POSIXTime
+ readishTime s = utcTimeToPOSIXSeconds <$>
+ parseTime defaultTimeLocale "%s%Qs" s