2010-11-06 21:06:19 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2013-06-24 20:26:00 +00:00
|
|
|
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
|
2010-11-06 21:06:19 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-05-10 21:29:59 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2010-11-06 21:06:19 +00:00
|
|
|
module Command.Fsck where
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
import Common.Annex
|
2010-11-06 21:06:19 +00:00
|
|
|
import Command
|
2012-01-20 17:23:11 +00:00
|
|
|
import qualified Annex
|
2011-07-05 22:31:46 +00:00
|
|
|
import qualified Remote
|
|
|
|
import qualified Types.Backend
|
|
|
|
import qualified Types.Key
|
2011-10-29 21:49:37 +00:00
|
|
|
import qualified Backend
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2013-01-08 16:41:09 +00:00
|
|
|
import Annex.Content.Direct
|
2013-06-24 20:26:00 +00:00
|
|
|
import Annex.Direct
|
2012-06-06 00:25:32 +00:00
|
|
|
import Annex.Perms
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
import Annex.Link
|
2011-10-15 20:21:08 +00:00
|
|
|
import Logs.Location
|
|
|
|
import Logs.Trust
|
2014-01-21 22:08:56 +00:00
|
|
|
import Config.NumCopies
|
2011-10-15 21:47:03 +00:00
|
|
|
import Annex.UUID
|
2011-07-06 00:36:43 +00:00
|
|
|
import Utility.DataUnits
|
2011-09-23 22:13:24 +00:00
|
|
|
import Utility.FileMode
|
2011-07-05 22:31:46 +00:00
|
|
|
import Config
|
2012-08-08 20:06:01 +00:00
|
|
|
import Types.Key
|
2014-03-13 23:06:26 +00:00
|
|
|
import Types.CleanupActions
|
2012-09-25 23:37:34 +00:00
|
|
|
import Utility.HumanTime
|
2013-06-18 01:30:52 +00:00
|
|
|
import Git.FilePath
|
2014-02-11 19:29:56 +00:00
|
|
|
import Utility.PID
|
2010-11-06 21:06:19 +00:00
|
|
|
|
2012-09-25 18:16:34 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
|
|
|
import Data.Time
|
|
|
|
import System.Posix.Types (EpochTime)
|
|
|
|
import System.Locale
|
|
|
|
|
2011-10-29 19:19:05 +00:00
|
|
|
def :: [Command]
|
2013-07-03 17:02:42 +00:00
|
|
|
def = [withOptions fsckOptions $ command "fsck" paramPaths seek
|
2013-03-24 22:28:21 +00:00
|
|
|
SectionMaintenance "check for problems"]
|
2012-01-19 19:24:05 +00:00
|
|
|
|
2014-01-26 20:25:55 +00:00
|
|
|
fsckFromOption :: Option
|
|
|
|
fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"
|
2012-01-19 19:24:05 +00:00
|
|
|
|
2012-09-25 17:19:05 +00:00
|
|
|
startIncrementalOption :: Option
|
2014-01-26 20:25:55 +00:00
|
|
|
startIncrementalOption = flagOption ['S'] "incremental" "start an incremental fsck"
|
2012-09-25 17:19:05 +00:00
|
|
|
|
2012-09-25 19:45:17 +00:00
|
|
|
moreIncrementalOption :: Option
|
2014-01-26 20:25:55 +00:00
|
|
|
moreIncrementalOption = flagOption ['m'] "more" "continue an incremental fsck"
|
2012-09-25 17:19:05 +00:00
|
|
|
|
2012-09-25 23:43:33 +00:00
|
|
|
incrementalScheduleOption :: Option
|
2014-01-26 20:25:55 +00:00
|
|
|
incrementalScheduleOption = fieldOption [] "incremental-schedule" paramTime
|
2012-09-25 23:43:33 +00:00
|
|
|
"schedule incremental fscking"
|
2012-09-25 23:37:34 +00:00
|
|
|
|
2013-07-03 17:02:42 +00:00
|
|
|
fsckOptions :: [Option]
|
|
|
|
fsckOptions =
|
2014-01-26 20:25:55 +00:00
|
|
|
[ fsckFromOption
|
2012-09-25 23:37:34 +00:00
|
|
|
, startIncrementalOption
|
|
|
|
, moreIncrementalOption
|
2012-09-25 23:43:33 +00:00
|
|
|
, incrementalScheduleOption
|
2013-07-03 19:26:59 +00:00
|
|
|
] ++ keyOptions
|
2010-12-30 19:06:26 +00:00
|
|
|
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
seek :: CommandSeek
|
|
|
|
seek ps = do
|
2014-01-26 20:25:55 +00:00
|
|
|
from <- getOptionField fsckFromOption Remote.byNameWithUUID
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
i <- getIncremental
|
|
|
|
withKeyOptions
|
2014-02-20 18:45:17 +00:00
|
|
|
(\k -> startKey i k =<< getNumCopies)
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
(withFilesInGit $ whenAnnexed $ start from i)
|
|
|
|
ps
|
2010-11-15 22:22:50 +00:00
|
|
|
|
fix inversion of control in CommandSeek (no behavior changes)
I've been disliking how the command seek actions were written for some
time, with their inversion of control and ugly workarounds.
The last straw to fix it was sync --content, which didn't fit the
Annex [CommandStart] interface well at all. I have not yet made it take
advantage of the changed interface though.
The crucial change, and probably why I didn't do it this way from the
beginning, is to make each CommandStart action be run with exceptions
caught, and if it fails, increment a failure counter in annex state.
So I finally remove the very first code I wrote for git-annex, which
was before I had exception handling in the Annex monad, and so ran outside
that monad, passing state explicitly as it ran each CommandStart action.
This was a real slog from 1 to 5 am.
Test suite passes.
Memory usage is lower than before, sometimes by a couple of megabytes, and
remains constant, even when running in a large repo, and even when
repeatedly failing and incrementing the error counter. So no accidental
laziness space leaks.
Wall clock speed is identical, even in large repos.
This commit was sponsored by an anonymous bitcoiner.
2014-01-20 08:11:42 +00:00
|
|
|
getIncremental :: Annex Incremental
|
|
|
|
getIncremental = do
|
2012-09-25 23:43:33 +00:00
|
|
|
i <- maybe (return False) (checkschedule . parseDuration)
|
2014-01-26 20:25:55 +00:00
|
|
|
=<< Annex.getField (optionName incrementalScheduleOption)
|
|
|
|
starti <- Annex.getFlag (optionName startIncrementalOption)
|
|
|
|
morei <- Annex.getFlag (optionName moreIncrementalOption)
|
2012-09-25 23:37:34 +00:00
|
|
|
case (i, starti, morei) of
|
|
|
|
(False, False, False) -> return NonIncremental
|
2014-02-20 19:56:45 +00:00
|
|
|
(False, True, False) -> startIncremental
|
2012-09-25 23:37:34 +00:00
|
|
|
(False ,False, True) -> ContIncremental <$> getStartTime
|
2014-02-20 19:56:45 +00:00
|
|
|
(True, False, False) ->
|
2012-09-25 23:37:34 +00:00
|
|
|
maybe startIncremental (return . ContIncremental . Just)
|
|
|
|
=<< getStartTime
|
2014-02-20 19:56:45 +00:00
|
|
|
_ -> error "Specify only one of --incremental, --more, or --incremental-schedule"
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
startIncremental = do
|
|
|
|
recordStartTime
|
|
|
|
return StartIncremental
|
|
|
|
|
|
|
|
checkschedule Nothing = error "bad --incremental-schedule value"
|
|
|
|
checkschedule (Just delta) = do
|
2014-03-13 23:06:26 +00:00
|
|
|
Annex.addCleanup FsckCleanup $ do
|
2012-11-12 05:05:04 +00:00
|
|
|
v <- getStartTime
|
|
|
|
case v of
|
|
|
|
Nothing -> noop
|
|
|
|
Just started -> do
|
|
|
|
now <- liftIO getPOSIXTime
|
2013-10-08 21:36:55 +00:00
|
|
|
when (now - realToFrac started >= durationToPOSIXTime delta)
|
2012-11-12 05:05:04 +00:00
|
|
|
resetStartTime
|
|
|
|
return True
|
2012-09-25 17:19:05 +00:00
|
|
|
|
|
|
|
start :: Maybe Remote -> Incremental -> FilePath -> (Key, Backend) -> CommandStart
|
|
|
|
start from inc file (key, backend) = do
|
2014-01-21 20:08:19 +00:00
|
|
|
numcopies <- getFileNumCopies file
|
2012-01-19 19:24:05 +00:00
|
|
|
case from of
|
2012-09-25 19:06:33 +00:00
|
|
|
Nothing -> go $ perform key file backend numcopies
|
|
|
|
Just r -> go $ performRemote key file backend numcopies r
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
go = runFsck inc file key
|
2010-11-15 22:22:50 +00:00
|
|
|
|
2014-01-21 21:08:49 +00:00
|
|
|
perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool
|
2012-09-25 19:06:33 +00:00
|
|
|
perform key file backend numcopies = check
|
2011-10-29 20:45:06 +00:00
|
|
|
-- order matters
|
2012-03-10 18:46:21 +00:00
|
|
|
[ fixLink key file
|
|
|
|
, verifyLocationLog key file
|
2013-01-19 18:11:23 +00:00
|
|
|
, verifyDirectMapping key file
|
2013-06-24 20:26:00 +00:00
|
|
|
, verifyDirectMode key file
|
2011-10-29 20:45:06 +00:00
|
|
|
, checkKeySize key
|
2013-04-16 20:17:20 +00:00
|
|
|
, checkBackend backend key (Just file)
|
2012-01-03 22:39:39 +00:00
|
|
|
, checkKeyNumCopies key file numcopies
|
2011-10-29 20:45:06 +00:00
|
|
|
]
|
2011-10-29 21:49:37 +00:00
|
|
|
|
2012-01-19 19:24:05 +00:00
|
|
|
{- To fsck a remote, the content is retrieved to a tmp file,
|
|
|
|
- and checked locally. -}
|
2014-01-21 21:08:49 +00:00
|
|
|
performRemote :: Key -> FilePath -> Backend -> NumCopies -> Remote -> Annex Bool
|
2012-09-25 19:06:33 +00:00
|
|
|
performRemote key file backend numcopies remote =
|
2012-03-14 21:43:34 +00:00
|
|
|
dispatch =<< Remote.hasKey remote key
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
dispatch (Left err) = do
|
|
|
|
showNote err
|
|
|
|
return False
|
|
|
|
dispatch (Right True) = withtmp $ \tmpfile ->
|
|
|
|
ifM (getfile tmpfile)
|
|
|
|
( go True (Just tmpfile)
|
|
|
|
, go True Nothing
|
|
|
|
)
|
|
|
|
dispatch (Right False) = go False Nothing
|
|
|
|
go present localcopy = check
|
|
|
|
[ verifyLocationLogRemote key file remote present
|
|
|
|
, checkKeySizeRemote key remote localcopy
|
|
|
|
, checkBackendRemote backend key remote localcopy
|
|
|
|
, checkKeyNumCopies key file numcopies
|
|
|
|
]
|
|
|
|
withtmp a = do
|
2014-02-11 19:29:56 +00:00
|
|
|
pid <- liftIO getPID
|
2014-02-26 20:52:56 +00:00
|
|
|
t <- fromRepo gitAnnexTmpObjectDir
|
2012-11-12 05:05:04 +00:00
|
|
|
createAnnexDirectory t
|
2014-02-11 19:29:56 +00:00
|
|
|
let tmp = t </> "fsck" ++ show pid ++ "." ++ keyFile key
|
2012-11-12 05:05:04 +00:00
|
|
|
let cleanup = liftIO $ catchIO (removeFile tmp) (const noop)
|
|
|
|
cleanup
|
|
|
|
cleanup `after` a tmp
|
|
|
|
getfile tmp =
|
|
|
|
ifM (Remote.retrieveKeyFileCheap remote key tmp)
|
|
|
|
( return True
|
|
|
|
, ifM (Annex.getState Annex.fast)
|
|
|
|
( return False
|
2013-04-11 21:15:45 +00:00
|
|
|
, Remote.retrieveKeyFile remote key Nothing tmp dummymeter
|
2012-03-14 21:43:34 +00:00
|
|
|
)
|
2012-11-12 05:05:04 +00:00
|
|
|
)
|
2013-04-11 21:15:45 +00:00
|
|
|
dummymeter _ = noop
|
2012-01-19 19:24:05 +00:00
|
|
|
|
2014-02-20 18:45:17 +00:00
|
|
|
startKey :: Incremental -> Key -> NumCopies -> CommandStart
|
|
|
|
startKey inc key numcopies =
|
|
|
|
case Backend.maybeLookupBackendName (Types.Key.keyBackendName key) of
|
|
|
|
Nothing -> stop
|
|
|
|
Just backend -> runFsck inc (key2file key) key $
|
|
|
|
performKey key backend numcopies
|
2011-10-29 21:49:37 +00:00
|
|
|
|
2014-02-20 18:45:17 +00:00
|
|
|
performKey :: Key -> Backend -> NumCopies -> Annex Bool
|
|
|
|
performKey key backend numcopies = check
|
2012-08-08 20:06:01 +00:00
|
|
|
[ verifyLocationLog key (key2file key)
|
2011-10-29 21:49:37 +00:00
|
|
|
, checkKeySize key
|
2013-04-16 20:17:20 +00:00
|
|
|
, checkBackend backend key Nothing
|
2014-02-20 18:45:17 +00:00
|
|
|
, checkKeyNumCopies key (key2file key) numcopies
|
2011-10-29 21:49:37 +00:00
|
|
|
]
|
|
|
|
|
2012-09-25 19:06:33 +00:00
|
|
|
check :: [Annex Bool] -> Annex Bool
|
2013-09-25 07:09:06 +00:00
|
|
|
check cs = and <$> sequence cs
|
2012-03-10 18:46:21 +00:00
|
|
|
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
{- Checks that the file's link points correctly to the content.
|
2013-01-06 19:42:49 +00:00
|
|
|
-
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
- In direct mode, there is only a link when the content is not present.
|
2013-01-06 19:42:49 +00:00
|
|
|
-}
|
2012-03-10 18:46:21 +00:00
|
|
|
fixLink :: Key -> FilePath -> Annex Bool
|
|
|
|
fixLink key file = do
|
2013-04-04 19:46:33 +00:00
|
|
|
want <- inRepo $ gitAnnexLink file key
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
have <- getAnnexLinkTarget file
|
2013-01-06 19:42:49 +00:00
|
|
|
maybe noop (go want) have
|
|
|
|
return True
|
|
|
|
where
|
2013-06-18 00:51:36 +00:00
|
|
|
go want have
|
2013-06-18 01:18:43 +00:00
|
|
|
| want /= fromInternalGitPath have = do
|
2013-06-18 00:51:36 +00:00
|
|
|
showNote "fixing link"
|
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir file)
|
|
|
|
liftIO $ removeFile file
|
|
|
|
addAnnexLink want file
|
|
|
|
| otherwise = noop
|
2012-03-10 18:46:21 +00:00
|
|
|
|
2011-03-02 18:30:36 +00:00
|
|
|
{- Checks that the location log reflects the current status of the key,
|
2012-12-13 04:45:27 +00:00
|
|
|
- in this repository only. -}
|
2011-10-29 21:49:37 +00:00
|
|
|
verifyLocationLog :: Key -> String -> Annex Bool
|
|
|
|
verifyLocationLog key desc = do
|
2011-03-02 18:30:36 +00:00
|
|
|
present <- inAnnex key
|
2013-01-06 19:42:49 +00:00
|
|
|
direct <- isDirect
|
|
|
|
u <- getUUID
|
2011-03-02 18:30:36 +00:00
|
|
|
|
2013-01-06 19:42:49 +00:00
|
|
|
{- Since we're checking that a key's file is present, throw
|
|
|
|
- in a permission fixup here too. -}
|
2013-11-15 18:52:03 +00:00
|
|
|
file <- calcRepo $ gitAnnexLocation key
|
|
|
|
when (present && not direct) $
|
2012-04-21 18:06:36 +00:00
|
|
|
freezeContent file
|
2013-11-15 18:52:03 +00:00
|
|
|
whenM (liftIO $ doesDirectoryExist $ parentDir file) $
|
2012-04-21 18:06:36 +00:00
|
|
|
freezeContentDir file
|
2011-03-28 20:19:20 +00:00
|
|
|
|
2013-01-06 19:42:49 +00:00
|
|
|
{- In direct mode, modified files will show up as not present,
|
|
|
|
- but that is expected and not something to do anything about. -}
|
2013-09-25 07:09:06 +00:00
|
|
|
if direct && not present
|
2013-01-06 19:42:49 +00:00
|
|
|
then return True
|
|
|
|
else verifyLocationLog' key desc present u (logChange key u)
|
2012-01-19 19:24:05 +00:00
|
|
|
|
|
|
|
verifyLocationLogRemote :: Key -> String -> Remote -> Bool -> Annex Bool
|
|
|
|
verifyLocationLogRemote key desc remote present =
|
|
|
|
verifyLocationLog' key desc present (Remote.uuid remote)
|
|
|
|
(Remote.logStatus remote key)
|
2011-03-02 18:30:36 +00:00
|
|
|
|
2012-01-19 19:24:05 +00:00
|
|
|
verifyLocationLog' :: Key -> String -> Bool -> UUID -> (LogStatus -> Annex ()) -> Annex Bool
|
2013-12-01 19:52:30 +00:00
|
|
|
verifyLocationLog' key desc present u updatestatus = do
|
2012-01-19 19:24:05 +00:00
|
|
|
uuids <- Remote.keyLocations key
|
2011-03-02 18:30:36 +00:00
|
|
|
case (present, u `elem` uuids) of
|
|
|
|
(True, False) -> do
|
2012-01-19 19:24:05 +00:00
|
|
|
fix InfoPresent
|
2011-03-02 18:30:36 +00:00
|
|
|
-- There is no data loss, so do not fail.
|
|
|
|
return True
|
|
|
|
(False, True) -> do
|
2012-01-19 19:24:05 +00:00
|
|
|
fix InfoMissing
|
2011-03-02 18:30:36 +00:00
|
|
|
warning $
|
2011-10-29 21:49:37 +00:00
|
|
|
"** Based on the location log, " ++ desc
|
2011-03-02 18:30:36 +00:00
|
|
|
++ "\n** was expected to be present, " ++
|
|
|
|
"but its content is missing."
|
|
|
|
return False
|
|
|
|
_ -> return True
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
fix s = do
|
|
|
|
showNote "fixing location log"
|
2013-12-01 19:52:30 +00:00
|
|
|
updatestatus s
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2013-01-19 18:11:23 +00:00
|
|
|
{- Ensures the direct mode mapping file is consistent. Each file
|
|
|
|
- it lists for the key should exist, and the specified file should be
|
|
|
|
- included in it.
|
|
|
|
-}
|
|
|
|
verifyDirectMapping :: Key -> FilePath -> Annex Bool
|
|
|
|
verifyDirectMapping key file = do
|
|
|
|
whenM isDirect $ do
|
|
|
|
fs <- addAssociatedFile key file
|
|
|
|
forM_ fs $ \f ->
|
|
|
|
unlessM (liftIO $ doesFileExist f) $
|
|
|
|
void $ removeAssociatedFile key f
|
|
|
|
return True
|
|
|
|
|
2013-06-24 20:26:00 +00:00
|
|
|
{- Ensures that files whose content is available are in direct mode. -}
|
|
|
|
verifyDirectMode :: Key -> FilePath -> Annex Bool
|
|
|
|
verifyDirectMode key file = do
|
2013-09-13 16:50:29 +00:00
|
|
|
whenM (isDirect <&&> isJust <$> isAnnexLink file) $ do
|
2013-06-24 20:26:00 +00:00
|
|
|
v <- toDirectGen key file
|
|
|
|
case v of
|
|
|
|
Nothing -> noop
|
|
|
|
Just a -> do
|
|
|
|
showNote "fixing direct mode"
|
|
|
|
a
|
|
|
|
return True
|
|
|
|
|
2011-07-05 22:31:46 +00:00
|
|
|
{- The size of the data for a key is checked against the size encoded in
|
2013-01-06 19:42:49 +00:00
|
|
|
- the key's metadata, if available.
|
|
|
|
-
|
|
|
|
- Not checked in direct mode, because files can be changed directly.
|
|
|
|
-}
|
2011-07-05 22:31:46 +00:00
|
|
|
checkKeySize :: Key -> Annex Bool
|
2013-01-06 19:42:49 +00:00
|
|
|
checkKeySize key = ifM isDirect
|
|
|
|
( return True
|
|
|
|
, do
|
2013-04-04 19:46:33 +00:00
|
|
|
file <- calcRepo $ gitAnnexLocation key
|
2013-01-06 19:42:49 +00:00
|
|
|
ifM (liftIO $ doesFileExist file)
|
|
|
|
( checkKeySizeOr badContent key file
|
|
|
|
, return True
|
|
|
|
)
|
|
|
|
)
|
2012-01-19 19:24:05 +00:00
|
|
|
|
|
|
|
checkKeySizeRemote :: Key -> Remote -> Maybe FilePath -> Annex Bool
|
|
|
|
checkKeySizeRemote _ _ Nothing = return True
|
2012-09-16 05:17:48 +00:00
|
|
|
checkKeySizeRemote key remote (Just file) =
|
|
|
|
checkKeySizeOr (badContentRemote remote) key file
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2012-09-16 05:17:48 +00:00
|
|
|
checkKeySizeOr :: (Key -> Annex String) -> Key -> FilePath -> Annex Bool
|
|
|
|
checkKeySizeOr bad key file = case Types.Key.keySize key of
|
2012-01-19 19:24:05 +00:00
|
|
|
Nothing -> return True
|
|
|
|
Just size -> do
|
2012-03-14 21:43:34 +00:00
|
|
|
size' <- fromIntegral . fileSize
|
2012-06-12 15:32:06 +00:00
|
|
|
<$> liftIO (getFileStatus file)
|
2012-03-14 21:43:34 +00:00
|
|
|
comparesizes size size'
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
comparesizes a b = do
|
|
|
|
let same = a == b
|
|
|
|
unless same $ badsize a b
|
|
|
|
return same
|
|
|
|
badsize a b = do
|
|
|
|
msg <- bad key
|
|
|
|
warning $ concat
|
|
|
|
[ "Bad file size ("
|
|
|
|
, compareSizes storageUnits True a b
|
|
|
|
, "); "
|
|
|
|
, msg
|
|
|
|
]
|
2011-07-05 22:31:46 +00:00
|
|
|
|
2013-01-06 19:42:49 +00:00
|
|
|
{- Runs the backend specific check on a key's content.
|
|
|
|
-
|
2013-01-08 16:41:09 +00:00
|
|
|
- In direct mode this is not done if the file has clearly been modified,
|
|
|
|
- because modification of direct mode files is allowed. It's still done
|
|
|
|
- if the file does not appear modified, to catch disk corruption, etc.
|
|
|
|
-}
|
2013-04-16 20:17:20 +00:00
|
|
|
checkBackend :: Backend -> Key -> Maybe FilePath -> Annex Bool
|
|
|
|
checkBackend backend key mfile = go =<< isDirect
|
|
|
|
where
|
|
|
|
go False = do
|
|
|
|
content <- calcRepo $ gitAnnexLocation key
|
|
|
|
checkBackendOr badContent backend key content
|
|
|
|
go True = maybe nocheck checkdirect mfile
|
|
|
|
checkdirect file = ifM (goodContent key file)
|
|
|
|
( checkBackendOr' (badContentDirect file) backend key file
|
|
|
|
(goodContent key file)
|
|
|
|
, nocheck
|
2013-01-08 16:41:09 +00:00
|
|
|
)
|
2013-04-16 20:17:20 +00:00
|
|
|
nocheck = return True
|
2012-01-19 19:24:05 +00:00
|
|
|
|
|
|
|
checkBackendRemote :: Backend -> Key -> Remote -> Maybe FilePath -> Annex Bool
|
2012-09-16 05:17:48 +00:00
|
|
|
checkBackendRemote backend key remote = maybe (return True) go
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2013-09-25 07:09:06 +00:00
|
|
|
go = checkBackendOr (badContentRemote remote) backend key
|
2012-01-19 19:24:05 +00:00
|
|
|
|
2012-09-16 05:17:48 +00:00
|
|
|
checkBackendOr :: (Key -> Annex String) -> Backend -> Key -> FilePath -> Annex Bool
|
|
|
|
checkBackendOr bad backend key file =
|
2013-01-08 19:07:00 +00:00
|
|
|
checkBackendOr' bad backend key file (return True)
|
|
|
|
|
|
|
|
checkBackendOr' :: (Key -> Annex String) -> Backend -> Key -> FilePath -> Annex Bool -> Annex Bool
|
|
|
|
checkBackendOr' bad backend key file postcheck =
|
2012-09-16 05:17:48 +00:00
|
|
|
case Types.Backend.fsckKey backend of
|
|
|
|
Nothing -> return True
|
|
|
|
Just a -> do
|
|
|
|
ok <- a key file
|
2013-01-08 19:07:00 +00:00
|
|
|
ifM postcheck
|
|
|
|
( do
|
|
|
|
unless ok $ do
|
|
|
|
msg <- bad key
|
|
|
|
warning $ "Bad file content; " ++ msg
|
|
|
|
return ok
|
|
|
|
, return True
|
|
|
|
)
|
2011-10-31 16:33:41 +00:00
|
|
|
|
2014-02-20 18:45:17 +00:00
|
|
|
checkKeyNumCopies :: Key -> String -> NumCopies -> Annex Bool
|
2011-07-05 22:31:46 +00:00
|
|
|
checkKeyNumCopies key file numcopies = do
|
2012-01-10 17:11:16 +00:00
|
|
|
(untrustedlocations, safelocations) <- trustPartition UnTrusted =<< Remote.keyLocations key
|
2014-01-21 20:08:19 +00:00
|
|
|
let present = NumCopies (length safelocations)
|
2014-01-21 21:08:49 +00:00
|
|
|
if present < numcopies
|
2011-07-05 22:31:46 +00:00
|
|
|
then do
|
2011-09-01 20:02:01 +00:00
|
|
|
ppuuids <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
|
2014-01-21 21:08:49 +00:00
|
|
|
warning $ missingNote file present numcopies ppuuids
|
2011-07-05 22:31:46 +00:00
|
|
|
return False
|
|
|
|
else return True
|
|
|
|
|
2014-01-21 20:08:19 +00:00
|
|
|
missingNote :: String -> NumCopies -> NumCopies -> String -> String
|
|
|
|
missingNote file (NumCopies 0) _ [] =
|
2011-07-05 22:31:46 +00:00
|
|
|
"** No known copies exist of " ++ file
|
2014-01-21 20:08:19 +00:00
|
|
|
missingNote file (NumCopies 0) _ untrusted =
|
2011-07-05 22:31:46 +00:00
|
|
|
"Only these untrusted locations may have copies of " ++ file ++
|
|
|
|
"\n" ++ untrusted ++
|
|
|
|
"Back it up to trusted locations with git-annex copy."
|
|
|
|
missingNote file present needed [] =
|
2014-01-21 20:08:19 +00:00
|
|
|
"Only " ++ show (fromNumCopies present) ++ " of " ++ show (fromNumCopies needed) ++
|
2011-07-05 22:31:46 +00:00
|
|
|
" trustworthy copies exist of " ++ file ++
|
|
|
|
"\nBack it up with git-annex copy."
|
|
|
|
missingNote file present needed untrusted =
|
|
|
|
missingNote file present needed [] ++
|
|
|
|
"\nThe following untrusted locations may also have copies: " ++
|
|
|
|
"\n" ++ untrusted
|
2012-01-19 19:24:05 +00:00
|
|
|
|
|
|
|
{- Bad content is moved aside. -}
|
|
|
|
badContent :: Key -> Annex String
|
|
|
|
badContent key = do
|
2013-01-07 17:01:53 +00:00
|
|
|
dest <- moveBad key
|
2012-01-19 19:24:05 +00:00
|
|
|
return $ "moved to " ++ dest
|
|
|
|
|
2013-01-08 19:07:00 +00:00
|
|
|
{- Bad content is left where it is, but we touch the file, so it'll be
|
|
|
|
- committed to a new key. -}
|
|
|
|
badContentDirect :: FilePath -> Key -> Annex String
|
|
|
|
badContentDirect file key = do
|
|
|
|
void $ liftIO $ catchMaybeIO $ touchFile file
|
|
|
|
logStatus key InfoMissing
|
2013-09-25 07:09:06 +00:00
|
|
|
return "left in place for you to examine"
|
2013-01-08 19:07:00 +00:00
|
|
|
|
2012-01-19 19:24:05 +00:00
|
|
|
badContentRemote :: Remote -> Key -> Annex String
|
|
|
|
badContentRemote remote key = do
|
|
|
|
ok <- Remote.removeKey remote key
|
bugfix: drop --from an unavailable remote no longer updates the location log, incorrectly, to say the remote does not have the key.
The comments correctly noted that the remote could drop the key and
yet False be returned due to some problem that occurred afterwards.
For example, if it's a network remote, it could drop the key just
as the network goes down, and so things timeout and a nonzero exit
from ssh is propigated through and False returned.
However... Most of the time, this scenario will not have happened.
False will mean the remote was not available or could not drop the key
at all.
So, instead of assuming the worst, just trust the status we have.
If we get it wrong, and the scenario above happened, our location
log will think the remote has the key. But the remote's location
log (assuming it has one) will know it dropped it, and the next sync
will regain consistency.
For a special remote, with no location log, our location log will be wrong,
but this is no different than the situation where someone else dropped
the key from the remote and we've not synced with them. The standard
paranoia about not trusting the location log to be the last word about
whether a remote has a key will save us from these situations. Ie,
if we try to drop the file, we'll actively check the remote,
and determine the inconsistency then.
2013-03-10 23:15:53 +00:00
|
|
|
when ok $
|
|
|
|
Remote.logStatus remote key InfoMissing
|
2012-01-19 19:24:05 +00:00
|
|
|
return $ (if ok then "dropped from " else "failed to drop from ")
|
|
|
|
++ Remote.name remote
|
2012-09-25 17:22:12 +00:00
|
|
|
|
2012-09-25 19:45:17 +00:00
|
|
|
data Incremental = StartIncremental | ContIncremental (Maybe EpochTime) | NonIncremental
|
2014-02-20 19:56:45 +00:00
|
|
|
deriving (Eq, Show)
|
2012-09-25 19:06:33 +00:00
|
|
|
|
|
|
|
runFsck :: Incremental -> FilePath -> Key -> Annex Bool -> CommandStart
|
2012-09-25 19:45:17 +00:00
|
|
|
runFsck inc file key a = ifM (needFsck inc key)
|
|
|
|
( do
|
|
|
|
showStart "fsck" file
|
|
|
|
next $ do
|
|
|
|
ok <- a
|
|
|
|
when ok $
|
|
|
|
recordFsckTime key
|
|
|
|
next $ return ok
|
|
|
|
, stop
|
|
|
|
)
|
2012-09-25 19:06:33 +00:00
|
|
|
|
|
|
|
{- Check if a key needs to be fscked, with support for incremental fscks. -}
|
2012-09-25 19:45:17 +00:00
|
|
|
needFsck :: Incremental -> Key -> Annex Bool
|
|
|
|
needFsck (ContIncremental Nothing) _ = return True
|
|
|
|
needFsck (ContIncremental starttime) key = do
|
2012-09-25 19:06:33 +00:00
|
|
|
fscktime <- getFsckTime key
|
|
|
|
return $ fscktime < starttime
|
2012-09-25 19:45:17 +00:00
|
|
|
needFsck _ _ = return True
|
2012-09-25 19:06:33 +00:00
|
|
|
|
|
|
|
{- To record the time that a key was last fscked, without
|
2012-09-25 18:16:34 +00:00
|
|
|
- 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
|
2012-09-25 19:06:33 +00:00
|
|
|
- is dropped. That way, if it's later added back, the fsck record
|
2012-09-25 18:16:34 +00:00
|
|
|
- won't still be present.
|
|
|
|
-}
|
2012-09-25 19:06:33 +00:00
|
|
|
recordFsckTime :: Key -> Annex ()
|
|
|
|
recordFsckTime key = do
|
2013-04-04 19:46:33 +00:00
|
|
|
parent <- parentDir <$> calcRepo (gitAnnexLocation key)
|
2012-09-25 19:06:33 +00:00
|
|
|
liftIO $ void $ tryIO $ do
|
|
|
|
touchFile parent
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2012-09-25 19:06:33 +00:00
|
|
|
setSticky parent
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2012-09-25 19:06:33 +00:00
|
|
|
|
|
|
|
getFsckTime :: Key -> Annex (Maybe EpochTime)
|
|
|
|
getFsckTime key = do
|
2013-04-04 19:46:33 +00:00
|
|
|
parent <- parentDir <$> calcRepo (gitAnnexLocation key)
|
2012-09-25 19:06:33 +00:00
|
|
|
liftIO $ catchDefaultIO Nothing $ do
|
|
|
|
s <- getFileStatus parent
|
|
|
|
return $ if isSticky $ fileMode s
|
|
|
|
then Just $ modificationTime s
|
|
|
|
else Nothing
|
2012-09-25 18:16:34 +00:00
|
|
|
|
2013-05-19 18:46:48 +00:00
|
|
|
{- Records the start time of an incremental fsck.
|
2012-09-25 18:16:34 +00:00
|
|
|
-
|
|
|
|
- To guard against time stamp damange (for example, if an annex directory
|
|
|
|
- is copied without -a), the fsckstate file contains a time that should
|
2014-02-13 16:40:10 +00:00
|
|
|
- be identical to its modification time.
|
2014-02-25 18:09:39 +00:00
|
|
|
- (This is not possible to do on Windows, and so the timestamp in
|
|
|
|
- the file will only be equal or greater than the modification time.)
|
2014-02-13 16:40:10 +00:00
|
|
|
-}
|
2012-09-25 19:45:17 +00:00
|
|
|
recordStartTime :: Annex ()
|
2012-09-25 18:16:34 +00:00
|
|
|
recordStartTime = do
|
|
|
|
f <- fromRepo gitAnnexFsckState
|
2012-09-25 19:06:33 +00:00
|
|
|
createAnnexDirectory $ parentDir f
|
2012-09-25 18:16:34 +00:00
|
|
|
liftIO $ do
|
|
|
|
nukeFile f
|
2014-02-03 14:16:05 +00:00
|
|
|
withFile f WriteMode $ \h -> do
|
2014-02-13 16:40:10 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2014-02-03 14:16:05 +00:00
|
|
|
t <- modificationTime <$> getFileStatus f
|
2014-02-13 16:40:10 +00:00
|
|
|
#else
|
2014-02-25 18:09:39 +00:00
|
|
|
t <- getPOSIXTime
|
2014-02-13 16:40:10 +00:00
|
|
|
#endif
|
2014-02-25 18:09:39 +00:00
|
|
|
hPutStr h $ showTime $ realToFrac t
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
showTime :: POSIXTime -> String
|
|
|
|
showTime = show
|
2012-09-25 18:16:34 +00:00
|
|
|
|
2012-09-25 23:37:34 +00:00
|
|
|
resetStartTime :: Annex ()
|
|
|
|
resetStartTime = liftIO . nukeFile =<< fromRepo gitAnnexFsckState
|
|
|
|
|
2012-09-25 18:16:34 +00:00
|
|
|
{- Gets the incremental fsck start time. -}
|
|
|
|
getStartTime :: Annex (Maybe EpochTime)
|
|
|
|
getStartTime = do
|
|
|
|
f <- fromRepo gitAnnexFsckState
|
|
|
|
liftIO $ catchDefaultIO Nothing $ do
|
|
|
|
timestamp <- modificationTime <$> getFileStatus f
|
2014-02-25 18:09:39 +00:00
|
|
|
let fromstatus = Just (realToFrac timestamp)
|
|
|
|
fromfile <- readishTime <$> readFile f
|
|
|
|
return $ if matchingtimestamp fromfile fromstatus
|
2012-09-25 18:16:34 +00:00
|
|
|
then Just timestamp
|
|
|
|
else Nothing
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
readishTime :: String -> Maybe POSIXTime
|
|
|
|
readishTime s = utcTimeToPOSIXSeconds <$>
|
|
|
|
parseTime defaultTimeLocale "%s%Qs" s
|
2014-02-25 18:09:39 +00:00
|
|
|
matchingtimestamp fromfile fromstatus =
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
fromfile == fromstatus
|
|
|
|
#else
|
|
|
|
fromfile >= fromstatus
|
|
|
|
#endif
|