assistant: Support repairing git remotes that are locally accessible

(eg, on removable drives)

gcrypt remotes are not yet handled.

This commit was sponsored by Sören Brunk.
This commit is contained in:
Joey Hess 2013-10-27 15:38:59 -04:00
parent 98ae3afc81
commit 7ed8e87a34
21 changed files with 132 additions and 75 deletions

View file

@ -177,6 +177,12 @@ fsckAlert button n = baseActivityAlert
brokenRepositoryAlert :: AlertButton -> Alert brokenRepositoryAlert :: AlertButton -> Alert
brokenRepositoryAlert = errorAlert "Serious problems have been detected with your repository. This needs your immediate attention!" brokenRepositoryAlert = errorAlert "Serious problems have been detected with your repository. This needs your immediate attention!"
repairingAlert :: String -> Alert
repairingAlert repodesc = activityAlert Nothing
[ Tensed "Attempting to repair" "Repaired"
, UnTensed $ T.pack repodesc
]
pairingAlert :: AlertButton -> Alert pairingAlert :: AlertButton -> Alert
pairingAlert button = baseActivityAlert pairingAlert button = baseActivityAlert
{ alertData = [ UnTensed "Pairing in progress" ] { alertData = [ UnTensed "Pairing in progress" ]

View file

@ -11,8 +11,11 @@ module Assistant.Repair where
import Assistant.Common import Assistant.Common
import Command.Repair (repairAnnexBranch) import Command.Repair (repairAnnexBranch)
import Git.Fsck (FsckResults) import Git.Fsck (FsckResults, foundBroken)
import Git.Repair (runRepairOf) import Git.Repair (runRepairOf)
import qualified Git
import qualified Remote
import qualified Types.Remote as Remote
import Logs.FsckResults import Logs.FsckResults
import Annex.UUID import Annex.UUID
import Utility.Batch import Utility.Batch
@ -28,11 +31,16 @@ import Assistant.WebApp.Types
import qualified Data.Text as T import qualified Data.Text as T
import Control.Concurrent.Async import Control.Concurrent.Async
{- Try to do a non-destructive repair. If that fails, pop up an alert. -} {- When the FsckResults require a repair, tries to do a non-destructive
brokenRepositoryDetected :: FsckResults -> UrlRenderer -> UUID -> Assistant () - repair. If that fails, pops up an alert. -}
brokenRepositoryDetected fsckresults urlrenderer u = do repairWhenNecessary :: UrlRenderer -> UUID -> Maybe Remote -> FsckResults -> Assistant ()
liftAnnex $ writeFsckResults u fsckresults repairWhenNecessary urlrenderer u mrmt fsckresults
handle =<< runRepair u False | foundBroken fsckresults = do
liftAnnex $ writeFsckResults u fsckresults
repodesc <- liftAnnex $ Remote.prettyUUID u
handle =<< alertDuring (repairingAlert repodesc)
(runRepair u mrmt False)
| otherwise = noop
where where
handle True = return () handle True = return ()
handle False = do handle False = do
@ -44,47 +52,58 @@ brokenRepositoryDetected fsckresults urlrenderer u = do
return () return ()
#endif #endif
runRepair :: UUID -> Bool -> Assistant Bool runRepair :: UUID -> Maybe Remote -> Bool -> Assistant Bool
runRepair u destructiverepair = do runRepair u mrmt destructiverepair = do
-- Stop the watcher from running while running repairs.
changeSyncable Nothing False
fsckresults <- liftAnnex $ readFsckResults u fsckresults <- liftAnnex $ readFsckResults u
myu <- liftAnnex getUUID myu <- liftAnnex getUUID
ok <- if u == myu ok <- if u == myu
then localrepair fsckresults then localrepair fsckresults
else remoterepair fsckresults else remoterepair fsckresults
liftAnnex $ writeFsckResults u Nothing liftAnnex $ writeFsckResults u Nothing
debug [ "Repaired", show u, show ok ]
-- Start the watcher running again. This also triggers it to do a
-- startup scan, which is especially important if the git repo
-- repair removed files from the index file. Those files will be
-- seen as new, and re-added to the repository.
when ok $
changeSyncable Nothing True
return ok return ok
where where
localrepair fsckresults = do localrepair fsckresults = do
-- Stop the watcher from running while running repairs.
changeSyncable Nothing False
-- This intentionally runs the repair inside the Annex -- This intentionally runs the repair inside the Annex
-- monad, which is not strictly necessary, but keeps -- monad, which is not strictly necessary, but keeps
-- other threads that might be trying to use the Annex -- other threads that might be trying to use the Annex
-- from running until it completes. -- from running until it completes.
ok <- liftAnnex $ do ok <- liftAnnex $ repair fsckresults Nothing
(ok, stillmissing, modifiedbranches) <- inRepo $
runRepairOf fsckresults destructiverepair
when destructiverepair $
repairAnnexBranch stillmissing modifiedbranches
return ok
-- Run a background fast fsck if a destructive repair had -- Run a background fast fsck if a destructive repair had
-- to be done, to ensure that the git-annex branch -- to be done, to ensure that the git-annex branch
-- reflects the current state of the repo. -- reflects the current state of the repo.
when (destructiverepair && not ok) $ when destructiverepair $
backgroundfsck [ Param "--fast" ] backgroundfsck [ Param "--fast" ]
-- Start the watcher running again. This also triggers it to
-- do a startup scan, which is especially important if the
-- git repo repair removed files from the index file. Those
-- files will be seen as new, and re-added to the repository.
when (ok || destructiverepair) $
changeSyncable Nothing True
return ok return ok
remoterepair _fsckresults = do remoterepair fsckresults = case Remote.repairRepo =<< mrmt of
error "TODO: remote repair" Nothing -> return False
Just mkrepair -> do
thisrepopath <- liftIO . absPath
=<< liftAnnex (fromRepo Git.repoPath)
a <- liftAnnex $ mkrepair $
repair fsckresults (Just thisrepopath)
liftIO $ catchBoolIO a
repair fsckresults referencerepo = do
(ok, stillmissing, modifiedbranches) <- inRepo $
runRepairOf fsckresults destructiverepair referencerepo
when destructiverepair $
repairAnnexBranch stillmissing modifiedbranches
return ok
backgroundfsck params = liftIO $ void $ async $ do backgroundfsck params = liftIO $ void $ async $ do
program <- readProgramFile program <- readProgramFile

View file

@ -28,12 +28,14 @@ import Logs.Transfer
import Assistant.Types.UrlRenderer import Assistant.Types.UrlRenderer
import Assistant.Alert import Assistant.Alert
import Remote import Remote
import qualified Types.Remote as Remote
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
import Assistant.WebApp.Types import Assistant.WebApp.Types
#endif #endif
import Git.Remote (RemoteName) import Git.Remote (RemoteName)
import qualified Git.Fsck import qualified Git.Fsck
import Assistant.Repair import Assistant.Repair
import qualified Git
import Control.Concurrent.Async import Control.Concurrent.Async
import Control.Concurrent.MVar import Control.Concurrent.MVar
@ -186,34 +188,39 @@ runActivity' urlrenderer (ScheduledSelfFsck _ d) = do
program <- liftIO $ readProgramFile program <- liftIO $ readProgramFile
g <- liftAnnex gitRepo g <- liftAnnex gitRepo
fsckresults <- showFscking urlrenderer Nothing $ tryNonAsync $ do fsckresults <- showFscking urlrenderer Nothing $ tryNonAsync $ do
r <- Git.Fsck.findBroken True g
void $ batchCommand program (Param "fsck" : annexFsckParams d) void $ batchCommand program (Param "fsck" : annexFsckParams d)
return r Git.Fsck.findBroken True g
when (Git.Fsck.foundBroken fsckresults) $ u <- liftAnnex getUUID
brokenRepositoryDetected fsckresults urlrenderer repairWhenNecessary urlrenderer u Nothing fsckresults
=<< liftAnnex getUUID
mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir) mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir)
where where
reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download
runActivity' urlrenderer (ScheduledRemoteFsck u s d) = go =<< liftAnnex (remoteFromUUID u) runActivity' urlrenderer (ScheduledRemoteFsck u s d) = handle =<< liftAnnex (remoteFromUUID u)
where where
go (Just r) = void $ case Remote.remoteFsck r of handle Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s]
Nothing -> void $ showFscking urlrenderer (Just $ Remote.name r) $ tryNonAsync $ do handle (Just rmt) = void $ case Remote.remoteFsck rmt of
Nothing -> go rmt $ do
program <- readProgramFile program <- readProgramFile
batchCommand program $ void $ batchCommand program $
[ Param "fsck" [ Param "fsck"
-- avoid downloading files -- avoid downloading files
, Param "--fast" , Param "--fast"
, Param "--from" , Param "--from"
, Param $ Remote.name r , Param $ Remote.name rmt
] ++ annexFsckParams d ] ++ annexFsckParams d
Just mkfscker -> Just mkfscker -> do
{- Note that having mkfsker return an IO action {- Note that having mkfsker return an IO action
- avoids running a long duration fsck in the - avoids running a long duration fsck in the
- Annex monad. -} - Annex monad. -}
void . showFscking urlrenderer (Just $ Remote.name r) . tryNonAsync go rmt =<< liftAnnex (mkfscker (annexFsckParams d))
=<< liftAnnex (mkfscker (annexFsckParams d)) go rmt annexfscker = do
go Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s] fsckresults <- showFscking urlrenderer (Just $ Remote.name rmt) $ tryNonAsync $ do
void annexfscker
let r = Remote.repo rmt
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 -> Maybe RemoteName -> IO (Either E.SomeException a) -> Assistant a
showFscking urlrenderer remotename a = do showFscking urlrenderer remotename a = do

