assistant: When autostarted, wait 5 seconds before running the startup scan, to avoid contending with the user's desktop login process.

This commit is contained in:
Joey Hess 2013-10-26 12:42:58 -04:00
parent 4830c0d830
commit 2233ddd5a2
7 changed files with 61 additions and 32 deletions

View file

@ -48,6 +48,7 @@ import Assistant.Types.UrlRenderer
import qualified Utility.Daemon import qualified Utility.Daemon
import Utility.LogFile import Utility.LogFile
import Utility.ThreadScheduler import Utility.ThreadScheduler
import Utility.HumanTime
import qualified Build.SysConfig as SysConfig import qualified Build.SysConfig as SysConfig
import System.Log.Logger import System.Log.Logger
@ -61,8 +62,8 @@ stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile
- -
- startbrowser is passed the url and html shim file, as well as the original - startbrowser is passed the url and html shim file, as well as the original
- stdout and stderr descriptors. -} - stdout and stderr descriptors. -}
startDaemon :: Bool -> Bool -> Maybe HostName -> Maybe (Maybe Handle -> Maybe Handle -> String -> FilePath -> IO ()) -> Annex () startDaemon :: Bool -> Bool -> Maybe Duration -> Maybe HostName -> Maybe (Maybe Handle -> Maybe Handle -> String -> FilePath -> IO ()) -> Annex ()
startDaemon assistant foreground listenhost startbrowser = do startDaemon assistant foreground startdelay listenhost startbrowser = do
Annex.changeState $ \s -> s { Annex.daemon = True } Annex.changeState $ \s -> s { Annex.daemon = True }
pidfile <- fromRepo gitAnnexPidFile pidfile <- fromRepo gitAnnexPidFile
logfile <- fromRepo gitAnnexLogFile logfile <- fromRepo gitAnnexLogFile
@ -140,7 +141,7 @@ startDaemon assistant foreground listenhost startbrowser = do
, watch $ watchThread , watch $ watchThread
-- must come last so that all threads that wait -- must come last so that all threads that wait
-- on it have already started waiting -- on it have already started waiting
, watch $ sanityCheckerStartupThread , watch $ sanityCheckerStartupThread startdelay
] ]
liftIO waitForTermination liftIO waitForTermination

View file

@ -25,15 +25,22 @@ import Utility.NotificationBroadcaster
import Config import Config
import qualified Git import qualified Git
import qualified Utility.Lsof as Lsof import qualified Utility.Lsof as Lsof
import Utility.HumanTime
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
{- This thread runs once at startup, and most other threads wait for it {- This thread runs once at startup, and most other threads wait for it
- to finish. (However, the webapp thread does not, to prevent the UI - to finish. (However, the webapp thread does not, to prevent the UI
- being nonresponsive.) -} - being nonresponsive.) -}
sanityCheckerStartupThread :: NamedThread sanityCheckerStartupThread :: Maybe Duration -> NamedThread
sanityCheckerStartupThread = namedThreadUnchecked "SanityCheckerStartup" $ sanityCheckerStartupThread startupdelay = namedThreadUnchecked "SanityCheckerStartup" $ do
startupCheck checkStaleGitLocks
liftIO $ maybe noop (threadDelaySeconds . Seconds . fromIntegral . durationSeconds) startupdelay
{- Notify other threads that the startup sanity check is done. -}
status <- getDaemonStatus
liftIO $ sendNotification $ startupSanityCheckNotifier status
{- This thread wakes up hourly for inxepensive frequent sanity checks. -} {- This thread wakes up hourly for inxepensive frequent sanity checks. -}
sanityCheckerHourlyThread :: NamedThread sanityCheckerHourlyThread :: NamedThread
@ -80,14 +87,6 @@ waitForNextCheck = do
oneDay - truncate (now - lastcheck) oneDay - truncate (now - lastcheck)
| otherwise = oneDay | otherwise = oneDay
startupCheck :: Assistant ()
startupCheck = do
checkStaleGitLocks
{- Notify other threads that the startup sanity check is done. -}
status <- getDaemonStatus
liftIO $ sendNotification $ startupSanityCheckNotifier status
{- It's important to stay out of the Annex monad as much as possible while {- It's important to stay out of the Annex monad as much as possible while
- running potentially expensive parts of this check, since remaining in it - running potentially expensive parts of this check, since remaining in it
- will block the watcher. -} - will block the watcher. -}

