much better webapp startup of the assistant
This avoids forking another process, avoids polling, fixes a race, and avoids a rare forkProcess thread hang that I saw once time when starting the webapp.
This commit is contained in:
parent
bc5b151617
commit
02ec8ea012
5 changed files with 27 additions and 40 deletions
|
@ -124,8 +124,8 @@ import Utility.ThreadScheduler
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
|
||||||
startDaemon :: Bool -> Bool -> Annex ()
|
startDaemon :: Bool -> Bool -> Maybe (IO ()) -> Annex ()
|
||||||
startDaemon assistant foreground
|
startDaemon assistant foreground webappwaiter
|
||||||
| foreground = do
|
| foreground = do
|
||||||
showStart (if assistant then "assistant" else "watch") "."
|
showStart (if assistant then "assistant" else "watch") "."
|
||||||
go id
|
go id
|
||||||
|
@ -157,12 +157,11 @@ startDaemon assistant foreground
|
||||||
, mountWatcherThread st dstatus scanremotes
|
, mountWatcherThread st dstatus scanremotes
|
||||||
, transferScannerThread st scanremotes transferqueue
|
, transferScannerThread st scanremotes transferqueue
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
, webAppThread st dstatus transferqueue
|
, webAppThread st dstatus transferqueue webappwaiter
|
||||||
#endif
|
#endif
|
||||||
, watchThread st dstatus transferqueue changechan
|
, watchThread st dstatus transferqueue changechan
|
||||||
]
|
]
|
||||||
debug "assistant"
|
debug "Assistant" ["all threads started"]
|
||||||
["all git-annex assistant threads started"]
|
|
||||||
waitForTermination
|
waitForTermination
|
||||||
|
|
||||||
stopDaemon :: Annex ()
|
stopDaemon :: Annex ()
|
||||||
|
|
|
@ -145,15 +145,17 @@ getConfigR = defaultLayout $ do
|
||||||
setTitle "configuration"
|
setTitle "configuration"
|
||||||
[whamlet|<a href="@{HomeR}">main|]
|
[whamlet|<a href="@{HomeR}">main|]
|
||||||
|
|
||||||
webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO ()
|
webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO ()
|
||||||
webAppThread st dstatus transferqueue = do
|
webAppThread st dstatus transferqueue onstartup = do
|
||||||
webapp <- mkWebApp
|
webapp <- mkWebApp
|
||||||
app <- toWaiAppPlain webapp
|
app <- toWaiAppPlain webapp
|
||||||
app' <- ifM debugEnabled
|
app' <- ifM debugEnabled
|
||||||
( return $ httpDebugLogger app
|
( return $ httpDebugLogger app
|
||||||
, return app
|
, return app
|
||||||
)
|
)
|
||||||
runWebApp app' $ \port -> runThreadState st $ writeHtmlShim webapp port
|
runWebApp app' $ \port -> do
|
||||||
|
runThreadState st $ writeHtmlShim webapp port
|
||||||
|
maybe noop id onstartup
|
||||||
where
|
where
|
||||||
mkWebApp = do
|
mkWebApp = do
|
||||||
dir <- absPath =<< runThreadState st (fromRepo repoPath)
|
dir <- absPath =<< runThreadState st (fromRepo repoPath)
|
||||||
|
|
|
@ -34,5 +34,5 @@ start :: Bool -> Bool -> Bool -> CommandStart
|
||||||
start assistant foreground stopdaemon = notBareRepo $ do
|
start assistant foreground stopdaemon = notBareRepo $ do
|
||||||
if stopdaemon
|
if stopdaemon
|
||||||
then stopDaemon
|
then stopDaemon
|
||||||
else startDaemon assistant foreground -- does not return
|
else startDaemon assistant foreground Nothing -- does not return
|
||||||
stop
|
stop
|
||||||
|
|
|
@ -12,12 +12,8 @@ import Command
|
||||||
import Assistant
|
import Assistant
|
||||||
import Utility.WebApp
|
import Utility.WebApp
|
||||||
import Utility.Daemon (checkDaemon)
|
import Utility.Daemon (checkDaemon)
|
||||||
import qualified Annex
|
|
||||||
import Option
|
import Option
|
||||||
|
|
||||||
import Control.Concurrent
|
|
||||||
import System.Posix.Process
|
|
||||||
|
|
||||||
def :: [Command]
|
def :: [Command]
|
||||||
def = [withOptions [restartOption] $
|
def = [withOptions [restartOption] $
|
||||||
command "webapp" paramNothing seek "launch webapp"]
|
command "webapp" paramNothing seek "launch webapp"]
|
||||||
|
@ -34,31 +30,20 @@ start restart = notBareRepo $ do
|
||||||
if restart
|
if restart
|
||||||
then do
|
then do
|
||||||
stopDaemon
|
stopDaemon
|
||||||
nuke =<< fromRepo gitAnnexPidFile
|
void $ liftIO . nukeFile =<< fromRepo gitAnnexPidFile
|
||||||
startassistant f
|
startassistant f
|
||||||
else unlessM (checkpid f) $
|
else ifM (checkpid <&&> checkshim f) $
|
||||||
startassistant f
|
( liftIO $ go f
|
||||||
let url = "file://" ++ f
|
, startassistant f
|
||||||
ifM (liftIO $ runBrowser url)
|
)
|
||||||
( stop
|
stop
|
||||||
, error $ "failed to start web browser on url " ++ url
|
|
||||||
)
|
|
||||||
where
|
where
|
||||||
nuke f = void $ liftIO $ catchMaybeIO $ removeFile f
|
checkpid = do
|
||||||
checkpid f = do
|
|
||||||
pidfile <- fromRepo gitAnnexPidFile
|
pidfile <- fromRepo gitAnnexPidFile
|
||||||
liftIO $
|
liftIO $ isJust <$> checkDaemon pidfile
|
||||||
doesFileExist f <&&> (isJust <$> checkDaemon pidfile)
|
checkshim f = liftIO $ doesFileExist f
|
||||||
startassistant f = do
|
startassistant = startDaemon True False . Just . go
|
||||||
nuke f
|
go f = unlessM (runBrowser url) $
|
||||||
{- Fork a separate process to run the assistant,
|
error $ "failed to start web browser on url " ++ url
|
||||||
- with a copy of the Annex state. -}
|
where
|
||||||
state <- Annex.getState id
|
url = "file://" ++ f
|
||||||
liftIO $ void $ forkProcess $
|
|
||||||
Annex.eval state $ startDaemon True False
|
|
||||||
waitdaemon f (1000 :: Int)
|
|
||||||
waitdaemon _ 0 = error "failed to start git-annex assistant"
|
|
||||||
waitdaemon f n = unlessM (checkpid f) $ do
|
|
||||||
-- wait 0.1 seconds before retry
|
|
||||||
liftIO $ threadDelay 100000
|
|
||||||
waitdaemon f (n - 1)
|
|
||||||
|
|
|
@ -32,6 +32,7 @@ import Blaze.ByteString.Builder.Char.Utf8 (fromText)
|
||||||
import Blaze.ByteString.Builder (Builder)
|
import Blaze.ByteString.Builder (Builder)
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
localhost :: String
|
localhost :: String
|
||||||
localhost = "localhost"
|
localhost = "localhost"
|
||||||
|
@ -52,12 +53,12 @@ runBrowser url = boolSystem cmd [Param url]
|
||||||
-
|
-
|
||||||
- An IO action can also be run, to do something with the port number,
|
- An IO action can also be run, to do something with the port number,
|
||||||
- such as start a web browser to view the webapp.
|
- such as start a web browser to view the webapp.
|
||||||
-}
|
-}
|
||||||
runWebApp :: Application -> (PortNumber -> IO ()) -> IO ()
|
runWebApp :: Application -> (PortNumber -> IO ()) -> IO ()
|
||||||
runWebApp app observer = do
|
runWebApp app observer = do
|
||||||
sock <- localSocket
|
sock <- localSocket
|
||||||
|
void $ forkIO $ runSettingsSocket defaultSettings sock app
|
||||||
observer =<< socketPort sock
|
observer =<< socketPort sock
|
||||||
runSettingsSocket defaultSettings sock app
|
|
||||||
|
|
||||||
{- Binds to a local socket, selecting any free port.
|
{- Binds to a local socket, selecting any free port.
|
||||||
-
|
-
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue