git-annex/Assistant/Restart.hs

116 lines
3.3 KiB
Haskell
Raw Normal View History

{- git-annex assistant restarting
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
2013-12-04 19:37:53 +00:00
{-# LANGUAGE CPP #-}
module Assistant.Restart where
import Assistant.Common
import Assistant.Threads.Watcher
import Assistant.DaemonStatus
import Assistant.NamedThread
import Utility.ThreadScheduler
import Utility.NotificationBroadcaster
import Utility.Url
2014-02-11 19:29:56 +00:00
import Utility.PID
import qualified Git.Construct
import qualified Git.Config
import Config.Files
import qualified Annex
import qualified Git
import Control.Concurrent
import System.Process (cwd)
2013-12-04 19:37:53 +00:00
#ifndef mingw32_HOST_OS
2014-02-11 19:29:56 +00:00
import System.Posix (signalProcess, sigTERM)
#else
import Utility.WinProcess
2013-12-04 19:37:53 +00:00
#endif
2014-02-25 02:00:25 +00:00
import Data.Default
2014-03-01 02:20:54 +00:00
import Network.URI
{- Before the assistant can be restarted, have to remove our
- gitAnnexUrlFile and our gitAnnexPidFile. Pausing the watcher is also
- a good idea, to avoid fighting when two assistants are running in the
- same repo.
-}
prepRestart :: Assistant ()
prepRestart = do
liftIO . maybe noop (`throwTo` PauseWatcher) =<< namedThreadId watchThread
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexUrlFile)
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexPidFile)
{- To finish a restart, send a global redirect to the new url
- to any web browsers that are displaying the webapp.
-
- Wait for browser to update before terminating this process. -}
postRestart :: URLString -> Assistant ()
postRestart url = do
modifyDaemonStatus_ $ \status -> status { globalRedirUrl = Just url }
liftIO . sendNotification . globalRedirNotifier =<< getDaemonStatus
void $ liftIO $ forkIO $ do
threadDelaySeconds (Seconds 120)
#ifndef mingw32_HOST_OS
2014-02-11 19:29:56 +00:00
signalProcess sigTERM =<< getPID
2013-12-04 19:37:53 +00:00
#else
terminatePID =<< getPID
2013-12-04 19:37:53 +00:00
#endif
runRestart :: Assistant URLString
runRestart = liftIO . newAssistantUrl
=<< liftAnnex (Git.repoLocation <$> Annex.gitRepo)
{- Starts up the assistant in the repository, and waits for it to create
- a gitAnnexUrlFile. Waits for the assistant to be up and listening for
- connections by testing the url. -}
newAssistantUrl :: FilePath -> IO URLString
newAssistantUrl repo = do
startAssistant repo
geturl
where
geturl = do
r <- Git.Config.read =<< Git.Construct.fromPath repo
waiturl $ gitAnnexUrlFile r
waiturl urlfile = do
v <- tryIO $ readFile urlfile
case v of
Left _ -> delayed $ waiturl urlfile
2014-03-01 02:20:54 +00:00
Right url -> ifM (assistantListening url)
( return url
, delayed $ waiturl urlfile
)
delayed a = do
threadDelay 100000 -- 1/10th of a second
a
2014-03-01 02:20:54 +00:00
{- Checks if the assistant is listening on an url.
-
- Always checks http, because https with self-signed cert is problimatic.
- warp-tls listens to http, in order to show an error page, so this works.
-}
assistantListening :: URLString -> IO Bool
assistantListening url = catchBoolIO $ fst <$> exists url' def
where
url' = case parseURI url of
Nothing -> url
Just uri -> show $ uri
{ uriScheme = "http:"
}
{- Does not wait for assistant to be listening for web connections.
-
- On windows, the assistant does not daemonize, which is why the forkIO is
- done.
-}
startAssistant :: FilePath -> IO ()
startAssistant repo = void $ forkIO $ do
program <- readProgramFile
(_, _, _, pid) <-
createProcess $
(proc program ["assistant"]) { cwd = Just repo }
void $ checkSuccessProcess pid