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.
This commit is contained in:
parent
3c08fee76b
commit
a7821c0581
11 changed files with 129 additions and 39 deletions
|
@ -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 =
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue