2012-06-13 16:36:33 +00:00
|
|
|
{- git-annex assistant daemon
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012-2013 Joey Hess <id@joeyh.name>
|
2012-06-13 16:36:33 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-06-13 16:36:33 +00:00
|
|
|
-}
|
|
|
|
|
2012-07-26 01:26:13 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
2021-04-05 17:40:31 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2012-07-26 01:26:13 +00:00
|
|
|
|
2012-06-13 16:36:33 +00:00
|
|
|
module Assistant where
|
|
|
|
|
2013-05-25 04:37:41 +00:00
|
|
|
import qualified Annex
|
2012-07-20 23:29:59 +00:00
|
|
|
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
|
2012-09-06 18:56:04 +00:00
|
|
|
import Assistant.Threads.DaemonStatus
|
2012-06-25 20:10:10 +00:00
|
|
|
import Assistant.Threads.Watcher
|
|
|
|
import Assistant.Threads.Committer
|
|
|
|
import Assistant.Threads.Pusher
|
2017-09-20 18:37:20 +00:00
|
|
|
import Assistant.Threads.Exporter
|
2012-06-25 20:10:10 +00:00
|
|
|
import Assistant.Threads.Merger
|
2012-07-03 14:58:40 +00:00
|
|
|
import Assistant.Threads.TransferWatcher
|
2012-07-05 20:34:20 +00:00
|
|
|
import Assistant.Threads.Transferrer
|
2014-04-08 19:23:50 +00:00
|
|
|
import Assistant.Threads.RemoteControl
|
2012-06-25 20:10:10 +00:00
|
|
|
import Assistant.Threads.SanityChecker
|
2013-10-08 15:48:28 +00:00
|
|
|
import Assistant.Threads.Cronner
|
2013-10-29 18:22:56 +00:00
|
|
|
import Assistant.Threads.ProblemFixer
|
2016-02-15 15:47:33 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2012-07-19 17:01:41 +00:00
|
|
|
import Assistant.Threads.MountWatcher
|
2013-03-12 09:48:41 +00:00
|
|
|
#endif
|
2012-08-21 23:58:53 +00:00
|
|
|
import Assistant.Threads.NetWatcher
|
2013-11-21 21:49:56 +00:00
|
|
|
import Assistant.Threads.Upgrader
|
2013-11-22 22:46:45 +00:00
|
|
|
import Assistant.Threads.UpgradeWatcher
|
2012-07-23 03:16:56 +00:00
|
|
|
import Assistant.Threads.TransferScanner
|
2012-08-28 18:04:28 +00:00
|
|
|
import Assistant.Threads.TransferPoller
|
add ConfigMonitor thread
Monitors git-annex branch for changes, which are noticed by the Merger
thread whenever the branch ref is changed (either due to an incoming push,
or a local change), and refreshes cached config values for modified config
files.
Rate limited to run no more often than once per minute. This is important
because frequent git-annex branch changes happen when files are being
added, or transferred, etc.
A primary use case is that, when preferred content changes are made,
and get pushed to remotes, the remotes start honoring those settings.
Other use cases include propigating repository description and trust
changes to remotes, and learning when a remote has added a new special
remote, so the webapp can present the GUI to enable that special remote
locally.
Also added a uuid.log cache. All other config files already had caches.
2012-10-20 20:37:06 +00:00
|
|
|
import Assistant.Threads.ConfigMonitor
|
2012-11-29 18:49:20 +00:00
|
|
|
import Assistant.Threads.Glacier
|
2012-07-26 01:26:13 +00:00
|
|
|
#ifdef WITH_WEBAPP
|
2012-09-08 23:57:15 +00:00
|
|
|
import Assistant.WebApp
|
2012-07-26 01:26:13 +00:00
|
|
|
import Assistant.Threads.WebApp
|
2012-09-08 19:07:44 +00:00
|
|
|
#ifdef WITH_PAIRING
|
|
|
|
import Assistant.Threads.PairListener
|
|
|
|
#endif
|
2012-07-27 16:14:57 +00:00
|
|
|
#else
|
2013-04-04 05:48:26 +00:00
|
|
|
import Assistant.Types.UrlRenderer
|
2012-07-26 01:26:13 +00:00
|
|
|
#endif
|
2012-06-13 16:36:33 +00:00
|
|
|
import qualified Utility.Daemon
|
2013-01-26 06:09:33 +00:00
|
|
|
import Utility.ThreadScheduler
|
2013-10-26 16:42:58 +00:00
|
|
|
import Utility.HumanTime
|
2014-02-25 18:09:39 +00:00
|
|
|
import Annex.Perms
|
2020-04-09 17:54:43 +00:00
|
|
|
import Annex.BranchState
|
2014-06-17 23:10:51 +00:00
|
|
|
import Utility.LogFile
|
2021-05-12 19:08:03 +00:00
|
|
|
import Annex.Path
|
2014-06-17 23:10:51 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
|
|
|
import Utility.Env
|
|
|
|
import System.Environment (getArgs)
|
2014-02-25 18:09:39 +00:00
|
|
|
#endif
|
2021-04-05 17:40:31 +00:00
|
|
|
import qualified Utility.Debug as Debug
|
2012-09-06 18:56:04 +00:00
|
|
|
|
2024-01-25 18:08:36 +00:00
|
|
|
import Network.Socket (HostName, PortNumber)
|
2013-03-27 16:37:15 +00:00
|
|
|
|
2012-08-01 20:10:26 +00:00
|
|
|
stopDaemon :: Annex ()
|
2020-11-04 18:20:37 +00:00
|
|
|
stopDaemon = liftIO . Utility.Daemon.stopDaemon . fromRawFilePath
|
|
|
|
=<< fromRepo gitAnnexPidFile
|
2012-08-01 20:10:26 +00:00
|
|
|
|
2013-01-15 17:34:59 +00:00
|
|
|
{- 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. -}
|
2024-01-25 18:08:36 +00:00
|
|
|
startDaemon :: Bool -> Bool -> Maybe Duration -> Maybe String -> Maybe HostName -> Maybe PortNumber -> Maybe (Maybe Handle -> Maybe Handle -> String -> FilePath -> IO ()) -> Annex ()
|
|
|
|
startDaemon assistant foreground startdelay cannotrun listenhost listenport startbrowser = do
|
2013-05-25 04:37:41 +00:00
|
|
|
Annex.changeState $ \s -> s { Annex.daemon = True }
|
2020-07-06 16:09:53 +00:00
|
|
|
enableInteractiveBranchAccess
|
2013-01-15 17:34:59 +00:00
|
|
|
pidfile <- fromRepo gitAnnexPidFile
|
2020-10-21 14:31:56 +00:00
|
|
|
logfile <- fromRepo gitAnnexDaemonLogFile
|
2021-04-05 17:40:31 +00:00
|
|
|
liftIO $ Debug.debug "Assistant" $ "logging to " ++ fromRawFilePath logfile
|
2020-03-05 18:56:47 +00:00
|
|
|
createAnnexDirectory (parentDir pidfile)
|
2014-06-17 23:10:51 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2015-01-09 17:11:56 +00:00
|
|
|
createAnnexDirectory (parentDir logfile)
|
2021-05-12 19:08:03 +00:00
|
|
|
let logfd = handleToFd =<< openLog (fromRawFilePath logfile)
|
2013-01-15 17:34:59 +00:00
|
|
|
if foreground
|
|
|
|
then do
|
|
|
|
origout <- liftIO $ catchMaybeIO $
|
|
|
|
fdToHandle =<< dup stdOutput
|
|
|
|
origerr <- liftIO $ catchMaybeIO $
|
|
|
|
fdToHandle =<< dup stdError
|
2020-11-04 18:20:37 +00:00
|
|
|
let undaemonize = Utility.Daemon.foreground logfd (Just (fromRawFilePath pidfile))
|
2013-05-09 16:02:31 +00:00
|
|
|
start undaemonize $
|
2013-01-15 17:34:59 +00:00
|
|
|
case startbrowser of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just a -> Just $ a origout origerr
|
2021-05-12 19:08:03 +00:00
|
|
|
else do
|
|
|
|
git_annex <- liftIO programPath
|
|
|
|
ps <- gitAnnexDaemonizeParams
|
|
|
|
start (Utility.Daemon.daemonize git_annex ps logfd (Just (fromRawFilePath pidfile)) False) Nothing
|
2013-11-12 18:54:02 +00:00
|
|
|
#else
|
2014-06-17 23:10:51 +00:00
|
|
|
-- Windows doesn't daemonize, but does redirect output to the
|
|
|
|
-- log file. The only way to do so is to restart the program.
|
2014-02-25 18:09:39 +00:00
|
|
|
when (foreground || not foreground) $ do
|
2014-06-17 23:10:51 +00:00
|
|
|
let flag = "GIT_ANNEX_OUTPUT_REDIR"
|
2015-01-09 17:11:56 +00:00
|
|
|
createAnnexDirectory (parentDir logfile)
|
2014-06-17 23:10:51 +00:00
|
|
|
ifM (liftIO $ isNothing <$> getEnv flag)
|
2020-06-03 19:18:48 +00:00
|
|
|
( liftIO $ withNullHandle $ \nullh -> do
|
2020-11-19 16:33:00 +00:00
|
|
|
loghandle <- openLog (fromRawFilePath logfile)
|
2014-06-17 23:10:51 +00:00
|
|
|
e <- getEnvironment
|
2015-02-28 21:23:13 +00:00
|
|
|
cmd <- programPath
|
2014-06-17 23:10:51 +00:00
|
|
|
ps <- getArgs
|
2020-06-03 19:18:48 +00:00
|
|
|
let p = (proc cmd ps)
|
2014-06-17 23:10:51 +00:00
|
|
|
{ env = Just (addEntry flag "1" e)
|
|
|
|
, std_in = UseHandle nullh
|
|
|
|
, std_out = UseHandle loghandle
|
|
|
|
, std_err = UseHandle loghandle
|
|
|
|
}
|
2020-06-03 19:18:48 +00:00
|
|
|
exitcode <- withCreateProcess p $ \_ _ _ pid ->
|
|
|
|
waitForProcess pid
|
|
|
|
exitWith exitcode
|
2020-11-19 16:33:00 +00:00
|
|
|
, start (Utility.Daemon.foreground (Just (fromRawFilePath pidfile))) $
|
2014-06-17 23:10:51 +00:00
|
|
|
case startbrowser of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just a -> Just $ a Nothing Nothing
|
|
|
|
)
|
2013-11-12 18:54:02 +00:00
|
|
|
#endif
|
2012-10-29 02:09:09 +00:00
|
|
|
where
|
2013-01-15 17:34:59 +00:00
|
|
|
start daemonize webappwaiter = withThreadState $ \st -> do
|
|
|
|
checkCanWatch
|
|
|
|
dstatus <- startDaemonStatus
|
2020-10-21 14:31:56 +00:00
|
|
|
logfile <- fromRepo gitAnnexDaemonLogFile
|
2021-04-05 17:40:31 +00:00
|
|
|
liftIO $ Debug.debug "Assistant" $ "logging to " ++ fromRawFilePath logfile
|
2013-01-15 17:34:59 +00:00
|
|
|
liftIO $ daemonize $
|
|
|
|
flip runAssistant (go webappwaiter)
|
|
|
|
=<< newAssistantData st dstatus
|
2012-08-01 20:10:26 +00:00
|
|
|
|
2012-09-23 15:48:09 +00:00
|
|
|
#ifdef WITH_WEBAPP
|
2013-04-03 21:44:34 +00:00
|
|
|
go webappwaiter = do
|
2013-01-26 03:14:32 +00:00
|
|
|
d <- getAssistant id
|
2013-02-06 19:38:41 +00:00
|
|
|
#else
|
2013-04-03 21:44:34 +00:00
|
|
|
go _webappwaiter = do
|
2012-09-23 15:48:09 +00:00
|
|
|
#endif
|
2013-04-03 21:44:34 +00:00
|
|
|
urlrenderer <- liftIO newUrlRenderer
|
2012-08-02 13:09:06 +00:00
|
|
|
#ifdef WITH_WEBAPP
|
2024-01-25 18:08:36 +00:00
|
|
|
let webappthread = [ assist $ webAppThread d urlrenderer False cannotrun Nothing listenhost listenport 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
|
2012-08-02 13:09:06 +00:00
|
|
|
#endif
|
2014-10-09 19:35:19 +00:00
|
|
|
, assist pushThread
|
|
|
|
, assist pushRetryThread
|
2017-09-20 18:37:20 +00:00
|
|
|
, assist exportThread
|
|
|
|
, assist exportRetryThread
|
2014-10-09 19:35:19 +00:00
|
|
|
, assist mergeThread
|
|
|
|
, assist transferWatcherThread
|
|
|
|
, assist transferPollerThread
|
|
|
|
, assist transfererThread
|
|
|
|
, assist remoteControlThread
|
|
|
|
, assist daemonStatusThread
|
assistant unused file handling
Make sanity checker run git annex unused daily, and queue up transfers
of unused files to any remotes that will have them. The transfer retrying
code works for us here, so eg when a backup disk remote is plugged in,
any transfers to it are done. Once the unused files reach a remote,
they'll be removed locally as unwanted.
If the setup does not cause unused files to go to a remote, they'll pile
up, and the sanity checker detects this using some heuristics that are
pretty good -- 1000 unused files, or 10% of disk used by unused files,
or more disk wasted by unused files than is left free. Once it detects
this, it pops up an alert in the webapp, with a button to take action.
TODO: Webapp UI to configure this, and also the ability to launch an
immediate cleanup of all unused files.
This commit was sponsored by Simon Michael.
2014-01-23 02:48:56 +00:00
|
|
|
, assist $ sanityCheckerDailyThread urlrenderer
|
2014-10-09 19:35:19 +00:00
|
|
|
, assist sanityCheckerHourlyThread
|
2013-11-17 18:58:35 +00:00
|
|
|
, assist $ problemFixerThread urlrenderer
|
2016-02-15 15:47:33 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2013-11-17 18:58:35 +00:00
|
|
|
, assist $ mountWatcherThread urlrenderer
|
2013-03-12 09:48:41 +00:00
|
|
|
#endif
|
2014-10-09 19:35:19 +00:00
|
|
|
, assist netWatcherThread
|
2013-11-21 21:49:56 +00:00
|
|
|
, assist $ upgraderThread urlrenderer
|
2013-11-24 17:20:58 +00:00
|
|
|
, 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-01-15 17:34:59 +00:00
|
|
|
|
2013-11-17 18:58:35 +00:00
|
|
|
mapM_ (startthread urlrenderer) threads
|
2013-01-26 06:09:33 +00:00
|
|
|
liftIO waitForTermination
|
2012-10-25 19:30:49 +00:00
|
|
|
|
2012-10-29 02:09:09 +00:00
|
|
|
watch a = (True, a)
|
|
|
|
assist a = (False, a)
|
2013-01-26 06:09:33 +00:00
|
|
|
startthread urlrenderer (watcher, t)
|
2013-02-06 19:38:41 +00:00
|
|
|
| watcher || assistant = startNamedThread urlrenderer t
|
2012-10-29 02:09:09 +00:00
|
|
|
| otherwise = noop
|