summaryrefslogtreecommitdiff
path: root/Assistant/Threads
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-10-27 16:42:13 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-10-27 16:42:13 -0400
commitbe581a2722e78f8a2e59e5ca78a1090efc432307 (patch)
treea24cb16a152bcce74bf4ae279056ac1f17ab4695 /Assistant/Threads
parent4b0b07f1783705714dd75ca1812ab676260e5728 (diff)
automatically launch git repository repair
Added a RemoteChecker thread, that waits for problems to be reported with remotes, and checks if their git repository is in need of repair. Currently, only failures to sync with the remote cause a problem to be reported. This seems enough, but we'll see. Plugging in a removable drive with a repository on it that is corrupted does automatically repair the repository, as long as the corruption causes git push or git pull to fail. Some types of corruption do not, eg missing/corrupt objects for blobs that git push doesn't need to look at. So, this is not really a replacement for scheduled git repository fscking. But it does make the assistant more robust. This commit is sponsored by Fernando Jimenez.
Diffstat (limited to 'Assistant/Threads')
-rw-r--r--Assistant/Threads/Cronner.hs23
-rw-r--r--Assistant/Threads/Pusher.hs5
-rw-r--r--Assistant/Threads/RemoteChecker.hs46
3 files changed, 52 insertions, 22 deletions
diff --git a/Assistant/Threads/Cronner.hs b/Assistant/Threads/Cronner.hs
index 6399de514..df5264d7f 100644
--- a/Assistant/Threads/Cronner.hs
+++ b/Assistant/Threads/Cronner.hs
@@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-{-# LANGUAGE DeriveDataTypeable, CPP #-}
+{-# LANGUAGE DeriveDataTypeable #-}
module Assistant.Threads.Cronner (
cronnerThread
@@ -29,10 +29,6 @@ import Assistant.Types.UrlRenderer
import Assistant.Alert
import Remote
import qualified Types.Remote as Remote
-#ifdef WITH_WEBAPP
-import Assistant.WebApp.Types
-#endif
-import Git.Remote (RemoteName)
import qualified Git.Fsck
import Assistant.Repair
import qualified Git
@@ -43,8 +39,6 @@ import Data.Time.LocalTime
import Data.Time.Clock
import qualified Data.Map as M
import qualified Data.Set as S
-import qualified Control.Exception as E
-import qualified Data.Text as T
{- Loads schedules for this repository, and fires off one thread for each
- scheduled event that runs on this repository. Each thread sleeps until
@@ -191,7 +185,7 @@ runActivity' urlrenderer (ScheduledSelfFsck _ d) = do
void $ batchCommand program (Param "fsck" : annexFsckParams d)
Git.Fsck.findBroken True g
u <- liftAnnex getUUID
- repairWhenNecessary urlrenderer u Nothing fsckresults
+ void $ repairWhenNecessary urlrenderer u Nothing fsckresults
mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir)
where
reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download
@@ -220,18 +214,7 @@ runActivity' urlrenderer (ScheduledRemoteFsck u s d) = handle =<< liftAnnex (rem
if Git.repoIsLocal r && not (Git.repoIsLocalUnknown r)
then Just <$> Git.Fsck.findBroken True r
else pure Nothing
- maybe noop (repairWhenNecessary urlrenderer u (Just rmt)) fsckresults
-
-showFscking :: UrlRenderer -> Maybe RemoteName -> IO (Either E.SomeException a) -> Assistant a
-showFscking urlrenderer remotename a = do
-#ifdef WITH_WEBAPP
- button <- mkAlertButton False (T.pack "Configure") urlrenderer ConfigFsckR
- r <- alertDuring (fsckAlert button remotename) $
- liftIO a
- either (liftIO . E.throwIO) return r
-#else
- a
-#endif
+ maybe noop (void . repairWhenNecessary urlrenderer u (Just rmt)) fsckresults
annexFsckParams :: Duration -> [CommandParam]
annexFsckParams d =
diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs
index 060f26cf5..3ec922fe4 100644
--- a/Assistant/Threads/Pusher.hs
+++ b/Assistant/Threads/Pusher.hs
@@ -13,6 +13,7 @@ import Assistant.Pushes
import Assistant.DaemonStatus
import Assistant.Sync
import Utility.ThreadScheduler
+import qualified Remote
import qualified Types.Remote as Remote
{- This thread retries pushes that failed before. -}
@@ -42,7 +43,7 @@ pushThread = namedThread "Pusher" $ runEvery (Seconds 2) <~> do
- to avoid ugly messages when a removable drive is not attached.
-}
pushTargets :: Assistant [Remote]
-pushTargets = liftIO . filterM available =<< candidates <$> getDaemonStatus
+pushTargets = liftIO . filterM (Remote.checkAvailable True)
+ =<< candidates <$> getDaemonStatus
where
candidates = filter (not . Remote.readonly) . syncGitRemotes
- available = maybe (return True) doesDirectoryExist . Remote.localpath
diff --git a/Assistant/Threads/RemoteChecker.hs b/Assistant/Threads/RemoteChecker.hs
new file mode 100644
index 000000000..ea0b578d2
--- /dev/null
+++ b/Assistant/Threads/RemoteChecker.hs
@@ -0,0 +1,46 @@
+{- git-annex assistant remote checker thread
+ -
+ - Copyright 2013 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Assistant.Threads.RemoteChecker (
+ remoteCheckerThread
+) where
+
+import Assistant.Common
+import Utility.ThreadScheduler
+import Assistant.Types.UrlRenderer
+import Assistant.Alert
+import Remote
+import qualified Types.Remote as Remote
+import qualified Git.Fsck
+import Assistant.Repair
+import qualified Git
+import Assistant.RemoteProblem
+import Assistant.Sync
+
+import Data.Function
+
+{- Waits for problems with remotes, and tries to fsck the remote and repair
+ - the problem. -}
+remoteCheckerThread :: UrlRenderer -> NamedThread
+remoteCheckerThread urlrenderer = namedThread "RemoteChecker" $ forever $ do
+ mapM_ (handleProblem urlrenderer)
+ =<< liftIO . filterM (checkAvailable True)
+ =<< nubremotes <$> getRemoteProblems
+ liftIO $ threadDelaySeconds (Seconds 60)
+ where
+ nubremotes = nubBy ((==) `on` Remote.uuid)
+
+handleProblem :: UrlRenderer -> Remote -> Assistant ()
+handleProblem urlrenderer rmt
+ | Git.repoIsLocal r && not (Git.repoIsLocalUnknown r) = do
+ fsckresults <- showFscking urlrenderer (Just $ Remote.name rmt) $ tryNonAsync $
+ Git.Fsck.findBroken True r
+ whenM (repairWhenNecessary urlrenderer (Remote.uuid rmt) (Just rmt) fsckresults) $
+ syncRemote rmt
+ | otherwise = noop
+ where
+ r = Remote.repo rmt