View file

@ -8,23 +8,10 @@
module Assistant.Threads.Transferrer where module Assistant.Threads.Transferrer where
import Assistant.Common import Assistant.Common
import Assistant.DaemonStatus
import Assistant.TransferQueue import Assistant.TransferQueue
import Assistant.TransferSlots import Assistant.TransferSlots
import Assistant.Alert
import Assistant.Alert.Utility
import Assistant.Commits
import Assistant.Drop
import Assistant.TransferrerPool
import Logs.Transfer import Logs.Transfer
import Logs.Location
import Annex.Content
import qualified Remote
import qualified Types.Remote as Remote
import qualified Git
import Config.Files import Config.Files
import Assistant.Threads.TransferWatcher
import Annex.Wanted
{- Dispatches transfers from the queue. -} {- Dispatches transfers from the queue. -}
transfererThread :: NamedThread transfererThread :: NamedThread

View file

@ -11,7 +11,6 @@ module Assistant.WebApp.Configurators.Delete where
import Assistant.WebApp.Common import Assistant.WebApp.Common
import Assistant.DeleteRemote import Assistant.DeleteRemote
import Assistant.WebApp.Utility
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.ScanRemotes import Assistant.ScanRemotes
import Assistant.Sync import Assistant.Sync

View file

@ -11,7 +11,8 @@ module Assistant.WebApp.Repair where
import Assistant.WebApp.Common import Assistant.WebApp.Common
import Assistant.WebApp.RepoList import Assistant.WebApp.RepoList
import Remote (prettyUUID) import Remote (prettyUUID, remoteFromUUID)
import Annex.UUID (getUUID)
import Assistant.Repair import Assistant.Repair
getRepairRepositoryR :: UUID -> Handler Html getRepairRepositoryR :: UUID -> Handler Html
@ -19,13 +20,15 @@ getRepairRepositoryR = postRepairRepositoryR
postRepairRepositoryR :: UUID -> Handler Html postRepairRepositoryR :: UUID -> Handler Html
postRepairRepositoryR u = page "Repair repository" Nothing $ do postRepairRepositoryR u = page "Repair repository" Nothing $ do
repodesc <- liftAnnex $ prettyUUID u repodesc <- liftAnnex $ prettyUUID u
repairingmainrepo <- (==) u <$> liftAnnex getUUID
$(widgetFile "control/repairrepository") $(widgetFile "control/repairrepository")
getRepairRepositoryRunR :: UUID -> Handler Html getRepairRepositoryRunR :: UUID -> Handler Html
getRepairRepositoryRunR = postRepairRepositoryRunR getRepairRepositoryRunR = postRepairRepositoryRunR
postRepairRepositoryRunR :: UUID -> Handler Html postRepairRepositoryRunR :: UUID -> Handler Html
postRepairRepositoryRunR u = do postRepairRepositoryRunR u = do
void $ liftAssistant $ runRepair u True r <- liftAnnex $ remoteFromUUID u
void $ liftAssistant $ runRepair u r True
page "Repair repository" Nothing $ do page "Repair repository" Nothing $ do
let repolist = repoListDisplay $ let repolist = repoListDisplay $
mainRepoSelector { nudgeAddMore = True } mainRepoSelector { nudgeAddMore = True }