View file

@ -14,43 +14,55 @@ import qualified Command.Watch
import Init import Init
import Config.Files import Config.Files
import qualified Build.SysConfig import qualified Build.SysConfig
import Utility.HumanTime
import System.Environment import System.Environment
def :: [Command] def :: [Command]
def = [noRepo checkAutoStart $ dontCheck repoExists $ def = [noRepo checkAutoStart $ dontCheck repoExists $ withOptions options $
withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption, autoStartOption] $
command "assistant" paramNothing seek SectionCommon command "assistant" paramNothing seek SectionCommon
"automatically handle changes"] "automatically handle changes"]
options :: [Option]
options =
[ Command.Watch.foregroundOption
, Command.Watch.stopOption
, autoStartOption
, startDelayOption
]
autoStartOption :: Option autoStartOption :: Option
autoStartOption = Option.flag [] "autostart" "start in known repositories" autoStartOption = Option.flag [] "autostart" "start in known repositories"
startDelayOption :: Option
startDelayOption = Option.field [] "startdelay" paramNumber "delay before running startup scan"
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFlag Command.Watch.stopOption $ \stopdaemon -> seek = [withFlag Command.Watch.stopOption $ \stopdaemon ->
withFlag Command.Watch.foregroundOption $ \foreground -> withFlag Command.Watch.foregroundOption $ \foreground ->
withFlag autoStartOption $ \autostart -> withFlag autoStartOption $ \autostart ->
withNothing $ start foreground stopdaemon autostart] withField startDelayOption (pure . maybe Nothing parseDuration) $ \startdelay ->
withNothing $ start foreground stopdaemon autostart startdelay]
start :: Bool -> Bool -> Bool -> CommandStart start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start foreground stopdaemon autostart start foreground stopdaemon autostart startdelay
| autostart = do | autostart = do
liftIO autoStart liftIO $ autoStart startdelay
stop stop
| otherwise = do | otherwise = do
ensureInitialized ensureInitialized
Command.Watch.start True foreground stopdaemon Command.Watch.start True foreground stopdaemon startdelay
{- Run outside a git repository. Check to see if any parameter is {- Run outside a git repository. Check to see if any parameter is
- --autostart and enter autostart mode. -} - --autostart and enter autostart mode. -}
checkAutoStart :: IO () checkAutoStart :: IO ()
checkAutoStart = ifM (elem "--autostart" <$> getArgs) checkAutoStart = ifM (elem "--autostart" <$> getArgs)
( autoStart ( autoStart Nothing
, error "Not in a git repository." , error "Not in a git repository."
) )
autoStart :: IO () autoStart :: Maybe Duration -> IO ()
autoStart = do autoStart startdelay = do
dirs <- liftIO readAutoStartFile dirs <- liftIO readAutoStartFile
when (null dirs) $ do when (null dirs) $ do
f <- autoStartFile f <- autoStartFile
@ -67,5 +79,10 @@ autoStart = do
go haveionice program dir = do go haveionice program dir = do
setCurrentDirectory dir setCurrentDirectory dir
if haveionice if haveionice
then boolSystem "ionice" [Param "-c3", Param program, Param "assistant"] then boolSystem "ionice" (Param "-c3" : Param program : baseparams)
else boolSystem program [Param "assistant"] else boolSystem program baseparams
where
baseparams =
[ Param "assistant"
, Param $ "--startdelay=" ++ fromDuration (fromMaybe (Duration 5) startdelay)
]

View file

