2010-11-06 21:06:19 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2016-02-14 21:27:50 +00:00
|
|
|
- Copyright 2010-2016 Joey Hess <id@joeyh.name>
|
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
|
|
|
|
|
|
|
|
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
|
2011-10-29 21:49:37 +00:00
|
|
|
import qualified Backend
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2016-02-14 20:52:43 +00:00
|
|
|
import qualified Annex.Content.Direct as 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
|
2015-04-05 16:50:02 +00:00
|
|
|
import Logs.Activity
|
2015-05-10 18:45:55 +00:00
|
|
|
import Logs.TimeStamp
|
2015-04-30 18:02:56 +00:00
|
|
|
import Annex.NumCopies
|
2011-10-15 21:47:03 +00:00
|
|
|
import Annex.UUID
|
2016-02-14 21:27:50 +00:00
|
|
|
import Annex.ReplaceFile
|
2011-07-06 00:36:43 +00:00
|
|
|
import Utility.DataUnits
|
2011-07-05 22:31:46 +00:00
|
|
|
import Config
|
2012-09-25 23:37:34 +00:00
|
|
|
import Utility.HumanTime
|
2015-04-18 18:13:07 +00:00
|
|
|
import Utility.CopyFile
|
2013-06-18 01:30:52 +00:00
|
|
|
import Git.FilePath
|
2014-02-11 19:29:56 +00:00
|
|
|
import Utility.PID
|
2015-12-11 20:05:56 +00:00
|
|
|
import qualified Database.Keys
|
2015-02-16 19:08:29 +00:00
|
|
|
import qualified Database.Fsck as FsckDb
|
2015-07-25 21:37:09 +00:00
|
|
|
import Types.CleanupActions
|
2010-11-06 21:06:19 +00:00
|
|
|
|
2012-09-25 18:16:34 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
|
|
|
import System.Posix.Types (EpochTime)
|
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2015-11-04 20:26:21 +00:00
|
|
|
cmd = withGlobalOptions (jobsOption : annexedMatchingOptions) $
|
2015-07-10 17:18:46 +00:00
|
|
|
command "fsck" SectionMaintenance
|
|
|
|
"find and fix problems"
|
|
|
|
paramPaths (seek <$$> optParser)
|
2015-07-08 20:58:54 +00:00
|
|
|
|
|
|
|
data FsckOptions = FsckOptions
|
|
|
|
{ fsckFiles :: CmdParams
|
2015-07-09 20:05:45 +00:00
|
|
|
, fsckFromOption :: Maybe (DeferredParse Remote)
|
2015-07-09 16:26:25 +00:00
|
|
|
, incrementalOpt :: Maybe IncrementalOpt
|
2015-07-09 16:44:03 +00:00
|
|
|
, keyOptions :: Maybe KeyOptions
|
2015-07-08 20:58:54 +00:00
|
|
|
}
|
|
|
|
|
2015-07-09 16:26:25 +00:00
|
|
|
data IncrementalOpt
|
|
|
|
= StartIncrementalO
|
|
|
|
| MoreIncrementalO
|
|
|
|
| ScheduleIncrementalO Duration
|
|
|
|
|
2015-07-08 20:58:54 +00:00
|
|
|
optParser :: CmdParamsDesc -> Parser FsckOptions
|
|
|
|
optParser desc = FsckOptions
|
|
|
|
<$> cmdParams desc
|
2015-07-09 20:05:45 +00:00
|
|
|
<*> optional (parseRemoteOption $ strOption
|
2015-07-09 14:41:17 +00:00
|
|
|
( long "from" <> short 'f' <> metavar paramRemote
|
2015-07-08 20:58:54 +00:00
|
|
|
<> help "check remote"
|
2015-09-14 17:19:04 +00:00
|
|
|
<> completeRemotes
|
2015-07-08 20:58:54 +00:00
|
|
|
))
|
2015-07-09 16:26:25 +00:00
|
|
|
<*> optional parseincremental
|
2015-07-09 16:44:03 +00:00
|
|
|
<*> optional (parseKeyOptions False)
|
2015-07-09 16:26:25 +00:00
|
|
|
where
|
|
|
|
parseincremental =
|
|
|
|
flag' StartIncrementalO
|
|
|
|
( long "incremental" <> short 'S'
|
|
|
|
<> help "start an incremental fsck"
|
|
|
|
)
|
|
|
|
<|> flag' MoreIncrementalO
|
|
|
|
( long "more" <> short 'm'
|
|
|
|
<> help "continue an incremental fsck"
|
|
|
|
)
|
|
|
|
<|> (ScheduleIncrementalO <$> option (str >>= parseDuration)
|
|
|
|
( long "incremental-schedule" <> metavar paramTime
|
|
|
|
<> help "schedule incremental fscking"
|
|
|
|
))
|
2015-07-08 20:58:54 +00:00
|
|
|
|
|
|
|
seek :: FsckOptions -> CommandSeek
|
2015-11-04 20:26:21 +00:00
|
|
|
seek o = allowConcurrentOutput $ do
|
2015-07-09 20:05:45 +00:00
|
|
|
from <- maybe (pure Nothing) (Just <$$> getParsed) (fsckFromOption o)
|
2015-02-17 21:08:11 +00:00
|
|
|
u <- maybe getUUID (pure . Remote.uuid) from
|
2015-11-10 18:44:58 +00:00
|
|
|
checkDeadRepo u
|
2015-07-09 16:26:25 +00:00
|
|
|
i <- prepIncremental u (incrementalOpt o)
|
2015-07-08 21:59:06 +00:00
|
|
|
withKeyOptions (keyOptions o) False
|
2015-04-05 16:50:02 +00:00
|
|
|
(\k -> startKey i k =<< getNumCopies)
|
|
|
|
(withFilesInGit $ whenAnnexed $ start from i)
|
2015-07-08 20:58:54 +00:00
|
|
|
(fsckFiles o)
|
2015-07-25 21:37:09 +00:00
|
|
|
cleanupIncremental i
|
2015-05-06 18:45:20 +00:00
|
|
|
void $ tryIO $ recordActivity Fsck u
|
2010-11-15 22:22:50 +00:00
|
|
|
|
2015-11-10 18:44:58 +00:00
|
|
|
checkDeadRepo :: UUID -> Annex ()
|
|
|
|
checkDeadRepo u =
|
|
|
|
whenM ((==) DeadTrusted <$> lookupTrust u) $
|
|
|
|
earlyWarning "Warning: Fscking a repository that is currently marked as dead."
|
|
|
|
|
2015-04-05 16:50:02 +00:00
|
|
|
start :: Maybe Remote -> Incremental -> FilePath -> Key -> CommandStart
|
|
|
|
start from inc file key = do
|
2014-04-17 22:03:39 +00:00
|
|
|
v <- Backend.getBackend file key
|
|
|
|
case v of
|
|
|
|
Nothing -> stop
|
|
|
|
Just backend -> do
|
|
|
|
numcopies <- getFileNumCopies file
|
|
|
|
case from of
|
2015-04-05 16:50:02 +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
|
|
|
|
2015-04-05 16:50:02 +00:00
|
|
|
perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool
|
2015-12-11 20:05:56 +00:00
|
|
|
perform key file backend numcopies = do
|
2016-02-14 21:09:54 +00:00
|
|
|
keystatus <- getKeyFileStatus key file
|
2015-12-11 20:05:56 +00:00
|
|
|
check
|
|
|
|
-- order matters
|
|
|
|
[ fixLink key file
|
|
|
|
, verifyLocationLog key keystatus file
|
2016-02-14 21:09:54 +00:00
|
|
|
, verifyAssociatedFiles key keystatus file
|
2016-02-14 21:27:50 +00:00
|
|
|
, verifyWorkTree key file
|
2015-12-11 20:05:56 +00:00
|
|
|
, checkKeySize key keystatus
|
|
|
|
, checkBackend backend key keystatus (Just file)
|
|
|
|
, checkKeyNumCopies key (Just file) numcopies
|
|
|
|
]
|
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. -}
|
2015-04-05 16:50:02 +00:00
|
|
|
performRemote :: Key -> FilePath -> Backend -> NumCopies -> Remote -> Annex Bool
|
|
|
|
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
|
2015-04-27 21:40:21 +00:00
|
|
|
dispatch (Right True) = withtmp $ \tmpfile -> do
|
|
|
|
r <- getfile tmpfile
|
|
|
|
case r of
|
|
|
|
Nothing -> go True Nothing
|
|
|
|
Just True -> go True (Just tmpfile)
|
|
|
|
Just False -> do
|
2015-02-10 17:10:58 +00:00
|
|
|
warning "failed to download file from remote"
|
2015-02-12 20:03:59 +00:00
|
|
|
void $ go True Nothing
|
2015-02-10 17:10:58 +00:00
|
|
|
return False
|
2012-11-12 05:05:04 +00:00
|
|
|
dispatch (Right False) = go False Nothing
|
|
|
|
go present localcopy = check
|
|
|
|
[ verifyLocationLogRemote key file remote present
|
|
|
|
, checkKeySizeRemote key remote localcopy
|
|
|
|
, checkBackendRemote backend key remote localcopy
|
2015-06-09 18:08:57 +00:00
|
|
|
, checkKeyNumCopies key (Just file) numcopies
|
2012-11-12 05:05:04 +00:00
|
|
|
]
|
|
|
|
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
|
2015-12-11 17:50:27 +00:00
|
|
|
getfile tmp = ifM (checkDiskSpace (Just (takeDirectory tmp)) key 0 True)
|
2015-05-12 17:23:22 +00:00
|
|
|
( ifM (Remote.retrieveKeyFileCheap remote key (Just file) tmp)
|
2015-04-27 21:40:21 +00:00
|
|
|
( return (Just True)
|
2012-11-12 05:05:04 +00:00
|
|
|
, ifM (Annex.getState Annex.fast)
|
2015-04-27 21:40:21 +00:00
|
|
|
( return Nothing
|
other 80% of avoding verification when hard linking to objects in shared repo
In c6632ee5c8e66c26ef18317f56ae02bae1e7e280, it actually only handled
uploading objects to a shared repository. To avoid verification when
downloading objects from a shared repository, was a lot harder.
On the plus side, if the process of downloading a file from a remote
is able to verify its content on the side, the remote can indicate this
now, and avoid the extra post-download verification.
As of yet, I don't have any remotes (except Git) using this ability.
Some more work would be needed to support it in special remotes.
It would make sense for tahoe to implicitly verify things downloaded from it;
as long as you trust your tahoe server (which typically runs locally),
there's cryptographic integrity. OTOH, despite bup being based on shas,
a bup repo under an attacker's control could have the git ref used for an
object changed, and so a bup repo shouldn't implicitly verify. Indeed,
tahoe seems unique in being trustworthy enough to implicitly verify.
2015-10-02 17:56:42 +00:00
|
|
|
, Just . fst <$>
|
2015-04-27 21:40:21 +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
|
|
|
)
|
2015-04-27 21:40:21 +00:00
|
|
|
, return (Just False)
|
2015-04-18 18:23:34 +00:00
|
|
|
)
|
2013-04-11 21:15:45 +00:00
|
|
|
dummymeter _ = noop
|
2012-01-19 19:24:05 +00:00
|
|
|
|
2015-04-05 16:50:02 +00:00
|
|
|
startKey :: Incremental -> Key -> NumCopies -> CommandStart
|
|
|
|
startKey inc key numcopies =
|
2016-01-20 20:36:33 +00:00
|
|
|
case Backend.maybeLookupBackendName (keyBackendName key) of
|
2014-02-20 18:45:17 +00:00
|
|
|
Nothing -> stop
|
|
|
|
Just backend -> runFsck inc (key2file key) key $
|
2015-04-05 16:50:02 +00:00
|
|
|
performKey key backend numcopies
|
2011-10-29 21:49:37 +00:00
|
|
|
|
2015-04-05 16:50:02 +00:00
|
|
|
performKey :: Key -> Backend -> NumCopies -> Annex Bool
|
2015-12-11 20:05:56 +00:00
|
|
|
performKey key backend numcopies = do
|
|
|
|
keystatus <- getKeyStatus key
|
|
|
|
check
|
|
|
|
[ verifyLocationLog key keystatus (key2file key)
|
|
|
|
, checkKeySize key keystatus
|
|
|
|
, checkBackend backend key keystatus Nothing
|
|
|
|
, checkKeyNumCopies key Nothing 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
|
|
|
|
2015-12-11 20:05:56 +00:00
|
|
|
{- Checks that symlinks points correctly to the annexed content.
|
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
|
2015-01-27 21:38:06 +00:00
|
|
|
want <- calcRepo $ 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"
|
2015-01-09 17:11:56 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True (parentDir file)
|
2013-06-18 00:51:36 +00:00
|
|
|
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. -}
|
2015-12-11 20:05:56 +00:00
|
|
|
verifyLocationLog :: Key -> KeyStatus -> String -> Annex Bool
|
|
|
|
verifyLocationLog key keystatus desc = do
|
|
|
|
obj <- calcRepo $ gitAnnexLocation key
|
|
|
|
present <- if isKeyUnlocked keystatus
|
|
|
|
then liftIO (doesFileExist obj)
|
|
|
|
else inAnnex key
|
2013-01-06 19:42:49 +00:00
|
|
|
direct <- isDirect
|
|
|
|
u <- getUUID
|
2011-03-02 18:30:36 +00:00
|
|
|
|
2015-12-11 20:05:56 +00:00
|
|
|
{- Since we're checking that a key's object file is present, throw
|
2013-01-06 19:42:49 +00:00
|
|
|
- in a permission fixup here too. -}
|
2015-12-11 20:05:56 +00:00
|
|
|
when (present && not direct) $ void $ tryIO $
|
|
|
|
if isKeyUnlocked keystatus
|
|
|
|
then thawContent obj
|
|
|
|
else freezeContent obj
|
|
|
|
whenM (liftIO $ doesDirectoryExist $ parentDir obj) $
|
|
|
|
freezeContentDir obj
|
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
|
2015-11-10 17:59:04 +00:00
|
|
|
uuids <- loggedLocations 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
|
|
|
|
2016-02-14 20:52:43 +00:00
|
|
|
{- Verifies the associated file records. -}
|
2016-02-14 21:09:54 +00:00
|
|
|
verifyAssociatedFiles :: Key -> KeyStatus -> FilePath -> Annex Bool
|
|
|
|
verifyAssociatedFiles key keystatus file = do
|
2016-02-14 20:52:43 +00:00
|
|
|
ifM isDirect (godirect, goindirect)
|
|
|
|
return True
|
|
|
|
where
|
|
|
|
godirect = do
|
|
|
|
fs <- Direct.addAssociatedFile key file
|
2013-01-19 18:11:23 +00:00
|
|
|
forM_ fs $ \f ->
|
|
|
|
unlessM (liftIO $ doesFileExist f) $
|
2016-02-14 20:52:43 +00:00
|
|
|
void $ Direct.removeAssociatedFile key f
|
2016-02-14 21:09:54 +00:00
|
|
|
goindirect = case keystatus of
|
|
|
|
KeyUnlocked -> do
|
|
|
|
f <- inRepo $ toTopFilePath file
|
|
|
|
afs <- Database.Keys.getAssociatedFiles key
|
|
|
|
unless (getTopFilePath f `elem` map getTopFilePath afs) $
|
|
|
|
Database.Keys.addAssociatedFile key f
|
|
|
|
_ -> return ()
|
2013-01-19 18:11:23 +00:00
|
|
|
|
2016-02-14 21:27:50 +00:00
|
|
|
verifyWorkTree :: Key -> FilePath -> Annex Bool
|
|
|
|
verifyWorkTree key file = do
|
|
|
|
ifM isDirect ( godirect, goindirect )
|
|
|
|
return True
|
|
|
|
where
|
|
|
|
{- Ensures that files whose content is available are in direct mode. -}
|
|
|
|
godirect = whenM (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
|
2016-02-14 21:27:50 +00:00
|
|
|
{- Make sure that a pointer file is replaced with its content,
|
|
|
|
- when the content is available. -}
|
|
|
|
goindirect = do
|
|
|
|
mk <- liftIO $ isPointerFile file
|
|
|
|
case mk of
|
|
|
|
Just k | k == key -> whenM (inAnnex key) $ do
|
|
|
|
showNote "fixing worktree content"
|
|
|
|
replaceFile file $ \tmp ->
|
|
|
|
ifM (annexThin <$> Annex.getGitConfig)
|
|
|
|
( void $ linkFromAnnex key tmp
|
|
|
|
, do
|
|
|
|
obj <- calcRepo $ gitAnnexLocation key
|
|
|
|
void $ checkedCopyFile key obj tmp
|
|
|
|
thawContent tmp
|
|
|
|
)
|
|
|
|
Database.Keys.storeInodeCaches key [file]
|
|
|
|
_ -> return ()
|
2013-06-24 20:26:00 +00:00
|
|
|
|
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.
|
|
|
|
-
|
2015-12-11 20:05:56 +00:00
|
|
|
- Not checked when a file is unlocked, or in direct mode.
|
2014-10-09 19:09:26 +00:00
|
|
|
-}
|
2015-12-11 20:05:56 +00:00
|
|
|
checkKeySize :: Key -> KeyStatus -> Annex Bool
|
|
|
|
checkKeySize _ KeyUnlocked = return True
|
2015-12-15 20:10:48 +00:00
|
|
|
checkKeySize key _ = do
|
2015-12-15 18:27:20 +00:00
|
|
|
file <- calcRepo $ gitAnnexLocation key
|
|
|
|
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) =
|
2015-04-18 18:13:07 +00:00
|
|
|
checkKeySizeOr (badContentRemote remote file) 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
|
2016-01-20 20:36:33 +00:00
|
|
|
checkKeySizeOr bad key file = case keySize key of
|
2012-01-19 19:24:05 +00:00
|
|
|
Nothing -> return True
|
|
|
|
Just size -> do
|
2015-01-20 20:58:48 +00:00
|
|
|
size' <- liftIO $ getFileSize 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
|
|
|
|
2015-12-11 20:05:56 +00:00
|
|
|
{- Runs the backend specific check on a key's content object.
|
|
|
|
-
|
|
|
|
- When a file is unlocked, it may be a hard link to the object,
|
|
|
|
- thus when the user modifies the file, the object will be modified and
|
|
|
|
- not pass the check, and we don't want to find an error in this case.
|
|
|
|
- So, skip the check if the key is unlocked and modified.
|
2013-01-06 19:42:49 +00:00
|
|
|
-
|
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.
|
|
|
|
-}
|
2015-12-11 20:05:56 +00:00
|
|
|
checkBackend :: Backend -> Key -> KeyStatus -> Maybe FilePath -> Annex Bool
|
|
|
|
checkBackend backend key keystatus mfile = go =<< isDirect
|
2013-04-16 20:17:20 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
go False = do
|
2013-04-16 20:17:20 +00:00
|
|
|
content <- calcRepo $ gitAnnexLocation key
|
2015-12-11 20:05:56 +00:00
|
|
|
ifM (pure (isKeyUnlocked keystatus) <&&> (not <$> isUnmodified key content))
|
|
|
|
( nocheck
|
|
|
|
, checkBackendOr badContent backend key content
|
|
|
|
)
|
2013-04-16 20:17:20 +00:00
|
|
|
go True = maybe nocheck checkdirect mfile
|
2016-02-14 20:52:43 +00:00
|
|
|
checkdirect file = ifM (Direct.goodContent key file)
|
2013-04-16 20:17:20 +00:00
|
|
|
( checkBackendOr' (badContentDirect file) backend key file
|
2016-02-14 20:52:43 +00:00
|
|
|
(Direct.goodContent key file)
|
2013-04-16 20:17:20 +00:00
|
|
|
, 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
|
2015-04-18 18:13:07 +00:00
|
|
|
go file = checkBackendOr (badContentRemote remote file) backend key file
|
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)
|
|
|
|
|
2015-10-01 17:28:49 +00:00
|
|
|
-- The postcheck action is run after the content is verified,
|
|
|
|
-- in order to detect situations where the file is changed while being
|
|
|
|
-- verified (particularly in direct mode).
|
2013-01-08 19:07:00 +00:00
|
|
|
checkBackendOr' :: (Key -> Annex String) -> Backend -> Key -> FilePath -> Annex Bool -> Annex Bool
|
|
|
|
checkBackendOr' bad backend key file postcheck =
|
2015-10-01 17:28:49 +00:00
|
|
|
case Types.Backend.verifyKeyContent backend of
|
2012-09-16 05:17:48 +00:00
|
|
|
Nothing -> return True
|
2015-10-01 17:28:49 +00:00
|
|
|
Just verifier -> do
|
|
|
|
ok <- verifier 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
|
|
|
|
2015-06-09 18:08:57 +00:00
|
|
|
checkKeyNumCopies :: Key -> AssociatedFile -> NumCopies -> Annex Bool
|
|
|
|
checkKeyNumCopies key afile numcopies = do
|
|
|
|
let file = fromMaybe (key2file key) afile
|
2016-02-19 19:12:11 +00:00
|
|
|
locs <- loggedLocations key
|
|
|
|
(untrustedlocations, otherlocations) <- trustPartition UnTrusted locs
|
|
|
|
(deadlocations, safelocations) <- trustPartition DeadTrusted otherlocations
|
2014-01-21 20:08:19 +00:00
|
|
|
let present = NumCopies (length safelocations)
|
2014-01-21 21:08:49 +00:00
|
|
|
if present < numcopies
|
2015-06-09 18:08:57 +00:00
|
|
|
then ifM (pure (isNothing afile) <&&> checkDead key)
|
|
|
|
( do
|
|
|
|
showLongNote $ "This key is dead, skipping."
|
|
|
|
return True
|
|
|
|
, do
|
2016-02-19 19:12:11 +00:00
|
|
|
untrusted <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
|
|
|
|
dead <- Remote.prettyPrintUUIDs "dead" deadlocations
|
|
|
|
warning $ missingNote file present numcopies untrusted dead
|
2015-06-09 19:12:40 +00:00
|
|
|
when (fromNumCopies present == 0 && isNothing afile) $
|
|
|
|
showLongNote "(Avoid this check by running: git annex dead --key )"
|
2015-06-09 18:08:57 +00:00
|
|
|
return False
|
|
|
|
)
|
2011-07-05 22:31:46 +00:00
|
|
|
else return True
|
|
|
|
|
2016-02-19 19:12:11 +00:00
|
|
|
missingNote :: String -> NumCopies -> NumCopies -> String -> String -> String
|
|
|
|
missingNote file (NumCopies 0) _ [] dead =
|
|
|
|
"** No known copies exist of " ++ file ++ honorDead dead
|
|
|
|
missingNote file (NumCopies 0) _ untrusted dead =
|
2011-07-05 22:31:46 +00:00
|
|
|
"Only these untrusted locations may have copies of " ++ file ++
|
|
|
|
"\n" ++ untrusted ++
|
2016-02-19 19:12:11 +00:00
|
|
|
"Back it up to trusted locations with git-annex copy." ++ honorDead dead
|
|
|
|
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."
|
2016-02-19 19:12:11 +00:00
|
|
|
missingNote file present needed untrusted dead =
|
|
|
|
missingNote file present needed [] dead ++
|
2011-07-05 22:31:46 +00:00
|
|
|
"\nThe following untrusted locations may also have copies: " ++
|
|
|
|
"\n" ++ untrusted
|
2016-02-19 19:12:11 +00:00
|
|
|
|
|
|
|
honorDead :: String -> String
|
|
|
|
honorDead dead
|
|
|
|
| null dead = ""
|
|
|
|
| otherwise = "\nThese dead repositories used to have copies\n" ++ dead
|
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
|
|
|
|
2015-04-18 18:13:07 +00:00
|
|
|
{- Bad content is dropped from the remote. We have downloaded a copy
|
|
|
|
- from the remote to a temp file already (in some cases, it's just a
|
|
|
|
- symlink to a file in the remote). To avoid any further data loss,
|
|
|
|
- that temp file is moved to the bad content directory unless
|
|
|
|
- the local annex has a copy of the content. -}
|
|
|
|
badContentRemote :: Remote -> FilePath -> Key -> Annex String
|
|
|
|
badContentRemote remote localcopy key = do
|
|
|
|
bad <- fromRepo gitAnnexBadDir
|
|
|
|
let destbad = bad </> key2file key
|
|
|
|
movedbad <- ifM (inAnnex key <||> liftIO (doesFileExist destbad))
|
|
|
|
( return False
|
|
|
|
, do
|
|
|
|
createAnnexDirectory (parentDir destbad)
|
|
|
|
liftIO $ catchDefaultIO False $
|
|
|
|
ifM (isSymbolicLink <$> getSymbolicLinkStatus localcopy)
|
|
|
|
( copyFileExternal CopyTimeStamps localcopy destbad
|
|
|
|
, do
|
|
|
|
moveFile localcopy destbad
|
|
|
|
return True
|
|
|
|
)
|
|
|
|
)
|
|
|
|
|
|
|
|
dropped <- Remote.removeKey remote key
|
|
|
|
when dropped $
|
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
|
|
|
Remote.logStatus remote key InfoMissing
|
2015-04-18 18:13:07 +00:00
|
|
|
return $ case (movedbad, dropped) of
|
|
|
|
(True, True) -> "moved from " ++ Remote.name remote ++
|
|
|
|
" to " ++ destbad
|
|
|
|
(False, True) -> "dropped from " ++ Remote.name remote
|
|
|
|
(_, False) -> "failed to drop from" ++ Remote.name remote
|
2012-09-25 17:22:12 +00:00
|
|
|
|
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 $
|
2015-02-16 19:08:29 +00:00
|
|
|
recordFsckTime inc key
|
2012-09-25 19:45:17 +00:00
|
|
|
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
|
2015-07-31 20:00:13 +00:00
|
|
|
needFsck (ScheduleIncremental _ _ i) k = needFsck i k
|
2015-02-16 20:04:23 +00:00
|
|
|
needFsck (ContIncremental h) key = liftIO $ not <$> FsckDb.inDb h key
|
2012-09-25 19:45:17 +00:00
|
|
|
needFsck _ _ = return True
|
2012-09-25 19:06:33 +00:00
|
|
|
|
2015-02-16 19:08:29 +00:00
|
|
|
recordFsckTime :: Incremental -> Key -> Annex ()
|
2015-02-16 20:48:19 +00:00
|
|
|
recordFsckTime inc key = withFsckDb inc $ \h -> liftIO $ FsckDb.addDb h key
|
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
|
|
|
-}
|
2015-02-17 21:08:11 +00:00
|
|
|
recordStartTime :: UUID -> Annex ()
|
|
|
|
recordStartTime u = do
|
|
|
|
f <- fromRepo (gitAnnexFsckState u)
|
2015-01-09 17:11:56 +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
|
|
|
|
2015-02-17 21:08:11 +00:00
|
|
|
resetStartTime :: UUID -> Annex ()
|
|
|
|
resetStartTime u = liftIO . nukeFile =<< fromRepo (gitAnnexFsckState u)
|
2012-09-25 23:37:34 +00:00
|
|
|
|
2012-09-25 18:16:34 +00:00
|
|
|
{- Gets the incremental fsck start time. -}
|
2015-02-17 21:08:11 +00:00
|
|
|
getStartTime :: UUID -> Annex (Maybe EpochTime)
|
|
|
|
getStartTime u = do
|
|
|
|
f <- fromRepo (gitAnnexFsckState u)
|
2012-09-25 18:16:34 +00:00
|
|
|
liftIO $ catchDefaultIO Nothing $ do
|
|
|
|
timestamp <- modificationTime <$> getFileStatus f
|
2014-02-25 18:09:39 +00:00
|
|
|
let fromstatus = Just (realToFrac timestamp)
|
2015-05-10 18:45:55 +00:00
|
|
|
fromfile <- parsePOSIXTime <$> readFile f
|
2014-02-25 18:09:39 +00:00
|
|
|
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
|
2014-02-25 18:09:39 +00:00
|
|
|
matchingtimestamp fromfile fromstatus =
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
fromfile == fromstatus
|
|
|
|
#else
|
|
|
|
fromfile >= fromstatus
|
|
|
|
#endif
|
2015-04-01 21:53:16 +00:00
|
|
|
|
2015-07-25 21:37:09 +00:00
|
|
|
data Incremental
|
|
|
|
= NonIncremental
|
2015-08-23 22:39:29 +00:00
|
|
|
| ScheduleIncremental Duration UUID Incremental
|
2015-07-25 21:37:09 +00:00
|
|
|
| StartIncremental FsckDb.FsckHandle
|
2015-07-31 20:00:13 +00:00
|
|
|
| ContIncremental FsckDb.FsckHandle
|
2015-04-01 21:53:16 +00:00
|
|
|
|
2015-07-09 16:26:25 +00:00
|
|
|
prepIncremental :: UUID -> Maybe IncrementalOpt -> Annex Incremental
|
|
|
|
prepIncremental _ Nothing = pure NonIncremental
|
|
|
|
prepIncremental u (Just StartIncrementalO) = do
|
|
|
|
recordStartTime u
|
|
|
|
ifM (FsckDb.newPass u)
|
2015-07-31 20:00:13 +00:00
|
|
|
( StartIncremental <$> openFsckDb u
|
2015-07-09 16:26:25 +00:00
|
|
|
, error "Cannot start a new --incremental fsck pass; another fsck process is already running."
|
|
|
|
)
|
|
|
|
prepIncremental u (Just MoreIncrementalO) =
|
2015-07-31 20:00:13 +00:00
|
|
|
ContIncremental <$> openFsckDb u
|
2015-07-09 16:26:25 +00:00
|
|
|
prepIncremental u (Just (ScheduleIncrementalO delta)) = do
|
|
|
|
started <- getStartTime u
|
2015-07-31 20:00:13 +00:00
|
|
|
i <- prepIncremental u $ Just $ case started of
|
2015-07-09 16:26:25 +00:00
|
|
|
Nothing -> StartIncrementalO
|
|
|
|
Just _ -> MoreIncrementalO
|
2015-07-31 20:00:13 +00:00
|
|
|
return (ScheduleIncremental delta u i)
|
2015-07-25 21:37:09 +00:00
|
|
|
|
|
|
|
cleanupIncremental :: Incremental -> Annex ()
|
2015-07-31 20:00:13 +00:00
|
|
|
cleanupIncremental (ScheduleIncremental delta u i) = do
|
|
|
|
v <- getStartTime u
|
|
|
|
case v of
|
|
|
|
Nothing -> noop
|
|
|
|
Just started -> do
|
|
|
|
now <- liftIO getPOSIXTime
|
|
|
|
when (now - realToFrac started >= durationToPOSIXTime delta) $
|
|
|
|
resetStartTime u
|
|
|
|
cleanupIncremental i
|
2015-07-25 21:37:09 +00:00
|
|
|
cleanupIncremental _ = return ()
|
2015-07-31 20:00:13 +00:00
|
|
|
|
|
|
|
openFsckDb :: UUID -> Annex FsckDb.FsckHandle
|
|
|
|
openFsckDb u = do
|
|
|
|
h <- FsckDb.openDb u
|
|
|
|
Annex.addCleanup FsckCleanup $
|
|
|
|
FsckDb.closeDb h
|
|
|
|
return h
|
|
|
|
|
|
|
|
withFsckDb :: Incremental -> (FsckDb.FsckHandle -> Annex ()) -> Annex ()
|
|
|
|
withFsckDb (ContIncremental h) a = a h
|
|
|
|
withFsckDb (StartIncremental h) a = a h
|
|
|
|
withFsckDb NonIncremental _ = noop
|
|
|
|
withFsckDb (ScheduleIncremental _ _ i) a = withFsckDb i a
|
2015-12-11 20:05:56 +00:00
|
|
|
|
2015-12-15 20:10:48 +00:00
|
|
|
data KeyStatus = KeyLocked | KeyUnlocked | KeyMissing
|
2015-12-11 20:05:56 +00:00
|
|
|
|
|
|
|
isKeyUnlocked :: KeyStatus -> Bool
|
|
|
|
isKeyUnlocked KeyUnlocked = True
|
|
|
|
isKeyUnlocked KeyLocked = False
|
2015-12-15 20:10:48 +00:00
|
|
|
isKeyUnlocked KeyMissing = False
|
2015-12-11 20:05:56 +00:00
|
|
|
|
|
|
|
getKeyStatus :: Key -> Annex KeyStatus
|
2015-12-15 18:27:20 +00:00
|
|
|
getKeyStatus key = ifM isDirect
|
|
|
|
( return KeyUnlocked
|
2015-12-15 20:10:48 +00:00
|
|
|
, catchDefaultIO KeyMissing $ do
|
2016-02-14 21:04:09 +00:00
|
|
|
unlocked <- not . null <$> Database.Keys.getAssociatedFiles key
|
2015-12-15 18:27:20 +00:00
|
|
|
return $ if unlocked then KeyUnlocked else KeyLocked
|
|
|
|
)
|
2016-02-14 21:09:54 +00:00
|
|
|
|
|
|
|
getKeyFileStatus :: Key -> FilePath -> Annex KeyStatus
|
|
|
|
getKeyFileStatus key file = do
|
|
|
|
s <- getKeyStatus key
|
|
|
|
case s of
|
|
|
|
KeyLocked -> catchDefaultIO KeyLocked $
|
|
|
|
ifM (isJust <$> isAnnexLink file)
|
|
|
|
( return KeyLocked
|
|
|
|
, return KeyUnlocked
|
|
|
|
)
|
|
|
|
_ -> return s
|