git-annex/Command/Fsck.hs

638 lines
20 KiB
Haskell
Raw Normal View History

2010-11-06 21:06:19 +00:00
{- git-annex command
-
- 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
import qualified Annex
import qualified Remote
import qualified Types.Backend
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
import Annex.Direct
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
import Logs.Activity
import Logs.TimeStamp
2015-04-30 18:02:56 +00:00
import Annex.NumCopies
import Annex.UUID
import Annex.ReplaceFile
2011-07-06 00:36:43 +00:00
import Utility.DataUnits
import Config
import Utility.HumanTime
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
import qualified Database.Keys
import qualified Database.Fsck as FsckDb
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)
cmd :: Command
cmd = withGlobalOptions (jobsOption : annexedMatchingOptions) $
command "fsck" SectionMaintenance
"find and fix problems"
paramPaths (seek <$$> optParser)
data FsckOptions = FsckOptions
{ fsckFiles :: CmdParams
2015-07-09 20:05:45 +00:00
, fsckFromOption :: Maybe (DeferredParse Remote)
, incrementalOpt :: Maybe IncrementalOpt
2015-07-09 16:44:03 +00:00
, keyOptions :: Maybe KeyOptions
}
data IncrementalOpt
= StartIncrementalO
| MoreIncrementalO
| ScheduleIncrementalO Duration
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
<> help "check remote"
<> completeRemotes
))
<*> optional parseincremental
2015-07-09 16:44:03 +00:00
<*> optional (parseKeyOptions False)
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"
))
seek :: FsckOptions -> CommandSeek
seek o = allowConcurrentOutput $ do
2015-07-09 20:05:45 +00:00
from <- maybe (pure Nothing) (Just <$$> getParsed) (fsckFromOption o)
u <- maybe getUUID (pure . Remote.uuid) from
checkDeadRepo u
i <- prepIncremental u (incrementalOpt o)
2015-07-08 21:59:06 +00:00
withKeyOptions (keyOptions o) False
(\k -> startKey i k =<< getNumCopies)
(withFilesInGit $ whenAnnexed $ start from i)
(fsckFiles o)
cleanupIncremental i
void $ tryIO $ recordActivity Fsck u
2010-11-15 22:22:50 +00:00
checkDeadRepo :: UUID -> Annex ()
checkDeadRepo u =
whenM ((==) DeadTrusted <$> lookupTrust u) $
earlyWarning "Warning: Fscking a repository that is currently marked as dead."
start :: Maybe Remote -> Incremental -> FilePath -> Key -> CommandStart
start from inc file key = do
v <- Backend.getBackend file key
case v of
Nothing -> stop
Just backend -> do
numcopies <- getFileNumCopies file
case from of
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
perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool
perform key file backend numcopies = do
keystatus <- getKeyFileStatus key file
check
-- order matters
[ fixLink key file
, verifyLocationLog key keystatus file
, verifyAssociatedFiles key keystatus file
, verifyWorkTree key file
, checkKeySize key keystatus
, checkBackend backend key keystatus (Just file)
, checkKeyNumCopies key (Just file) numcopies
]
{- To fsck a remote, the content is retrieved to a tmp file,
- and checked locally. -}
performRemote :: Key -> FilePath -> Backend -> NumCopies -> Remote -> Annex Bool
performRemote key file backend numcopies remote =
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
warning "failed to download file from remote"
2015-02-12 20:03:59 +00:00
void $ go True Nothing
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
, 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
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 (checkDiskSpace (Just (takeDirectory tmp)) key 0 True)
( 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
, Just . fst <$>
2015-04-27 21:40:21 +00:00
Remote.retrieveKeyFile remote key Nothing tmp dummymeter
)
2012-11-12 05:05:04 +00:00
)
2015-04-27 21:40:21 +00:00
, return (Just False)
)
dummymeter _ = noop
startKey :: Incremental -> Key -> NumCopies -> CommandStart
startKey inc key numcopies =
case Backend.maybeLookupBackendName (keyBackendName key) of
Nothing -> stop
Just backend -> runFsck inc (key2file key) key $
performKey key backend numcopies
performKey :: Key -> Backend -> NumCopies -> Annex Bool
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
]
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
{- Checks that symlinks points correctly to the annexed content.
2013-01-06 19:42:49 +00:00
-}
fixLink :: Key -> FilePath -> Annex Bool
fixLink key file = do
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
go want have
| want /= fromInternalGitPath have = do
showNote "fixing link"
liftIO $ createDirectoryIfMissing True (parentDir file)
liftIO $ removeFile file
addAnnexLink want file
| otherwise = noop
{- Checks that the location log reflects the current status of the key,
2012-12-13 04:45:27 +00:00
- in this repository only. -}
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
{- 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. -}
when (present && not direct) $ void $ tryIO $
if isKeyUnlocked keystatus
then thawContent obj
else freezeContent obj
whenM (liftIO $ doesDirectoryExist $ parentDir obj) $
freezeContentDir obj
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)
verifyLocationLogRemote :: Key -> String -> Remote -> Bool -> Annex Bool
verifyLocationLogRemote key desc remote present =
verifyLocationLog' key desc present (Remote.uuid remote)
(Remote.logStatus remote key)
verifyLocationLog' :: Key -> String -> Bool -> UUID -> (LogStatus -> Annex ()) -> Annex Bool
2013-12-01 19:52:30 +00:00
verifyLocationLog' key desc present u updatestatus = do
uuids <- loggedLocations key
case (present, u `elem` uuids) of
(True, False) -> do
fix InfoPresent
-- There is no data loss, so do not fail.
return True
(False, True) -> do
fix InfoMissing
warning $
"** Based on the location log, " ++ desc
++ "\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
2016-02-14 20:52:43 +00:00
{- Verifies the associated file records. -}
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
forM_ fs $ \f ->
unlessM (liftIO $ doesFileExist f) $
2016-02-14 20:52:43 +00:00
void $ Direct.removeAssociatedFile key f
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 ()
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
v <- toDirectGen key file
case v of
Nothing -> noop
Just a -> do
showNote "fixing direct mode"
a
{- 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 ()
{- 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 when a file is unlocked, or in direct mode.
-}
checkKeySize :: Key -> KeyStatus -> Annex Bool
checkKeySize _ KeyUnlocked = return True
checkKeySize key _ = do
file <- calcRepo $ gitAnnexLocation key
ifM (liftIO $ doesFileExist file)
( checkKeySizeOr badContent key file
, return True
)
checkKeySizeRemote :: Key -> Remote -> Maybe FilePath -> Annex Bool
checkKeySizeRemote _ _ Nothing = return True
checkKeySizeRemote key remote (Just file) =
checkKeySizeOr (badContentRemote remote file) key file
checkKeySizeOr :: (Key -> Annex String) -> Key -> FilePath -> Annex Bool
checkKeySizeOr bad key file = case keySize key of
Nothing -> return True
Just size -> do
size' <- liftIO $ getFileSize file
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
]
{- 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.
-}
checkBackend :: Backend -> Key -> KeyStatus -> Maybe FilePath -> Annex Bool
checkBackend backend key keystatus mfile = go =<< isDirect
where
go False = do
content <- calcRepo $ gitAnnexLocation key
ifM (pure (isKeyUnlocked keystatus) <&&> (not <$> isUnmodified key content))
( nocheck
, checkBackendOr badContent backend key content
)
go True = maybe nocheck checkdirect mfile
2016-02-14 20:52:43 +00:00
checkdirect file = ifM (Direct.goodContent key file)
( checkBackendOr' (badContentDirect file) backend key file
2016-02-14 20:52:43 +00:00
(Direct.goodContent key file)
, nocheck
2013-01-08 16:41:09 +00:00
)
nocheck = return True
checkBackendRemote :: Backend -> Key -> Remote -> Maybe FilePath -> Annex Bool
checkBackendRemote backend key remote = maybe (return True) go
2012-11-12 05:05:04 +00:00
where
go file = checkBackendOr (badContentRemote remote file) backend key file
checkBackendOr :: (Key -> Annex String) -> Backend -> Key -> FilePath -> Annex Bool
checkBackendOr bad backend key file =
checkBackendOr' bad backend key file (return True)
-- 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).
checkBackendOr' :: (Key -> Annex String) -> Backend -> Key -> FilePath -> Annex Bool -> Annex Bool
checkBackendOr' bad backend key file postcheck =
case Types.Backend.verifyKeyContent backend of
Nothing -> return True
Just verifier -> do
ok <- verifier key file
ifM postcheck
( do
unless ok $ do
msg <- bad key
warning $ "Bad file content; " ++ msg
return ok
, return True
)
checkKeyNumCopies :: Key -> AssociatedFile -> NumCopies -> Annex Bool
checkKeyNumCopies key afile numcopies = do
let file = fromMaybe (key2file key) afile
locs <- loggedLocations key
(untrustedlocations, otherlocations) <- trustPartition UnTrusted locs
(deadlocations, safelocations) <- trustPartition DeadTrusted otherlocations
let present = NumCopies (length safelocations)
if present < numcopies
then ifM (pure (isNothing afile) <&&> checkDead key)
( do
showLongNote $ "This key is dead, skipping."
return True
, do
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 )"
return False
)
else return True
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 =
"Only these untrusted locations may have copies of " ++ file ++
"\n" ++ untrusted ++
"Back it up to trusted locations with git-annex copy." ++ honorDead dead
missingNote file present needed [] _ =
"Only " ++ show (fromNumCopies present) ++ " of " ++ show (fromNumCopies needed) ++
" trustworthy copies exist of " ++ file ++
"\nBack it up with git-annex copy."
missingNote file present needed untrusted dead =
missingNote file present needed [] dead ++
"\nThe following untrusted locations may also have copies: " ++
"\n" ++ untrusted
honorDead :: String -> String
honorDead dead
| null dead = ""
| otherwise = "\nThese dead repositories used to have copies\n" ++ dead
{- Bad content is moved aside. -}
badContent :: Key -> Annex String
badContent key = do
dest <- moveBad key
return $ "moved to " ++ dest
{- 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"
{- 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 $
Remote.logStatus remote key InfoMissing
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
runFsck inc file key a = ifM (needFsck inc key)
( do
showStart "fsck" file
next $ do
ok <- a
when ok $
recordFsckTime inc 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. -}
needFsck :: Incremental -> Key -> Annex Bool
needFsck (ScheduleIncremental _ _ i) k = needFsck i k
needFsck (ContIncremental h) key = liftIO $ not <$> FsckDb.inDb h key
needFsck _ _ = return True
2012-09-25 19:06:33 +00:00
recordFsckTime :: Incremental -> Key -> Annex ()
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
- be identical to its modification time.
- (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.)
-}
recordStartTime :: UUID -> Annex ()
recordStartTime u = do
f <- fromRepo (gitAnnexFsckState u)
createAnnexDirectory $ parentDir f
2012-09-25 18:16:34 +00:00
liftIO $ do
nukeFile f
withFile f WriteMode $ \h -> do
#ifndef mingw32_HOST_OS
t <- modificationTime <$> getFileStatus f
#else
t <- getPOSIXTime
#endif
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
resetStartTime :: UUID -> Annex ()
resetStartTime u = liftIO . nukeFile =<< fromRepo (gitAnnexFsckState u)
2012-09-25 18:16:34 +00:00
{- Gets the incremental fsck start time. -}
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
let fromstatus = Just (realToFrac timestamp)
fromfile <- parsePOSIXTime <$> 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
matchingtimestamp fromfile fromstatus =
#ifndef mingw32_HOST_OS
fromfile == fromstatus
#else
fromfile >= fromstatus
#endif
data Incremental
= NonIncremental
| ScheduleIncremental Duration UUID Incremental
| StartIncremental FsckDb.FsckHandle
| ContIncremental FsckDb.FsckHandle
prepIncremental :: UUID -> Maybe IncrementalOpt -> Annex Incremental
prepIncremental _ Nothing = pure NonIncremental
prepIncremental u (Just StartIncrementalO) = do
recordStartTime u
ifM (FsckDb.newPass u)
( StartIncremental <$> openFsckDb u
, error "Cannot start a new --incremental fsck pass; another fsck process is already running."
)
prepIncremental u (Just MoreIncrementalO) =
ContIncremental <$> openFsckDb u
prepIncremental u (Just (ScheduleIncrementalO delta)) = do
started <- getStartTime u
i <- prepIncremental u $ Just $ case started of
Nothing -> StartIncrementalO
Just _ -> MoreIncrementalO
return (ScheduleIncremental delta u i)
cleanupIncremental :: Incremental -> Annex ()
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
cleanupIncremental _ = return ()
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
data KeyStatus = KeyLocked | KeyUnlocked | KeyMissing
isKeyUnlocked :: KeyStatus -> Bool
isKeyUnlocked KeyUnlocked = True
isKeyUnlocked KeyLocked = False
isKeyUnlocked KeyMissing = False
getKeyStatus :: Key -> Annex KeyStatus
getKeyStatus key = ifM isDirect
( return KeyUnlocked
, catchDefaultIO KeyMissing $ do
unlocked <- not . null <$> Database.Keys.getAssociatedFiles key
return $ if unlocked then KeyUnlocked else KeyLocked
)
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