View file

@ -124,9 +124,13 @@ explodePacks r = do
{- Try to retrieve a set of missing objects, from the remotes of a {- Try to retrieve a set of missing objects, from the remotes of a
- repository. Returns any that could not be retreived. - repository. Returns any that could not be retreived.
-
- If another clone of the repository exists locally, which might not be a
- remote of the repo being repaired, its path can be passed as a reference
- repository.
-} -}
retrieveMissingObjects :: MissingObjects -> Repo -> IO MissingObjects retrieveMissingObjects :: MissingObjects -> Maybe FilePath -> Repo -> IO MissingObjects
retrieveMissingObjects missing r retrieveMissingObjects missing referencerepo r
| S.null missing = return missing | S.null missing = return missing
| otherwise = withTmpDir "tmprepo" $ \tmpdir -> do | otherwise = withTmpDir "tmprepo" $ \tmpdir -> do
unlessM (boolSystem "git" [Params "init", File tmpdir]) $ unlessM (boolSystem "git" [Params "init", File tmpdir]) $
@ -137,12 +141,19 @@ retrieveMissingObjects missing r
then return stillmissing then return stillmissing
else pullremotes tmpr (remotes r) fetchallrefs stillmissing else pullremotes tmpr (remotes r) fetchallrefs stillmissing
where where
pullremotes _tmpr [] _ stillmissing = return stillmissing pullremotes tmpr [] fetchrefs stillmissing = case referencerepo of
Nothing -> return stillmissing
Just p -> ifM (fetchfrom p fetchrefs tmpr)
( do
void $ copyObjects tmpr r
findMissing (S.toList stillmissing) r
, return stillmissing
)
pullremotes tmpr (rmt:rmts) fetchrefs s pullremotes tmpr (rmt:rmts) fetchrefs s
| S.null s = return s | S.null s = return s
| otherwise = do | otherwise = do
putStrLn $ "Trying to recover missing objects from remote " ++ repoDescribe rmt putStrLn $ "Trying to recover missing objects from remote " ++ repoDescribe rmt
ifM (fetchsome rmt fetchrefs tmpr) ifM (fetchfrom (repoLocation rmt) fetchrefs tmpr)
( do ( do
void $ copyObjects tmpr r void $ copyObjects tmpr r
stillmissing <- findMissing (S.toList s) r stillmissing <- findMissing (S.toList s) r
@ -155,9 +166,9 @@ retrieveMissingObjects missing r
] ]
pullremotes tmpr rmts fetchrefs s pullremotes tmpr rmts fetchrefs s
) )
fetchsome rmt ps = runBool $ fetchfrom fetchurl ps = runBool $
[ Param "fetch" [ Param "fetch"
, Param (repoLocation rmt) , Param fetchurl
, Params "--force --update-head-ok --quiet" , Params "--force --update-head-ok --quiet"
] ++ ps ] ++ ps
-- fetch refs and tags -- fetch refs and tags
@ -427,14 +438,15 @@ runRepair forced g = do
putStrLn "Running git fsck ..." putStrLn "Running git fsck ..."
fsckresult <- findBroken False g fsckresult <- findBroken False g
if foundBroken fsckresult if foundBroken fsckresult
then runRepairOf fsckresult forced g then runRepairOf fsckresult forced Nothing g
else do else do
putStrLn "No problems found." putStrLn "No problems found."
return (True, S.empty, []) return (True, S.empty, [])
runRepairOf :: FsckResults -> Bool -> Repo -> IO (Bool, MissingObjects, [Branch])
runRepairOf fsckresult forced g = do runRepairOf :: FsckResults -> Bool -> Maybe FilePath -> Repo -> IO (Bool, MissingObjects, [Branch])
runRepairOf fsckresult forced referencerepo g = do
missing <- cleanCorruptObjects fsckresult g missing <- cleanCorruptObjects fsckresult g
stillmissing <- retrieveMissingObjects missing g stillmissing <- retrieveMissingObjects missing referencerepo g
if S.null stillmissing if S.null stillmissing
then successfulfinish stillmissing [] then successfulfinish stillmissing []
else do else do

