convert WebApp; avoid duplicate arg parsing for no repo mode
This commit is contained in:
parent
b95a48fe45
commit
fd086c5752
2 changed files with 39 additions and 44 deletions
|
@ -101,7 +101,7 @@ import qualified Command.Version
|
||||||
import qualified Command.Watch
|
import qualified Command.Watch
|
||||||
import qualified Command.Assistant
|
import qualified Command.Assistant
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
--import qualified Command.WebApp
|
import qualified Command.WebApp
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_XMPP
|
#ifdef WITH_XMPP
|
||||||
import qualified Command.XMPPGit
|
import qualified Command.XMPPGit
|
||||||
|
@ -206,7 +206,7 @@ cmds =
|
||||||
, Command.Watch.cmd
|
, Command.Watch.cmd
|
||||||
, Command.Assistant.cmd
|
, Command.Assistant.cmd
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
-- , Command.WebApp.cmd
|
, Command.WebApp.cmd
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_XMPP
|
#ifdef WITH_XMPP
|
||||||
, Command.XMPPGit.cmd
|
, Command.XMPPGit.cmd
|
||||||
|
|
|
@ -34,35 +34,37 @@ import Annex.Version
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Network.Socket (HostName)
|
|
||||||
import System.Environment (getArgs)
|
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = withOptions [listenOption] $
|
cmd = noCommit $ dontCheck repoExists $ notBareRepo $
|
||||||
noCommit $ dontCheck repoExists $ notBareRepo $
|
noRepo (startNoRepo <$$> optParser) $
|
||||||
noRepo (withParams startNoRepo) $
|
|
||||||
command "webapp" SectionCommon "launch webapp"
|
command "webapp" SectionCommon "launch webapp"
|
||||||
paramNothing (withParams seek)
|
paramNothing (seek <$$> optParser)
|
||||||
|
|
||||||
listenOption :: Option
|
data WebAppOptions = WebAppOptions
|
||||||
listenOption = fieldOption [] "listen" paramAddress
|
{ listenAddress :: Maybe String
|
||||||
"accept connections to this address"
|
}
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
optParser :: CmdParamsDesc -> Parser WebAppOptions
|
||||||
seek ps = do
|
optParser _ = WebAppOptions
|
||||||
listenhost <- getOptionField listenOption return
|
<$> optional (strOption
|
||||||
withNothing (start listenhost) ps
|
( long "listen" <> metavar paramAddress
|
||||||
|
<> help "accept connections to this address"
|
||||||
|
))
|
||||||
|
|
||||||
start :: Maybe HostName -> CommandStart
|
seek :: WebAppOptions -> CommandSeek
|
||||||
|
seek = commandAction . start
|
||||||
|
|
||||||
|
start :: WebAppOptions -> CommandStart
|
||||||
start = start' True
|
start = start' True
|
||||||
|
|
||||||
start' :: Bool -> Maybe HostName -> CommandStart
|
start' :: Bool -> WebAppOptions -> CommandStart
|
||||||
start' allowauto listenhost = do
|
start' allowauto o = do
|
||||||
liftIO ensureInstalled
|
liftIO ensureInstalled
|
||||||
ifM isInitialized
|
ifM isInitialized
|
||||||
( maybe notinitialized (go <=< needsUpgrade) =<< getVersion
|
( maybe notinitialized (go <=< needsUpgrade) =<< getVersion
|
||||||
, if allowauto
|
, if allowauto
|
||||||
then liftIO $ startNoRepo []
|
then liftIO $ startNoRepo o
|
||||||
else notinitialized
|
else notinitialized
|
||||||
)
|
)
|
||||||
stop
|
stop
|
||||||
|
@ -70,22 +72,22 @@ start' allowauto listenhost = do
|
||||||
go cannotrun = do
|
go cannotrun = do
|
||||||
browser <- fromRepo webBrowser
|
browser <- fromRepo webBrowser
|
||||||
f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim
|
f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim
|
||||||
listenhost' <- if isJust listenhost
|
listenAddress' <- if isJust (listenAddress o)
|
||||||
then pure listenhost
|
then pure (listenAddress o)
|
||||||
else annexListen <$> Annex.getGitConfig
|
else annexListen <$> Annex.getGitConfig
|
||||||
ifM (checkpid <&&> checkshim f)
|
ifM (checkpid <&&> checkshim f)
|
||||||
( if isJust listenhost
|
( if isJust (listenAddress o)
|
||||||
then error "The assistant is already running, so --listen cannot be used."
|
then error "The assistant is already running, so --listen cannot be used."
|
||||||
else do
|
else do
|
||||||
url <- liftIO . readFile
|
url <- liftIO . readFile
|
||||||
=<< fromRepo gitAnnexUrlFile
|
=<< fromRepo gitAnnexUrlFile
|
||||||
liftIO $ if isJust listenhost'
|
liftIO $ if isJust listenAddress'
|
||||||
then putStrLn url
|
then putStrLn url
|
||||||
else liftIO $ openBrowser browser f url Nothing Nothing
|
else liftIO $ openBrowser browser f url Nothing Nothing
|
||||||
, do
|
, do
|
||||||
startDaemon True True Nothing cannotrun listenhost' $ Just $
|
startDaemon True True Nothing cannotrun listenAddress' $ Just $
|
||||||
\origout origerr url htmlshim ->
|
\origout origerr url htmlshim ->
|
||||||
if isJust listenhost'
|
if isJust listenAddress'
|
||||||
then maybe noop (`hPutStrLn` url) origout
|
then maybe noop (`hPutStrLn` url) origout
|
||||||
else openBrowser browser htmlshim url origout origerr
|
else openBrowser browser htmlshim url origout origerr
|
||||||
)
|
)
|
||||||
|
@ -96,34 +98,27 @@ start' allowauto listenhost = do
|
||||||
notinitialized = do
|
notinitialized = do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
liftIO $ cannotStartIn (Git.repoLocation g) "repository has not been initialized by git-annex"
|
liftIO $ cannotStartIn (Git.repoLocation g) "repository has not been initialized by git-annex"
|
||||||
liftIO $ firstRun listenhost
|
liftIO $ firstRun o
|
||||||
|
|
||||||
{- When run without a repo, start the first available listed repository in
|
{- When run without a repo, start the first available listed repository in
|
||||||
- the autostart file. If none, it's our first time being run! -}
|
- the autostart file. If none, it's our first time being run! -}
|
||||||
startNoRepo :: CmdParams -> IO ()
|
startNoRepo :: WebAppOptions -> IO ()
|
||||||
startNoRepo _ = do
|
startNoRepo o = go =<< liftIO (filterM doesDirectoryExist =<< readAutoStartFile)
|
||||||
-- FIXME should be able to reuse regular getopt, but
|
|
||||||
-- it currently runs in the Annex monad.
|
|
||||||
args <- getArgs
|
|
||||||
let listenhost = headMaybe $ map (snd . separate (== '=')) $
|
|
||||||
filter ("--listen=" `isPrefixOf`) args
|
|
||||||
|
|
||||||
go listenhost =<< liftIO (filterM doesDirectoryExist =<< readAutoStartFile)
|
|
||||||
where
|
where
|
||||||
go listenhost [] = firstRun listenhost
|
go [] = firstRun o
|
||||||
go listenhost (d:ds) = do
|
go (d:ds) = do
|
||||||
v <- tryNonAsync $ do
|
v <- tryNonAsync $ do
|
||||||
setCurrentDirectory d
|
setCurrentDirectory d
|
||||||
Annex.new =<< Git.CurrentRepo.get
|
Annex.new =<< Git.CurrentRepo.get
|
||||||
case v of
|
case v of
|
||||||
Left e -> do
|
Left e -> do
|
||||||
cannotStartIn d (show e)
|
cannotStartIn d (show e)
|
||||||
go listenhost ds
|
go ds
|
||||||
Right state -> void $ Annex.eval state $ do
|
Right state -> void $ Annex.eval state $ do
|
||||||
whenM (fromRepo Git.repoIsLocalBare) $
|
whenM (fromRepo Git.repoIsLocalBare) $
|
||||||
error $ d ++ " is a bare git repository, cannot run the webapp in it"
|
error $ d ++ " is a bare git repository, cannot run the webapp in it"
|
||||||
callCommandAction $
|
callCommandAction $
|
||||||
start' False listenhost
|
start' False o
|
||||||
|
|
||||||
cannotStartIn :: FilePath -> String -> IO ()
|
cannotStartIn :: FilePath -> String -> IO ()
|
||||||
cannotStartIn d reason = warningIO $ "unable to start webapp in repository " ++ d ++ ": " ++ reason
|
cannotStartIn d reason = warningIO $ "unable to start webapp in repository " ++ d ++ ": " ++ reason
|
||||||
|
@ -141,8 +136,8 @@ cannotStartIn d reason = warningIO $ "unable to start webapp in repository " ++
|
||||||
- Note that it's important that mainthread never terminates! Much
|
- Note that it's important that mainthread never terminates! Much
|
||||||
- of this complication is due to needing to keep the mainthread running.
|
- of this complication is due to needing to keep the mainthread running.
|
||||||
-}
|
-}
|
||||||
firstRun :: Maybe HostName -> IO ()
|
firstRun :: WebAppOptions -> IO ()
|
||||||
firstRun listenhost = do
|
firstRun o = do
|
||||||
checkEnvironmentIO
|
checkEnvironmentIO
|
||||||
{- Without a repository, we cannot have an Annex monad, so cannot
|
{- Without a repository, we cannot have an Annex monad, so cannot
|
||||||
- get a ThreadState. This is only safe because the
|
- get a ThreadState. This is only safe because the
|
||||||
|
@ -159,7 +154,7 @@ firstRun listenhost = do
|
||||||
startNamedThread urlrenderer $
|
startNamedThread urlrenderer $
|
||||||
webAppThread d urlrenderer True Nothing
|
webAppThread d urlrenderer True Nothing
|
||||||
(callback signaler)
|
(callback signaler)
|
||||||
listenhost
|
(listenAddress o)
|
||||||
(callback mainthread)
|
(callback mainthread)
|
||||||
waitNamedThreads
|
waitNamedThreads
|
||||||
where
|
where
|
||||||
|
@ -167,7 +162,7 @@ firstRun listenhost = do
|
||||||
putMVar v ""
|
putMVar v ""
|
||||||
takeMVar v
|
takeMVar v
|
||||||
mainthread v url htmlshim
|
mainthread v url htmlshim
|
||||||
| isJust listenhost = do
|
| isJust (listenAddress o)= do
|
||||||
putStrLn url
|
putStrLn url
|
||||||
hFlush stdout
|
hFlush stdout
|
||||||
go
|
go
|
||||||
|
@ -181,7 +176,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 Nothing Nothing listenhost $ Just $
|
startDaemon True True Nothing Nothing (listenAddress o) $ Just $
|
||||||
sendurlback v
|
sendurlback v
|
||||||
sendurlback v _origout _origerr url _htmlshim = do
|
sendurlback v _origout _origerr url _htmlshim = do
|
||||||
recordUrl url
|
recordUrl url
|
||||||
|
|
Loading…
Reference in a new issue