aboutsummaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-08-02 00:42:33 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-08-02 00:42:33 -0400
commit60da0d6ad28bff7c601ba631a8ec65030f940367 (patch)
tree56b137977c3f88c46e406859db8457a08fb80371 /Command
parent23fe661d37ceb6c7bf754e9dc8fd5dda89793b63 (diff)
full autostart support
git annex assistant --autostart will start separate daemons in each listed autostart repo running the webapp outside any git-annex repo will open it on the first listed autostart repo
Diffstat (limited to 'Command')
-rw-r--r--Command/Assistant.hs58
-rw-r--r--Command/Watch.hs9
-rw-r--r--Command/WebApp.hs39
3 files changed, 89 insertions, 17 deletions
diff --git a/Command/Assistant.hs b/Command/Assistant.hs
index 60eac5d21..24cc3ec6c 100644
--- a/Command/Assistant.hs
+++ b/Command/Assistant.hs
@@ -7,12 +7,66 @@
module Command.Assistant where
+import Common.Annex
import Command
+import qualified Option
import qualified Command.Watch
+import Init
+import Locations.UserConfig
+
+import System.Environment
+import System.Posix.Directory
def :: [Command]
-def = [withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $
+def = [noRepo checkAutoStart $ dontCheck repoExists $
+ withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption, autoStartOption] $
command "assistant" paramNothing seek "automatically handle changes"]
+autoStartOption :: Option
+autoStartOption = Option.flag [] "autostart" "start in known repositories"
+
seek :: [CommandSeek]
-seek = Command.Watch.mkSeek True
+seek = [withFlag Command.Watch.stopOption $ \stopdaemon ->
+ withFlag Command.Watch.foregroundOption $ \foreground ->
+ withFlag autoStartOption $ \autostart ->
+ withNothing $ start foreground stopdaemon autostart]
+
+start :: Bool -> Bool -> Bool -> CommandStart
+start foreground stopdaemon autostart
+ | autostart = do
+ liftIO $ autoStart
+ stop
+ | otherwise = do
+ ensureInitialized
+ Command.Watch.start True foreground stopdaemon
+
+{- Run outside a git repository. Check to see if any parameter is
+ - --autostart and enter autostart mode. -}
+checkAutoStart :: IO ()
+checkAutoStart = ifM (any (== "--autostart") <$> getArgs)
+ ( autoStart
+ , error "Not in a git repository."
+ )
+
+autoStart :: IO ()
+autoStart = do
+ autostartfile <- autoStartFile
+ let nothing = error $ "Nothing listed in " ++ autostartfile
+ ifM (doesFileExist autostartfile)
+ ( do
+ dirs <- lines <$> readFile autostartfile
+ programfile <- programFile
+ program <- catchDefaultIO (readFile programfile) "git-annex"
+ when (null dirs) nothing
+ forM_ dirs $ \d -> do
+ putStrLn $ "git-annex autostart in " ++ d
+ ifM (catchBoolIO $ go program d)
+ ( putStrLn "ok"
+ , putStrLn "failed"
+ )
+ , nothing
+ )
+ where
+ go program dir = do
+ changeWorkingDirectory dir
+ boolSystem program [Param "assistant"]
diff --git a/Command/Watch.hs b/Command/Watch.hs
index 61c859106..eb70ef6b1 100644
--- a/Command/Watch.hs
+++ b/Command/Watch.hs
@@ -16,13 +16,10 @@ def :: [Command]
def = [withOptions [foregroundOption, stopOption] $
command "watch" paramNothing seek "watch for changes"]
-mkSeek :: Bool -> [CommandSeek]
-mkSeek assistant = [withFlag stopOption $ \stopdaemon ->
- withFlag foregroundOption $ \foreground ->
- withNothing $ start assistant foreground stopdaemon]
-
seek :: [CommandSeek]
-seek = mkSeek False
+seek = [withFlag stopOption $ \stopdaemon ->
+ withFlag foregroundOption $ \foreground ->
+ withNothing $ start False foreground stopdaemon]
foregroundOption :: Option
foregroundOption = Option.flag [] "foreground" "do not daemonize"
diff --git a/Command/WebApp.hs b/Command/WebApp.hs
index f143d8667..d3153f630 100644
--- a/Command/WebApp.hs
+++ b/Command/WebApp.hs
@@ -18,12 +18,14 @@ import Utility.Daemon (checkDaemon, lockPidFile)
import Init
import qualified Git.CurrentRepo
import qualified Annex
+import Locations.UserConfig
+import System.Posix.Directory
import Control.Concurrent
import Control.Concurrent.STM
def :: [Command]
-def = [oneShot $ noRepo firstRun $ dontCheck repoExists $
+def = [oneShot $ noRepo startNoRepo $ dontCheck repoExists $
command "webapp" paramNothing seek "launch webapp"]
seek :: [CommandSeek]
@@ -31,7 +33,7 @@ seek = [withNothing start]
start :: CommandStart
start = notBareRepo $ do
- ifM (isInitialized) ( go , liftIO firstRun )
+ ifM (isInitialized) ( go , liftIO startNoRepo )
stop
where
go = do
@@ -46,14 +48,24 @@ start = notBareRepo $ do
liftIO $ isJust <$> checkDaemon pidfile
checkshim f = liftIO $ doesFileExist f
-openBrowser :: FilePath -> IO ()
-openBrowser htmlshim = unlessM (runBrowser url) $
- error $ "failed to start web browser on url " ++ url
- where
- url = fileUrl htmlshim
+{- When run without a repo, see if there is an autoStartFile,
+ - and if so, start the first available listed repository.
+ - If not, it's our first time being run! -}
+startNoRepo :: IO ()
+startNoRepo = do
+ autostartfile <- autoStartFile
+ ifM (doesFileExist autostartfile) ( autoStart autostartfile , firstRun )
-fileUrl :: FilePath -> String
-fileUrl file = "file://" ++ file
+autoStart :: FilePath -> IO ()
+autoStart autostartfile = do
+ dirs <- lines <$> readFile autostartfile
+ edirs <- filterM doesDirectoryExist dirs
+ case edirs of
+ [] -> firstRun -- what else can I do? Nothing works..
+ (d:_) -> do
+ changeWorkingDirectory d
+ state <- Annex.new =<< Git.CurrentRepo.get
+ void $ Annex.eval state $ doCommand start
{- Run the webapp without a repository, which prompts the user, makes one,
- changes to it, starts the regular assistant, and redirects the
@@ -92,3 +104,12 @@ firstRun = do
{- Set up the pid file in the new repo. -}
dummydaemonize = do
liftIO . lockPidFile =<< fromRepo gitAnnexPidFile
+
+openBrowser :: FilePath -> IO ()
+openBrowser htmlshim = unlessM (runBrowser url) $
+ error $ "failed to start web browser on url " ++ url
+ where
+ url = fileUrl htmlshim
+
+fileUrl :: FilePath -> String
+fileUrl file = "file://" ++ file