@ -11,6 +11,7 @@ import Common.Annex
import Assistant import Assistant
import Command import Command
import Option import Option
import Utility.HumanTime
def :: [Command] def :: [Command]
def = [notBareRepo $ withOptions [foregroundOption, stopOption] $ def = [notBareRepo $ withOptions [foregroundOption, stopOption] $
@ -19,7 +20,7 @@ def = [notBareRepo $ withOptions [foregroundOption, stopOption] $
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFlag stopOption $ \stopdaemon -> seek = [withFlag stopOption $ \stopdaemon ->
withFlag foregroundOption $ \foreground -> withFlag foregroundOption $ \foreground ->
withNothing $ start False foreground stopdaemon] withNothing $ start False foreground stopdaemon Nothing]
foregroundOption :: Option foregroundOption :: Option
foregroundOption = Option.flag [] "foreground" "do not daemonize" foregroundOption = Option.flag [] "foreground" "do not daemonize"
@ -27,9 +28,9 @@ foregroundOption = Option.flag [] "foreground" "do not daemonize"
stopOption :: Option stopOption :: Option
stopOption = Option.flag [] "stop" "stop daemon" stopOption = Option.flag [] "stop" "stop daemon"
start :: Bool -> Bool -> Bool -> CommandStart start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start assistant foreground stopdaemon = do start assistant foreground stopdaemon startdelay = do
if stopdaemon if stopdaemon
then stopDaemon then stopDaemon
else startDaemon assistant foreground Nothing Nothing -- does not return else startDaemon assistant foreground startdelay Nothing Nothing -- does not return
stop stop

View file

@ -69,7 +69,7 @@ start' allowauto listenhost = do
url <- liftIO . readFile url <- liftIO . readFile
=<< fromRepo gitAnnexUrlFile =<< fromRepo gitAnnexUrlFile
liftIO $ openBrowser browser f url Nothing Nothing liftIO $ openBrowser browser f url Nothing Nothing
, startDaemon True True listenhost $ Just $ , startDaemon True True Nothing listenhost $ Just $
\origout origerr url htmlshim -> \origout origerr url htmlshim ->
if isJust listenhost if isJust listenhost
then maybe noop (`hPutStrLn` url) origout then maybe noop (`hPutStrLn` url) origout
@ -155,7 +155,7 @@ firstRun listenhost = do
_wait <- takeMVar v _wait <- takeMVar v
state <- Annex.new =<< Git.CurrentRepo.get state <- Annex.new =<< Git.CurrentRepo.get
Annex.eval state $ Annex.eval state $
startDaemon True True listenhost $ Just $ startDaemon True True Nothing listenhost $ Just $
sendurlback v sendurlback v
sendurlback v _origout _origerr url _htmlshim = do sendurlback v _origout _origerr url _htmlshim = do
recordUrl url recordUrl url

7
debian/changelog vendored
View file

@ -1,3 +1,10 @@
git-annex (4.20131025) UNRELEASED; urgency=low
* assistant: When autostarted, wait 5 seconds before running the startup
scan, to avoid contending with the user's desktop login process.
-- Joey Hess <joeyh@debian.org> Sat, 26 Oct 2013 12:11:48 -0400
git-annex (4.20131024) unstable; urgency=low git-annex (4.20131024) unstable; urgency=low
* webapp: Fix bug when adding a remote and git-remote-gcrypt * webapp: Fix bug when adding a remote and git-remote-gcrypt

View file

@ -18,3 +18,7 @@ to
Exec=sleep 5 ionice -c 3 /usr/bin/git-annex assistant --autostart Exec=sleep 5 ionice -c 3 /usr/bin/git-annex assistant --autostart
This delays the start of git-annex for 5 seconds, letting the desktop get started, and forces git-annex to yield IO to other programs -preventing it from slowing them down by forcing them to wait for disk access. Since this is a background daemon with potentially high IO usage, but no need for quick responsiveness, perhaps that would make a decent default? This delays the start of git-annex for 5 seconds, letting the desktop get started, and forces git-annex to yield IO to other programs -preventing it from slowing them down by forcing them to wait for disk access. Since this is a background daemon with potentially high IO usage, but no need for quick responsiveness, perhaps that would make a decent default?
> Added 5 second delay to existing ionice. Provisionally [[done]],
> although it does occur to me that the startup scan could add some delays
> in between actions to run more as a batch job. --[[Joey]]