git-annex/Command/Fsck.hs

169 lines
4.8 KiB
Haskell
Raw Normal View History

2010-11-06 21:06:19 +00:00
{- git-annex command
-
- Copyright 2010-2011 Joey Hess <joey@kitenet.net>
2010-11-06 21:06:19 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
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
import qualified Remote
import qualified Types.Backend
import qualified Types.Key
import qualified Backend
2011-10-04 04:40:47 +00:00
import Annex.Content
2011-10-15 20:21:08 +00:00
import Logs.Location
import Logs.Trust
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
import Config
2010-11-06 21:06:19 +00:00
def :: [Command]
def = [command "fsck" paramPaths seek "check for problems"]
seek :: [CommandSeek]
seek =
[ withNumCopies $ \n -> whenAnnexed $ start n
, withBarePresentKeys startBare
]
2010-11-15 22:22:50 +00:00
start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart
start numcopies file (key, backend) = do
2010-11-15 22:22:50 +00:00
showStart "fsck" file
next $ perform key file backend numcopies
2010-11-15 22:22:50 +00:00
perform :: Key -> FilePath -> Backend Annex -> Maybe Int -> CommandPerform
perform key file backend numcopies = check
2011-10-29 20:45:06 +00:00
-- order matters
[ verifyLocationLog key file
, checkKeySize key
, checkKeyNumCopies key file numcopies
, checkBackend backend key
2011-10-29 20:45:06 +00:00
]
{- To fsck a bare repository, fsck each key in the location log. -}
withBarePresentKeys :: (Key -> CommandStart) -> CommandSeek
2011-10-29 22:47:53 +00:00
withBarePresentKeys a params = isBareRepo >>= go
where
go False = return []
go True = do
2011-11-11 05:52:58 +00:00
unless (null params) $
error "fsck should be run without parameters in a bare repository"
prepStart a loggedKeys
startBare :: Key -> CommandStart
startBare key = case Backend.maybeLookupBackendName (Types.Key.keyBackendName key) of
Nothing -> stop
Just backend -> do
showStart "fsck" (show key)
next $ performBare key backend
{- Note that numcopies cannot be checked in a bare repository, because
- getting the numcopies value requires a working copy with .gitattributes
- files. -}
performBare :: Key -> Backend Annex -> CommandPerform
performBare key backend = check
[ verifyLocationLog key (show key)
, checkKeySize key
, checkBackend backend key
]
check :: [Annex Bool] -> CommandPerform
check = sequence >=> dispatch
2011-10-29 20:45:06 +00:00
where
dispatch vs
2011-10-29 20:45:06 +00:00
| all (== True) vs = next $ return True
| otherwise = stop
{- Checks that the location log reflects the current status of the key,
in this repository only. -}
verifyLocationLog :: Key -> String -> Annex Bool
verifyLocationLog key desc = do
present <- inAnnex key
-- Since we're checking that a key's file is present, throw
-- in a permission fixup here too.
when present $ do
f <- inRepo $ gitAnnexLocation key
liftIO $ do
preventWrite f
preventWrite (parentDir f)
2011-10-11 18:43:45 +00:00
u <- getUUID
2011-06-22 20:13:43 +00:00
uuids <- keyLocations key
case (present, u `elem` uuids) of
(True, False) -> do
fix u InfoPresent
-- There is no data loss, so do not fail.
return True
(False, True) -> do
fix u InfoMissing
warning $
"** Based on the location log, " ++ desc
++ "\n** was expected to be present, " ++
"but its content is missing."
return False
_ -> return True
where
fix u s = do
showNote "fixing location log"
2011-11-09 05:15:51 +00:00
logChange key u s
{- The size of the data for a key is checked against the size encoded in
- the key's metadata, if available. -}
checkKeySize :: Key -> Annex Bool
checkKeySize key = do
file <- inRepo $ gitAnnexLocation key
present <- liftIO $ doesFileExist file
case (present, Types.Key.keySize key) of
(_, Nothing) -> return True
(False, _) -> return True
(True, Just size) -> do
stat <- liftIO $ getFileStatus file
let size' = fromIntegral (fileSize stat)
if size == size'
then return True
else do
dest <- moveBad key
warning $ "Bad file size (" ++
compareSizes storageUnits True size size' ++
"); moved to " ++ dest
return False
checkBackend :: Backend Annex -> Key -> Annex Bool
2011-11-11 05:52:58 +00:00
checkBackend = Types.Backend.fsckKey
2011-10-29 20:45:06 +00:00
checkKeyNumCopies :: Key -> FilePath -> Maybe Int -> Annex Bool
checkKeyNumCopies key file numcopies = do
needed <- getNumCopies numcopies
2011-09-06 21:19:29 +00:00
(untrustedlocations, safelocations) <- trustPartition UnTrusted =<< keyLocations key
let present = length safelocations
if present < needed
then do
ppuuids <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
2011-10-29 20:45:06 +00:00
warning $ missingNote file present needed ppuuids
return False
else return True
missingNote :: String -> Int -> Int -> String -> String
missingNote file 0 _ [] =
"** No known copies exist of " ++ file
missingNote file 0 _ untrusted =
"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 [] =
"Only " ++ show present ++ " of " ++ show needed ++
" 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