add remote fsck interface

Currently only implemented for local git remotes. May try to add support
to git-annex-shell for ssh remotes later. Could concevably also be
supported by some special remote, although that seems unlikely.

Cronner user this when available, and when not falls back to
fsck --fast --from remote

git annex fsck --from does not itself use this interface.
To do so, I would need to pass --fast and all other options that influence
fsck on to the git annex fsck that it runs inside the remote. And that
seems like a lot of work for a result that would be no better than
cd remote; git annex fsck
This may need to be revisited if git-annex-shell gets support, since it
may be the case that the user cannot ssh to the server to run git-annex
fsck there, but can run git-annex-shell there.

This commit was sponsored by Damien Diederen.
This commit is contained in:
Joey Hess 2013-10-11 16:03:18 -04:00
parent 7e723d2f56
commit 1ffb3bb0ba
15 changed files with 104 additions and 41 deletions

View file

@ -15,6 +15,7 @@ import Assistant.Alert.Utility
import qualified Remote import qualified Remote
import Utility.Tense import Utility.Tense
import Logs.Transfer import Logs.Transfer
import Git.Remote (RemoteName)
import Data.String import Data.String
import qualified Data.Text as T import qualified Data.Text as T
@ -149,9 +150,11 @@ sanityCheckFixAlert msg = Alert
alerthead = "The daily sanity check found and fixed a problem:" alerthead = "The daily sanity check found and fixed a problem:"
alertfoot = "If these problems persist, consider filing a bug report." alertfoot = "If these problems persist, consider filing a bug report."
fsckAlert :: AlertButton -> Alert fsckAlert :: AlertButton -> Maybe RemoteName -> Alert
fsckAlert button = baseActivityAlert fsckAlert button n = baseActivityAlert
{ alertData = [ UnTensed "Consistency check in progress" ] { alertData = case n of
Nothing -> [ UnTensed $ T.pack $ "Consistency check in progress" ]
Just remotename -> [ UnTensed $ T.pack $ "Consistency check of " ++ remotename ++ " in progress"]
, alertButton = Just button , alertButton = Just button
} }

View file

@ -21,15 +21,17 @@ import Utility.Scheduled
import Types.ScheduledActivity import Types.ScheduledActivity
import Utility.ThreadScheduler import Utility.ThreadScheduler
import Utility.HumanTime import Utility.HumanTime
import qualified Build.SysConfig import Utility.Batch
import Assistant.TransferQueue import Assistant.TransferQueue
import Annex.Content import Annex.Content
import Logs.Transfer import Logs.Transfer
import Assistant.Types.UrlRenderer import Assistant.Types.UrlRenderer
import Assistant.Alert import Assistant.Alert
import Remote
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
import Assistant.WebApp.Types import Assistant.WebApp.Types
#endif #endif
import Git.Remote (RemoteName)
import Control.Concurrent.Async import Control.Concurrent.Async
import Data.Time.LocalTime import Data.Time.LocalTime
@ -134,45 +136,44 @@ secondsUntilLocalTime t = do
runActivity :: UrlRenderer -> ScheduledActivity -> Assistant () runActivity :: UrlRenderer -> ScheduledActivity -> Assistant ()
runActivity urlrenderer (ScheduledSelfFsck _ d) = do runActivity urlrenderer (ScheduledSelfFsck _ d) = do
program <- liftIO $ readProgramFile program <- liftIO $ readProgramFile
void $ runFsck urlrenderer Nothing $
batchCommand program (Param "fsck" : fsckParams d)
mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir)
where
reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download
runActivity urlrenderer (ScheduledRemoteFsck u s d) = go =<< liftAnnex (remoteFromUUID u)
where
go (Just r) = void $ case Remote.remoteFsck r of
Nothing -> void $ runFsck urlrenderer (Just $ Remote.name r) $ do
program <- readProgramFile
batchCommand program $
[ Param "fsck"
-- avoid downloading files
, Param "--fast"
, Param "--from"
, Param $ Remote.name r
] ++ fsckParams d
Just mkfscker ->
{- Note that having mkfsker return an IO action
- avoids running a long duration fsck in the
- Annex monad. -}
void . runFsck urlrenderer (Just $ Remote.name r)
=<< liftAnnex (mkfscker (fsckParams d))
go Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s]
runFsck :: UrlRenderer -> Maybe RemoteName -> IO Bool -> Assistant Bool
runFsck urlrenderer remotename a = do
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
button <- mkAlertButton False (T.pack "Configure") urlrenderer ConfigFsckR button <- mkAlertButton False (T.pack "Configure") urlrenderer ConfigFsckR
r <- alertDuring (fsckAlert button) $ liftIO $ do r <- alertDuring (fsckAlert button remotename) $ liftIO $ do
E.try (runfsck program) :: IO (Either E.SomeException ExitCode) E.try a :: IO (Either E.SomeException Bool)
either (liftIO . E.throwIO) (const noop) r either (liftIO . E.throwIO) return r
#else #else
runfsck program a
#endif #endif
queueBad
where
runfsck program = niceShell $
program ++ " fsck --incremental-schedule=1d --time-limit=" ++ fromDuration d
runActivity _ (ScheduledRemoteFsck _ _ _) = fsckParams :: Duration -> [CommandParam]
debug ["remote fsck not implemented yet"] fsckParams d =
[ Param "--incremental-schedule=1d"
queueBad :: Assistant () , Param $ "--time-limit=" ++ fromDuration d
queueBad = mapM_ queue =<< liftAnnex (dirKeys gitAnnexBadDir)
where
queue k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download
{- Runs a shell command niced, until it terminates.
-
- When an async exception is received, the command is sent a SIGTERM,
- and after it finishes shutting down the exception is re-raised. -}
niceShell :: String -> IO ExitCode
niceShell command = do
(_, _, _, pid) <- createProcess $ proc "sh"
[ "-c"
, "exec " ++ nicedcommand
] ]
r <- E.try (waitForProcess pid) :: IO (Either E.SomeException ExitCode)
case r of
Right exitcode -> return exitcode
Left asyncexception -> do
terminateProcess pid
void $ waitForProcess pid
E.throwIO asyncexception
where
nicedcommand
| Build.SysConfig.nice = "nice " ++ command
| otherwise = command

