git-annex/Assistant.hs

197 lines
5.9 KiB
Haskell
Raw Normal View History

2012-06-13 16:36:33 +00:00
{- git-annex assistant daemon
-
- Copyright 2012-2013 Joey Hess <joey@kitenet.net>
2012-06-13 16:36:33 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
2012-06-13 16:36:33 +00:00
module Assistant where
import qualified Annex
import Assistant.Common
2012-06-13 16:36:33 +00:00
import Assistant.DaemonStatus
2012-10-30 18:34:48 +00:00
import Assistant.NamedThread
2012-10-29 23:07:10 +00:00
import Assistant.Types.ThreadedMonad
import Assistant.Threads.DaemonStatus
2012-06-25 20:10:10 +00:00
import Assistant.Threads.Watcher
import Assistant.Threads.Committer
import Assistant.Threads.Pusher
import Assistant.Threads.Merger
import Assistant.Threads.TransferWatcher
2012-07-05 20:34:20 +00:00
import Assistant.Threads.Transferrer
import Assistant.Threads.RemoteControl
2012-06-25 20:10:10 +00:00
import Assistant.Threads.SanityChecker
import Assistant.Threads.Cronner
2013-10-29 18:22:56 +00:00
import Assistant.Threads.ProblemFixer
#ifdef WITH_CLIBS
import Assistant.Threads.MountWatcher
#endif
import Assistant.Threads.NetWatcher
import Assistant.Threads.Upgrader
import Assistant.Threads.UpgradeWatcher
import Assistant.Threads.TransferScanner
2012-08-28 18:04:28 +00:00
import Assistant.Threads.TransferPoller
import Assistant.Threads.ConfigMonitor
import Assistant.Threads.Glacier
#ifdef WITH_WEBAPP
import Assistant.WebApp
import Assistant.Threads.WebApp
2012-09-08 19:07:44 +00:00
#ifdef WITH_PAIRING
import Assistant.Threads.PairListener
#endif
#ifdef WITH_XMPP
import Assistant.Threads.XMPPClient
import Assistant.Threads.XMPPPusher
#endif
#else
2013-04-04 05:48:26 +00:00
import Assistant.Types.UrlRenderer
#endif
2012-06-13 16:36:33 +00:00
import qualified Utility.Daemon
import Utility.ThreadScheduler
import Utility.HumanTime
import qualified Build.SysConfig as SysConfig
import Annex.Perms
import Utility.LogFile
#ifdef mingw32_HOST_OS
import Utility.Env
import Config.Files
import System.Environment (getArgs)
#endif
import System.Log.Logger
import Network.Socket (HostName)
stopDaemon :: Annex ()
stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile
{- Starts the daemon. If the daemon is run in the foreground, once it's
- running, can start the browser.
-
- startbrowser is passed the url and html shim file, as well as the original
- stdout and stderr descriptors. -}
2013-11-17 18:58:35 +00:00
startDaemon :: Bool -> Bool -> Maybe Duration -> Maybe String -> Maybe HostName -> Maybe (Maybe Handle -> Maybe Handle -> String -> FilePath -> IO ()) -> Annex ()
startDaemon assistant foreground startdelay cannotrun listenhost startbrowser = do
Annex.changeState $ \s -> s { Annex.daemon = True }
pidfile <- fromRepo gitAnnexPidFile
logfile <- fromRepo gitAnnexLogFile
2014-07-16 20:14:51 +00:00
liftIO $ debugM desc $ "logging to " ++ logfile
#ifndef mingw32_HOST_OS
createAnnexDirectory (parentDir logfile)
logfd <- liftIO $ handleToFd =<< openLog logfile
if foreground
then do
origout <- liftIO $ catchMaybeIO $
fdToHandle =<< dup stdOutput
origerr <- liftIO $ catchMaybeIO $
fdToHandle =<< dup stdError
let undaemonize = Utility.Daemon.foreground logfd (Just pidfile)
start undaemonize $
case startbrowser of
Nothing -> Nothing
Just a -> Just $ a origout origerr
else
start (Utility.Daemon.daemonize logfd (Just pidfile) False) Nothing
#else
-- Windows doesn't daemonize, but does redirect output to the
-- log file. The only way to do so is to restart the program.
when (foreground || not foreground) $ do
let flag = "GIT_ANNEX_OUTPUT_REDIR"
createAnnexDirectory (parentDir logfile)
ifM (liftIO $ isNothing <$> getEnv flag)
( liftIO $ withFile devNull WriteMode $ \nullh -> do
loghandle <- openLog logfile
e <- getEnvironment
cmd <- readProgramFile
ps <- getArgs
(_, _, _, pid) <- createProcess (proc cmd ps)
{ env = Just (addEntry flag "1" e)
, std_in = UseHandle nullh
, std_out = UseHandle loghandle
, std_err = UseHandle loghandle
}
exitWith =<< waitForProcess pid
, start (Utility.Daemon.foreground (Just pidfile)) $
case startbrowser of
Nothing -> Nothing
Just a -> Just $ a Nothing Nothing
)
#endif
2012-10-29 02:09:09 +00:00
where
desc
2013-03-12 10:45:56 +00:00
| assistant = "assistant"
| otherwise = "watch"
start daemonize webappwaiter = withThreadState $ \st -> do
checkCanWatch
dstatus <- startDaemonStatus
logfile <- fromRepo gitAnnexLogFile
liftIO $ debugM desc $ "logging to " ++ logfile
liftIO $ daemonize $
flip runAssistant (go webappwaiter)
=<< newAssistantData st dstatus
2012-09-23 15:48:09 +00:00
#ifdef WITH_WEBAPP
go webappwaiter = do
2013-01-26 03:14:32 +00:00
d <- getAssistant id
#else
go _webappwaiter = do
2012-09-23 15:48:09 +00:00
#endif
notice ["starting", desc, "version", SysConfig.packageversion]
urlrenderer <- liftIO newUrlRenderer
#ifdef WITH_WEBAPP
let webappthread = [ assist $ webAppThread d urlrenderer False cannotrun Nothing listenhost webappwaiter ]
2013-11-17 18:58:35 +00:00
#else
let webappthread = []
#endif
let threads = if isJust cannotrun
then webappthread
else webappthread ++
2014-10-09 19:35:19 +00:00
[ watch commitThread
2013-11-17 18:58:35 +00:00
#ifdef WITH_WEBAPP
2012-09-08 19:07:44 +00:00
#ifdef WITH_PAIRING
2013-11-17 18:58:35 +00:00
, assist $ pairListenerThread urlrenderer
2012-09-08 19:07:44 +00:00
#endif
#ifdef WITH_XMPP
2013-11-17 18:58:35 +00:00
, assist $ xmppClientThread urlrenderer
, assist $ xmppSendPackThread urlrenderer
, assist $ xmppReceivePackThread urlrenderer
#endif
#endif
2014-10-09 19:35:19 +00:00
, assist pushThread
, assist pushRetryThread
, assist mergeThread
, assist transferWatcherThread
, assist transferPollerThread
, assist transfererThread
, assist remoteControlThread
, assist daemonStatusThread
, assist $ sanityCheckerDailyThread urlrenderer
2014-10-09 19:35:19 +00:00
, assist sanityCheckerHourlyThread
2013-11-17 18:58:35 +00:00
, assist $ problemFixerThread urlrenderer
#ifdef WITH_CLIBS
2013-11-17 18:58:35 +00:00
, assist $ mountWatcherThread urlrenderer
#endif
2014-10-09 19:35:19 +00:00
, assist netWatcherThread
, assist $ upgraderThread urlrenderer
, assist $ upgradeWatcherThread urlrenderer
2014-10-09 19:35:19 +00:00
, assist netWatcherFallbackThread
2013-11-17 18:58:35 +00:00
, assist $ transferScannerThread urlrenderer
, assist $ cronnerThread urlrenderer
2014-10-09 19:35:19 +00:00
, assist configMonitorThread
, assist glacierThread
, watch watchThread
2013-11-17 18:58:35 +00:00
-- must come last so that all threads that wait
-- on it have already started waiting
, watch $ sanityCheckerStartupThread startdelay
]
2013-11-17 18:58:35 +00:00
mapM_ (startthread urlrenderer) threads
liftIO waitForTermination
2012-10-29 02:09:09 +00:00
watch a = (True, a)
assist a = (False, a)
startthread urlrenderer (watcher, t)
| watcher || assistant = startNamedThread urlrenderer t
2012-10-29 02:09:09 +00:00
| otherwise = noop