View file

@ -64,6 +64,7 @@ gen r u c gc = do
, hasKeyCheap = bupLocal buprepo , hasKeyCheap = bupLocal buprepo
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = Nothing , remoteFsck = Nothing
, repairRepo = Nothing
, config = c , config = c
, repo = r , repo = r
, gitconfig = gc , gitconfig = gc

View file

@ -55,6 +55,7 @@ gen r u c gc = do
hasKeyCheap = True, hasKeyCheap = True,
whereisKey = Nothing, whereisKey = Nothing,
remoteFsck = Nothing, remoteFsck = Nothing,
repairRepo = Nothing,
config = M.empty, config = M.empty,
repo = r, repo = r,
gitconfig = gc, gitconfig = gc,

View file

@ -108,6 +108,7 @@ gen' r u c gc = do
, hasKeyCheap = repoCheap r , hasKeyCheap = repoCheap r
, whereisKey = Nothing , whereisKey = Nothing
, remoteFsck = Nothing , remoteFsck = Nothing
, repairRepo = Nothing
, config = M.empty , config = M.empty
, localpath = localpathCalc r , localpath = localpathCalc r
, repo = r , repo = r

View file

@ -117,6 +117,9 @@ gen r u c gc
, remoteFsck = if Git.repoIsUrl r , remoteFsck = if Git.repoIsUrl r
then Nothing then Nothing
else Just $ fsckOnRemote r else Just $ fsckOnRemote r
, repairRepo = if Git.repoIsUrl r
then Nothing
else Just $ repairRemote r
, config = M.empty , config = M.empty
, localpath = localpathCalc r , localpath = localpathCalc r
, repo = r , repo = r
@ -419,6 +422,10 @@ fsckOnRemote r params
] ++ env ] ++ env
batchCommandEnv program (Param "fsck" : params) (Just env') batchCommandEnv program (Param "fsck" : params) (Just env')
{- The passed repair action is run in the Annex monad of the remote. -}
repairRemote :: Git.Repo -> Annex Bool -> Annex (IO Bool)
repairRemote r a = return $ Remote.Git.onLocal r a
{- 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

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

View file

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

View file

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

View file

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

View file

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

View file

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

View file

@ -69,6 +69,8 @@ data RemoteA a = Remote {
-- without transferring all the data to the local repo -- without transferring all the data to the local repo
-- The parameters are passed to the fsck command on the remote. -- The parameters are passed to the fsck command on the remote.
remoteFsck :: Maybe ([CommandParam] -> a (IO Bool)), remoteFsck :: Maybe ([CommandParam] -> a (IO Bool)),
-- Runs an action to repair the remote's git repository.
repairRepo :: Maybe (a Bool -> 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

2
debian/changelog vendored
View file

@ -10,6 +10,8 @@ git-annex (4.20131025) UNRELEASED; urgency=low
without such a file, so files can still be retreived from them. without such a file, so files can still be retreived from them.
* assistant: Automatically repair damanged git repository, if it can * assistant: Automatically repair damanged git repository, if it can
be done without losing data. be done without losing data.
* assistant: Support repairing git remotes that are locally accessible
(eg, on removable drives).
-- Joey Hess <joeyh@debian.org> Sat, 26 Oct 2013 12:11:48 -0400 -- Joey Hess <joeyh@debian.org> Sat, 26 Oct 2013 12:11:48 -0400

View file

@ -59,8 +59,6 @@ call it for non-local remotes.
Add git fsck to scheduled self fsck **done** Add git fsck to scheduled self fsck **done**
TODO: Add git fsck of local remotes to scheduled remote fscks.
TODO: git fsck on ssh remotes? Probably not worth the complexity.. TODO: git fsck on ssh remotes? Probably not worth the complexity..
TODO: If committing to the repository fails, after resolving any dangling TODO: If committing to the repository fails, after resolving any dangling
@ -71,6 +69,11 @@ If git fsck finds problems, launch git repository repair. **done**
git annex fsck --fast at end of repository repair to ensure git annex fsck --fast at end of repository repair to ensure
git-annex branch is accurate. **done** git-annex branch is accurate. **done**
TODO: "Repair" gcrypt remotes, by removing all refs and objects,
and re-pushing. (Since the objects are encrypted data, there is no way
to pull missing ones from anywhere..)
Need to preserve gcrypt-id while doing this!
TODO: along with displaying alert when there is a problem detected TODO: along with displaying alert when there is a problem detected
by consistency check, send an email alert. (Using system MTA?) by consistency check, send an email alert. (Using system MTA?)

View file

@ -7,12 +7,13 @@
<p> <p>
While this is not good, this problem can be automatically repaired, While this is not good, this problem can be automatically repaired,
often without data loss. often without data loss.
<p> $if repairingmainrepo
When possible, the corrupt data will be recovered from other # <p>
repositories. You should make sure any other repositories that might # When possible, the corrupt data will be recovered from other #
have this data are available before continuing. So, plug in any # repositories. You should make sure any other repositories that might #
removable drive that contains a repository, or make sure your network # have this data are available before continuing. So, plug in any #
connection to other repositories is active. removable drive that contains a repository, or make sure your network #
connection to other repositories is active.
<p> <p>
<a .btn .btn-primary href="@{RepairRepositoryRunR u}" onclick="$('#workingmodal').modal('show');"> <a .btn .btn-primary href="@{RepairRepositoryRunR u}" onclick="$('#workingmodal').modal('show');">
Start Repair Process Start Repair Process