View file

@ -16,6 +16,7 @@ module Remote (
hasKey, hasKey,
hasKeyCheap, hasKeyCheap,
whereisKey, whereisKey,
remoteFsck,
remoteTypes, remoteTypes,
remoteList, remoteList,

View file

@ -63,6 +63,7 @@ gen r u c gc = do
, hasKey = checkPresent r bupr' , hasKey = checkPresent r bupr'
, hasKeyCheap = bupLocal buprepo , hasKeyCheap = bupLocal buprepo
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = Nothing
, config = c , config = c
, repo = r , repo = r
, gitconfig = gc , gitconfig = gc

View file

@ -54,6 +54,7 @@ gen r u c gc = do
hasKey = checkPresent dir chunksize, hasKey = checkPresent dir chunksize,
hasKeyCheap = True, hasKeyCheap = True,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing,
config = M.empty, config = M.empty,
repo = r, repo = r,
gitconfig = gc, gitconfig = gc,

View file

@ -107,6 +107,7 @@ gen' r u c gc = do
, hasKey = checkPresent this rsyncopts , hasKey = checkPresent this rsyncopts
, hasKeyCheap = repoCheap r , hasKeyCheap = repoCheap r
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = Nothing
, config = M.empty , config = M.empty
, localpath = localpathCalc r , localpath = localpathCalc r
, repo = r , repo = r

View file

@ -42,10 +42,12 @@ import Utility.Metered
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import Utility.CopyFile import Utility.CopyFile
#endif #endif
import Utility.Batch
import Remote.Helper.Git import Remote.Helper.Git
import Remote.Helper.Messages import Remote.Helper.Messages
import qualified Remote.Helper.Ssh as Ssh import qualified Remote.Helper.Ssh as Ssh
import qualified Remote.GCrypt import qualified Remote.GCrypt
import Config.Files
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.MSampleVar import Control.Concurrent.MSampleVar
@ -111,6 +113,9 @@ gen r u c gc
, hasKey = inAnnex r , hasKey = inAnnex r
, hasKeyCheap = repoCheap r , hasKeyCheap = repoCheap r
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = if Git.repoIsUrl r
then Nothing
else Just $ fsckOnRemote r
, config = M.empty , config = M.empty
, localpath = localpathCalc r , localpath = localpathCalc r
, repo = r , repo = r
@ -396,6 +401,17 @@ copyToRemote r key file p
(\d -> rsyncOrCopyFile params object d p) (\d -> rsyncOrCopyFile params object d p)
) )
fsckOnRemote :: Git.Repo -> [CommandParam] -> Annex (IO Bool)
fsckOnRemote r params
| Git.repoIsUrl r = return $ do
program <- readProgramFile
batchCommand program $ Param "fsck" : params
| otherwise = do
s <- Ssh.git_annex_shell r "fsck" params []
return $ case s of
Nothing -> return False
Just (c, ps) -> batchCommand c ps
{- Runs an action on a local repository inexpensively, by making an annex {- Runs an action on a local repository inexpensively, by making an annex
- monad using that repository. -} - monad using that repository. -}
onLocal :: Git.Repo -> Annex a -> IO a onLocal :: Git.Repo -> Annex a -> IO a

