add config page for fsck, and alert with button when a fsck is running

This commit is contained in:
Joey Hess 2013-10-10 18:02:33 -04:00
parent 18f4d1b400
commit e9745f2da2
12 changed files with 74 additions and 23 deletions

View file

@ -134,7 +134,7 @@ startDaemon assistant foreground listenhost startbrowser = do
, assist $ netWatcherThread , assist $ netWatcherThread
, assist $ netWatcherFallbackThread , assist $ netWatcherFallbackThread
, assist $ transferScannerThread urlrenderer , assist $ transferScannerThread urlrenderer
, assist $ cronnerThread , assist $ cronnerThread urlrenderer
, assist $ configMonitorThread , assist $ configMonitorThread
, assist $ glacierThread , assist $ glacierThread
, watch $ watchThread , watch $ watchThread

View file

@ -27,17 +27,19 @@ import Assistant.WebApp
import Yesod import Yesod
#endif #endif
{- Makes a button for an alert that opens a Route. The button will {- Makes a button for an alert that opens a Route.
- close the alert it's attached to when clicked. -} -
- If autoclose is set, the button will close the alert it's
- attached to when clicked. -}
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
mkAlertButton :: T.Text -> UrlRenderer -> Route WebApp -> Assistant AlertButton mkAlertButton :: Bool -> T.Text -> UrlRenderer -> Route WebApp -> Assistant AlertButton
mkAlertButton label urlrenderer route = do mkAlertButton autoclose label urlrenderer route = do
close <- asIO1 removeAlert close <- asIO1 removeAlert
url <- liftIO $ renderUrl urlrenderer route [] url <- liftIO $ renderUrl urlrenderer route []
return $ AlertButton return $ AlertButton
{ buttonLabel = label { buttonLabel = label
, buttonUrl = url , buttonUrl = url
, buttonAction = Just close , buttonAction = if autoclose then Just close else Nothing
} }
#endif #endif
@ -147,6 +149,12 @@ 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 button = baseActivityAlert
{ alertData = [ UnTensed "Consistency check in progress" ]
, alertButton = Just button
}
pairingAlert :: AlertButton -> Alert pairingAlert :: AlertButton -> Alert
pairingAlert button = baseActivityAlert pairingAlert button = baseActivityAlert
{ alertData = [ UnTensed "Pairing in progress" ] { alertData = [ UnTensed "Pairing in progress" ]

View file

@ -81,7 +81,7 @@ finishRemovingRemote :: UrlRenderer -> UUID -> Assistant ()
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
finishRemovingRemote urlrenderer uuid = do finishRemovingRemote urlrenderer uuid = do
desc <- liftAnnex $ Remote.prettyUUID uuid desc <- liftAnnex $ Remote.prettyUUID uuid
button <- mkAlertButton (T.pack "Finish deletion process") urlrenderer $ button <- mkAlertButton True (T.pack "Finish deletion process") urlrenderer $
FinishDeleteRepositoryR uuid FinishDeleteRepositoryR uuid
void $ addAlert $ remoteRemovalAlert desc button void $ addAlert $ remoteRemovalAlert desc button
#else #else

View file

@ -76,7 +76,7 @@ startNamedThread urlrenderer (NamedThread afterstartupsanitycheck name a) = do
] ]
hPutStrLn stderr msg hPutStrLn stderr msg
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
button <- runAssistant d $ mkAlertButton button <- runAssistant d $ mkAlertButton True
(T.pack "Restart Thread") (T.pack "Restart Thread")
urlrenderer urlrenderer
(RestartThreadR name) (RestartThreadR name)

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable, CPP #-}
module Assistant.Threads.Cronner ( module Assistant.Threads.Cronner (
cronnerThread cronnerThread
@ -25,6 +25,11 @@ import qualified Build.SysConfig
import Assistant.TransferQueue import Assistant.TransferQueue
import Annex.Content import Annex.Content
import Logs.Transfer import Logs.Transfer
import Assistant.Types.UrlRenderer
import Assistant.Alert
#ifdef WITH_WEBAPP
import Assistant.WebApp.Types
#endif
import Control.Concurrent.Async import Control.Concurrent.Async
import Data.Time.LocalTime import Data.Time.LocalTime
@ -32,6 +37,7 @@ import Data.Time.Clock
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Set as S import qualified Data.Set as S
import qualified Control.Exception as E import qualified Control.Exception as E
import qualified Data.Text as T
{- Loads schedules for this repository, and fires off one thread for each {- Loads schedules for this repository, and fires off one thread for each
- scheduled event. These threads sleep until the next time the event - scheduled event. These threads sleep until the next time the event
@ -41,8 +47,8 @@ import qualified Control.Exception as E
- schedules. When there's a change, compare the old and new list of - schedules. When there's a change, compare the old and new list of
- schedules to find deleted and added ones. Start new threads for added - schedules to find deleted and added ones. Start new threads for added
- ones, and kill the threads for deleted ones. -} - ones, and kill the threads for deleted ones. -}
cronnerThread :: NamedThread cronnerThread :: UrlRenderer -> NamedThread
cronnerThread = namedThreadUnchecked "Cronner" $ do cronnerThread urlrenderer = namedThreadUnchecked "Cronner" $ do
dstatus <- getDaemonStatus dstatus <- getDaemonStatus
h <- liftIO $ newNotificationHandle False (scheduleLogNotifier dstatus) h <- liftIO $ newNotificationHandle False (scheduleLogNotifier dstatus)
go h M.empty go h M.empty
@ -70,7 +76,7 @@ cronnerThread = namedThreadUnchecked "Cronner" $ do
(M.filterWithKey (\k _ -> S.member k removedactivities) m) (M.filterWithKey (\k _ -> S.member k removedactivities) m)
go h m' go h m'
startactivities as lastruntimes = forM as $ \activity -> do startactivities as lastruntimes = forM as $ \activity -> do
runner <- asIO2 activityThread runner <- asIO2 (activityThread urlrenderer)
a <- liftIO $ async $ a <- liftIO $ async $
runner activity (M.lookup activity lastruntimes) runner activity (M.lookup activity lastruntimes)
return (activity, a) return (activity, a)
@ -79,8 +85,8 @@ cronnerThread = namedThreadUnchecked "Cronner" $ do
- sleep until that time, and run it. Then call setLastRunTime, and - sleep until that time, and run it. Then call setLastRunTime, and
- loop. - loop.
-} -}
activityThread :: ScheduledActivity -> Maybe LocalTime -> Assistant () activityThread :: UrlRenderer -> ScheduledActivity -> Maybe LocalTime -> Assistant ()
activityThread activity lasttime = go lasttime =<< getnexttime lasttime activityThread urlrenderer activity lasttime = go lasttime =<< getnexttime lasttime
where where
getnexttime = liftIO . nextTime schedule getnexttime = liftIO . nextTime schedule
go _ Nothing = debug ["no scheduled events left for", desc] go _ Nothing = debug ["no scheduled events left for", desc]
@ -111,7 +117,7 @@ activityThread activity lasttime = go lasttime =<< getnexttime lasttime
(localTimeToUTC tz t) > 600 (localTimeToUTC tz t) > 600
run nowt = do run nowt = do
debug ["starting", desc] debug ["starting", desc]
runActivity activity runActivity urlrenderer activity
debug ["finished", desc] debug ["finished", desc]
liftAnnex $ setLastRunTime activity nowt liftAnnex $ setLastRunTime activity nowt
go (Just nowt) =<< getnexttime (Just nowt) go (Just nowt) =<< getnexttime (Just nowt)
@ -125,13 +131,23 @@ secondsUntilLocalTime t = do
then Seconds secs then Seconds secs
else Seconds 0 else Seconds 0
runActivity :: ScheduledActivity -> Assistant () runActivity :: UrlRenderer -> ScheduledActivity -> Assistant ()
runActivity (ScheduledSelfFsck _ d) = do runActivity urlrenderer (ScheduledSelfFsck _ d) = do
program <- liftIO $ readProgramFile program <- liftIO $ readProgramFile
void $ liftIO $ niceShell $ #ifdef WITH_WEBAPP
program ++ " fsck --incremental-schedule=1d --time-limit=" ++ fromDuration d button <- mkAlertButton False (T.pack "Configure") urlrenderer ConfigFsckR
r <- alertDuring (fsckAlert button) $ liftIO $ do
E.try (runfsck program) :: IO (Either E.SomeException ExitCode)
either (liftIO . E.throwIO) (const noop) r
#else
runfsck program
#endif
queueBad queueBad
runActivity (ScheduledRemoteFsck _ _ _) = where
runfsck program = niceShell $
program ++ " fsck --incremental-schedule=1d --time-limit=" ++ fromDuration d
runActivity _ (ScheduledRemoteFsck _ _ _) =
debug ["remote fsck not implemented yet"] debug ["remote fsck not implemented yet"]
queueBad :: Assistant () queueBad :: Assistant ()

View file

@ -102,7 +102,7 @@ pairListenerThread urlrenderer = namedThread "PairListener" $ do
pairReqReceived :: Bool -> UrlRenderer -> PairMsg -> Assistant () pairReqReceived :: Bool -> UrlRenderer -> PairMsg -> Assistant ()
pairReqReceived True _ _ = noop -- ignore our own PairReq pairReqReceived True _ _ = noop -- ignore our own PairReq
pairReqReceived False urlrenderer msg = do pairReqReceived False urlrenderer msg = do
button <- mkAlertButton (T.pack "Respond") urlrenderer (FinishLocalPairR msg) button <- mkAlertButton True (T.pack "Respond") urlrenderer (FinishLocalPairR msg)
void $ addAlert $ pairRequestReceivedAlert repo button void $ addAlert $ pairRequestReceivedAlert repo button
where where
repo = pairRepo msg repo = pairRepo msg

View file

@ -29,6 +29,7 @@ import Assistant.WebApp.Configurators.XMPP
import Assistant.WebApp.Configurators.Preferences import Assistant.WebApp.Configurators.Preferences
import Assistant.WebApp.Configurators.Edit import Assistant.WebApp.Configurators.Edit
import Assistant.WebApp.Configurators.Delete import Assistant.WebApp.Configurators.Delete
import Assistant.WebApp.Configurators.Fsck
import Assistant.WebApp.Documentation import Assistant.WebApp.Documentation
import Assistant.WebApp.Control import Assistant.WebApp.Control
import Assistant.WebApp.OtherRepos import Assistant.WebApp.OtherRepos

View file

@ -336,7 +336,7 @@ pairMsgReceived urlrenderer PairReq theiruuid selfjid theirjid
finishXMPPPairing theirjid theiruuid finishXMPPPairing theirjid theiruuid
-- Show an alert to let the user decide if they want to pair. -- Show an alert to let the user decide if they want to pair.
showalert = do showalert = do
button <- mkAlertButton (T.pack "Respond") urlrenderer $ button <- mkAlertButton True (T.pack "Respond") urlrenderer $
ConfirmXMPPPairFriendR $ ConfirmXMPPPairFriendR $
PairKey theiruuid $ formatJID theirjid PairKey theiruuid $ formatJID theirjid
void $ addAlert $ pairRequestReceivedAlert void $ addAlert $ pairRequestReceivedAlert

View file

@ -0,0 +1,17 @@
{- git-annex assistant fsck configuration
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, TemplateHaskell, OverloadedStrings, FlexibleContexts #-}
{-# LANGUAGE CPP #-}
module Assistant.WebApp.Configurators.Fsck where
import Assistant.WebApp.Common
getConfigFsckR :: Handler Html
getConfigFsckR = page "Consistency checks" (Just Configuration) $ do
error "TODO"

View file

@ -55,7 +55,7 @@ checkCloudRepos :: UrlRenderer -> Remote -> Assistant ()
checkCloudRepos urlrenderer r = checkCloudRepos urlrenderer r =
unlessM (syncingToCloudRemote <$> getDaemonStatus) $ do unlessM (syncingToCloudRemote <$> getDaemonStatus) $ do
buddyname <- getBuddyName $ Remote.uuid r buddyname <- getBuddyName $ Remote.uuid r
button <- mkAlertButton "Add a cloud repository" urlrenderer $ button <- mkAlertButton True "Add a cloud repository" urlrenderer $
NeedCloudRepoR $ Remote.uuid r NeedCloudRepoR $ Remote.uuid r
void $ addAlert $ cloudRepoNeededAlert buddyname button void $ addAlert $ cloudRepoNeededAlert buddyname button
#else #else

View file

@ -19,6 +19,7 @@
/config/xmpp/for/self XMPPConfigForPairSelfR GET POST /config/xmpp/for/self XMPPConfigForPairSelfR GET POST
/config/xmpp/for/frield XMPPConfigForPairFriendR GET POST /config/xmpp/for/frield XMPPConfigForPairFriendR GET POST
/config/xmpp/needcloudrepo/#UUID NeedCloudRepoR GET /config/xmpp/needcloudrepo/#UUID NeedCloudRepoR GET
/config/fsck ConfigFsckR GET
/config/addrepository AddRepositoryR GET /config/addrepository AddRepositoryR GET
/config/repository/new NewRepositoryR GET POST /config/repository/new NewRepositoryR GET POST

View file

@ -13,6 +13,7 @@
<p> <p>
Tune the behavior of git-annex, including how many copies # Tune the behavior of git-annex, including how many copies #
to retain of each file, and how much disk space it can use. to retain of each file, and how much disk space it can use.
<div .row-fluid>
<div .span4> <div .span4>
$if xmppconfigured $if xmppconfigured
<h3> <h3>
@ -28,3 +29,10 @@
<p> <p>
Keep in touch with remote devices, and with your friends, # Keep in touch with remote devices, and with your friends, #
by configuring a jabber account. by configuring a jabber account.
<div .span4>
<h3>
<a href="@{ConfigFsckR}">
Configure consistency checks
<p>
Set up periodic checks of your data to detect and recover from #
disk problems.