View file

@ -59,6 +59,7 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost
hasKey = checkPresent this, hasKey = checkPresent this,
hasKeyCheap = False, hasKeyCheap = False,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing,
config = c, config = c,
repo = r, repo = r,
gitconfig = gc, gitconfig = gc,

View file

@ -52,6 +52,7 @@ gen r u c gc = do
hasKey = checkPresent r hooktype, hasKey = checkPresent r hooktype,
hasKeyCheap = False, hasKeyCheap = False,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing,
config = M.empty, config = M.empty,
localpath = Nothing, localpath = Nothing,
repo = r, repo = r,

View file

@ -79,6 +79,7 @@ gen r u c gc = do
, hasKey = checkPresent r o , hasKey = checkPresent r o
, hasKeyCheap = False , hasKeyCheap = False
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = Nothing
, config = M.empty , config = M.empty
, repo = r , repo = r
, gitconfig = gc , gitconfig = gc

View file

@ -62,6 +62,7 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost
hasKey = checkPresent this, hasKey = checkPresent this,
hasKeyCheap = False, hasKeyCheap = False,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing,
config = c, config = c,
repo = r, repo = r,
gitconfig = gc, gitconfig = gc,

View file

@ -56,6 +56,7 @@ gen r _ _ gc =
hasKey = checkKey, hasKey = checkKey,
hasKeyCheap = False, hasKeyCheap = False,
whereisKey = Just getUrls, whereisKey = Just getUrls,
remoteFsck = Nothing,
config = M.empty, config = M.empty,
gitconfig = gc, gitconfig = gc,
localpath = Nothing, localpath = Nothing,

View file

@ -65,6 +65,7 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost
hasKey = checkPresent this, hasKey = checkPresent this,
hasKeyCheap = False, hasKeyCheap = False,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing,
config = c, config = c,
repo = r, repo = r,
gitconfig = gc, gitconfig = gc,

View file

@ -19,6 +19,7 @@ import Types.GitConfig
import Config.Cost import Config.Cost
import Utility.Metered import Utility.Metered
import Git.Remote import Git.Remote
import Utility.SafeCommand
type RemoteConfigKey = String type RemoteConfigKey = String
type RemoteConfig = M.Map RemoteConfigKey String type RemoteConfig = M.Map RemoteConfigKey String
@ -64,6 +65,10 @@ data RemoteA a = Remote {
hasKeyCheap :: Bool, hasKeyCheap :: Bool,
-- Some remotes can provide additional details for whereis. -- Some remotes can provide additional details for whereis.
whereisKey :: Maybe (Key -> a [String]), whereisKey :: Maybe (Key -> a [String]),
-- Some remotes can run a fsck operation on the remote,
-- without transferring all the data to the local repo
-- The parameters are passed to the fsck command on the remote.
remoteFsck :: Maybe ([CommandParam] -> a (IO Bool)),
-- a Remote has a persistent configuration store -- a Remote has a persistent configuration store
config :: RemoteConfig, config :: RemoteConfig,
-- git repo for the Remote -- git repo for the Remote

View file

@ -9,10 +9,14 @@
module Utility.Batch where module Utility.Batch where
import Common
import qualified Build.SysConfig
#if defined(linux_HOST_OS) || defined(__ANDROID__) #if defined(linux_HOST_OS) || defined(__ANDROID__)
import Control.Concurrent.Async import Control.Concurrent.Async
import System.Posix.Process import System.Posix.Process
#endif #endif
import qualified Control.Exception as E
{- Runs an operation, at batch priority. {- Runs an operation, at batch priority.
- -
@ -38,3 +42,27 @@ batch a = a
maxNice :: Int maxNice :: Int
maxNice = 19 maxNice = 19
{- Runs a command in a way that's suitable for batch jobs.
- The command is run niced. If the calling thread receives an async
- exception, it sends the command a SIGTERM, and after the command
- finishes shuttting down, it re-raises the async exception. -}
batchCommand :: String -> [CommandParam] -> IO Bool
batchCommand command params = do
(_, _, _, pid) <- createProcess $ proc "sh"
[ "-c"
, "exec " ++ nicedcommand
]
r <- E.try (waitForProcess pid) :: IO (Either E.SomeException ExitCode)
case r of
Right ExitSuccess -> return True
Right _ -> return False
Left asyncexception -> do
terminateProcess pid
void $ waitForProcess pid
E.throwIO asyncexception
where
commandline = unwords $ map shellEscape $ command : toCommand params
nicedcommand
| Build.SysConfig.nice = "nice " ++ commandline
| otherwise = commandline