2012-06-13 16:36:33 +00:00
|
|
|
{- git-annex assistant daemon status
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012 Joey Hess <id@joeyh.name>
|
2012-06-23 05:20:40 +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
|
|
|
-}
|
|
|
|
|
2014-01-06 01:30:48 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
|
|
|
|
2012-06-13 16:36:33 +00:00
|
|
|
module Assistant.DaemonStatus where
|
|
|
|
|
2012-10-30 18:34:48 +00:00
|
|
|
import Assistant.Common
|
2013-04-04 05:48:26 +00:00
|
|
|
import Assistant.Alert.Utility
|
2013-05-12 23:19:28 +00:00
|
|
|
import Utility.Tmp
|
2012-07-28 20:01:50 +00:00
|
|
|
import Utility.NotificationBroadcaster
|
2023-08-16 18:31:31 +00:00
|
|
|
import Types.Availability
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2012-07-05 16:21:22 +00:00
|
|
|
import Logs.Transfer
|
2012-08-26 19:39:02 +00:00
|
|
|
import Logs.Trust
|
2018-10-30 03:13:36 +00:00
|
|
|
import Utility.TimeStamp
|
2012-08-26 18:56:26 +00:00
|
|
|
import qualified Remote
|
2012-10-11 23:22:29 +00:00
|
|
|
import qualified Types.Remote as Remote
|
2017-08-17 16:26:14 +00:00
|
|
|
import Config.DynamicConfig
|
2020-01-15 17:19:02 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2012-06-13 16:36:33 +00:00
|
|
|
|
2012-07-28 22:02:11 +00:00
|
|
|
import Control.Concurrent.STM
|
2012-06-13 16:36:33 +00:00
|
|
|
import System.Posix.Types
|
2012-06-13 17:35:15 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
2018-04-22 17:28:31 +00:00
|
|
|
import qualified Data.Map.Strict as M
|
2014-04-09 19:26:41 +00:00
|
|
|
import qualified Data.Set as S
|
2012-06-13 16:36:33 +00:00
|
|
|
|
2012-10-30 18:44:18 +00:00
|
|
|
getDaemonStatus :: Assistant DaemonStatus
|
2016-09-30 23:51:16 +00:00
|
|
|
getDaemonStatus = (atomically . readTVar) <<~ daemonStatusHandle
|
2012-06-13 16:36:33 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
modifyDaemonStatus_ :: (DaemonStatus -> DaemonStatus) -> Assistant ()
|
|
|
|
modifyDaemonStatus_ a = modifyDaemonStatus $ \s -> (a s, ())
|
2012-07-06 22:44:13 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
modifyDaemonStatus :: (DaemonStatus -> (DaemonStatus, b)) -> Assistant b
|
|
|
|
modifyDaemonStatus a = do
|
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ do
|
|
|
|
(s, b) <- atomically $ do
|
2016-09-30 23:51:16 +00:00
|
|
|
r@(!s, _) <- a <$> readTVar dstatus
|
|
|
|
writeTVar dstatus s
|
2012-10-30 19:39:15 +00:00
|
|
|
return r
|
|
|
|
sendNotification $ changeNotifier s
|
|
|
|
return b
|
|
|
|
|
2013-03-15 22:12:45 +00:00
|
|
|
{- Returns a function that updates the lists of syncable remotes
|
|
|
|
- and other associated information. -}
|
2012-11-11 20:23:16 +00:00
|
|
|
calcSyncRemotes :: Annex (DaemonStatus -> DaemonStatus)
|
2012-10-14 18:47:01 +00:00
|
|
|
calcSyncRemotes = do
|
2017-08-17 16:26:14 +00:00
|
|
|
rs <- filterM (liftIO . getDynamicConfig . remoteAnnexSync . Remote.gitconfig)
|
|
|
|
=<< (concat . Remote.byCost <$> Remote.remoteList)
|
2012-11-11 04:26:29 +00:00
|
|
|
alive <- trustExclude DeadTrusted (map Remote.uuid rs)
|
2012-08-26 19:39:02 +00:00
|
|
|
let good r = Remote.uuid r `elem` alive
|
2012-11-11 20:23:16 +00:00
|
|
|
let syncable = filter good rs
|
2017-09-20 17:27:59 +00:00
|
|
|
contentremotes <- filterM (not <$$> liftIO . getDynamicConfig . remoteAnnexIgnore . Remote.gitconfig) $
|
2018-06-04 18:31:55 +00:00
|
|
|
filter (\r -> Remote.uuid r /= NoUUID) syncable
|
2020-12-18 19:11:53 +00:00
|
|
|
let (exportremotes, nonexportremotes) = partition (exportTree . Remote.config) contentremotes
|
2020-12-21 17:46:04 +00:00
|
|
|
let isimport r = importTree (Remote.config r) || Remote.thirdPartyPopulated (Remote.remotetype r)
|
|
|
|
let dataremotes = filter (not . isimport) nonexportremotes
|
2023-08-16 18:31:31 +00:00
|
|
|
tocloud <- anyM iscloud contentremotes
|
2013-03-15 22:12:45 +00:00
|
|
|
|
2012-11-11 20:23:16 +00:00
|
|
|
return $ \dstatus -> dstatus
|
|
|
|
{ syncRemotes = syncable
|
2024-05-24 18:52:22 +00:00
|
|
|
, syncGitRemotes = filter Remote.gitSyncableRemote syncable
|
2017-09-20 17:27:59 +00:00
|
|
|
, syncDataRemotes = dataremotes
|
|
|
|
, exportRemotes = exportremotes
|
|
|
|
, downloadRemotes = contentremotes
|
2023-08-16 18:31:31 +00:00
|
|
|
, syncingToCloudRemote = tocloud
|
2012-11-11 20:23:16 +00:00
|
|
|
}
|
2013-03-15 23:16:13 +00:00
|
|
|
where
|
2023-08-16 18:31:31 +00:00
|
|
|
iscloud r
|
|
|
|
| Remote.readonly r = pure False
|
|
|
|
| otherwise = tryNonAsync (Remote.availability r) >>= return . \case
|
|
|
|
Right GloballyAvailable -> True
|
|
|
|
_ -> False
|
2012-08-26 18:56:26 +00:00
|
|
|
|
2013-03-28 21:11:53 +00:00
|
|
|
{- Updates the syncRemotes list from the list of all remotes in Annex state. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
updateSyncRemotes :: Assistant ()
|
2012-11-13 21:50:54 +00:00
|
|
|
updateSyncRemotes = do
|
|
|
|
modifyDaemonStatus_ =<< liftAnnex calcSyncRemotes
|
2013-03-15 22:12:45 +00:00
|
|
|
status <- getDaemonStatus
|
|
|
|
liftIO $ sendNotification $ syncRemotesNotifier status
|
2013-03-15 23:16:13 +00:00
|
|
|
|
2013-03-15 22:12:45 +00:00
|
|
|
when (syncingToCloudRemote status) $
|
|
|
|
updateAlertMap $
|
|
|
|
M.filter $ \alert ->
|
|
|
|
alertName alert /= Just CloudRepoNeededAlert
|
2012-07-22 19:06:18 +00:00
|
|
|
|
2014-04-09 19:26:41 +00:00
|
|
|
changeCurrentlyConnected :: (S.Set UUID -> S.Set UUID) -> Assistant ()
|
|
|
|
changeCurrentlyConnected sm = do
|
|
|
|
modifyDaemonStatus_ $ \ds -> ds
|
|
|
|
{ currentlyConnectedRemotes = sm (currentlyConnectedRemotes ds)
|
|
|
|
}
|
|
|
|
v <- currentlyConnectedRemotes <$> getDaemonStatus
|
|
|
|
debug [show v]
|
|
|
|
liftIO . sendNotification =<< syncRemotesNotifier <$> getDaemonStatus
|
|
|
|
|
2013-10-08 15:48:28 +00:00
|
|
|
updateScheduleLog :: Assistant ()
|
|
|
|
updateScheduleLog =
|
|
|
|
liftIO . sendNotification =<< scheduleLogNotifier <$> getDaemonStatus
|
|
|
|
|
2012-07-28 22:02:11 +00:00
|
|
|
{- Load any previous daemon status file, and store it in a MVar for this
|
2012-07-02 20:11:04 +00:00
|
|
|
- process to use as its DaemonStatus. Also gets current transfer status. -}
|
2012-06-13 18:02:40 +00:00
|
|
|
startDaemonStatus :: Annex DaemonStatusHandle
|
|
|
|
startDaemonStatus = do
|
|
|
|
file <- fromRepo gitAnnexDaemonStatusFile
|
|
|
|
status <- liftIO $
|
2012-09-17 04:18:07 +00:00
|
|
|
flip catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus
|
2012-07-02 20:11:04 +00:00
|
|
|
transfers <- M.fromList <$> getTransfers
|
2012-11-11 20:23:16 +00:00
|
|
|
addsync <- calcSyncRemotes
|
2016-09-30 23:51:16 +00:00
|
|
|
liftIO $ atomically $ newTVar $ addsync $ status
|
2012-06-13 21:54:23 +00:00
|
|
|
{ scanComplete = False
|
|
|
|
, sanityCheckRunning = False
|
2012-07-02 20:11:04 +00:00
|
|
|
, currentTransfers = transfers
|
2012-06-13 21:54:23 +00:00
|
|
|
}
|
2012-06-13 18:02:40 +00:00
|
|
|
|
2012-06-13 17:35:15 +00:00
|
|
|
{- Don't just dump out the structure, because it will change over time,
|
|
|
|
- and parts of it are not relevant. -}
|
|
|
|
writeDaemonStatusFile :: FilePath -> DaemonStatus -> IO ()
|
|
|
|
writeDaemonStatusFile file status =
|
|
|
|
viaTmp writeFile file =<< serialized <$> getPOSIXTime
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
serialized now = unlines
|
|
|
|
[ "lastRunning:" ++ show now
|
|
|
|
, "scanComplete:" ++ show (scanComplete status)
|
|
|
|
, "sanityCheckRunning:" ++ show (sanityCheckRunning status)
|
|
|
|
, "lastSanityCheck:" ++ maybe "" show (lastSanityCheck status)
|
|
|
|
]
|
2012-06-13 17:35:15 +00:00
|
|
|
|
|
|
|
readDaemonStatusFile :: FilePath -> IO DaemonStatus
|
2012-07-28 20:01:50 +00:00
|
|
|
readDaemonStatusFile file = parse <$> newDaemonStatus <*> readFile file
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
parse status = foldr parseline status . lines
|
|
|
|
parseline line status
|
2015-05-10 18:45:55 +00:00
|
|
|
| key == "lastRunning" = parseval parsePOSIXTime $ \v ->
|
2012-10-31 06:34:03 +00:00
|
|
|
status { lastRunning = Just v }
|
|
|
|
| key == "scanComplete" = parseval readish $ \v ->
|
|
|
|
status { scanComplete = v }
|
|
|
|
| key == "sanityCheckRunning" = parseval readish $ \v ->
|
|
|
|
status { sanityCheckRunning = v }
|
2015-05-10 18:45:55 +00:00
|
|
|
| key == "lastSanityCheck" = parseval parsePOSIXTime $ \v ->
|
2012-10-31 06:34:03 +00:00
|
|
|
status { lastSanityCheck = Just v }
|
|
|
|
| otherwise = status -- unparsable line
|
|
|
|
where
|
|
|
|
(key, value) = separate (== ':') line
|
|
|
|
parseval parser a = maybe status a (parser value)
|
2012-06-13 17:35:15 +00:00
|
|
|
|
|
|
|
{- Checks if a time stamp was made after the daemon was lastRunning.
|
|
|
|
-
|
|
|
|
- Some slop is built in; this really checks if the time stamp was made
|
|
|
|
- at least ten minutes after the daemon was lastRunning. This is to
|
|
|
|
- ensure the daemon shut down cleanly, and deal with minor clock skew.
|
|
|
|
-
|
|
|
|
- If the daemon has never ran before, this always returns False.
|
|
|
|
-}
|
|
|
|
afterLastDaemonRun :: EpochTime -> DaemonStatus -> Bool
|
2012-06-13 18:02:40 +00:00
|
|
|
afterLastDaemonRun timestamp status = maybe False (< t) (lastRunning status)
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
t = realToFrac (timestamp + slop) :: POSIXTime
|
|
|
|
slop = fromIntegral tenMinutes
|
2012-06-13 18:19:21 +00:00
|
|
|
|
|
|
|
tenMinutes :: Int
|
|
|
|
tenMinutes = 10 * 60
|
2012-07-05 20:34:20 +00:00
|
|
|
|
2012-07-28 22:47:24 +00:00
|
|
|
{- Mutates the transfer map. Runs in STM so that the transfer map can
|
|
|
|
- be modified in the same transaction that modifies the transfer queue.
|
|
|
|
- Note that this does not send a notification of the change; that's left
|
|
|
|
- to the caller. -}
|
|
|
|
adjustTransfersSTM :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> STM ()
|
|
|
|
adjustTransfersSTM dstatus a = do
|
2016-09-30 23:51:16 +00:00
|
|
|
s <- readTVar dstatus
|
2014-01-06 01:30:48 +00:00
|
|
|
let !v = a (currentTransfers s)
|
2016-09-30 23:51:16 +00:00
|
|
|
writeTVar dstatus $ s { currentTransfers = v }
|
2012-07-28 22:47:24 +00:00
|
|
|
|
2013-04-02 20:17:06 +00:00
|
|
|
{- Checks if a transfer is currently running. -}
|
|
|
|
checkRunningTransferSTM :: DaemonStatusHandle -> Transfer -> STM Bool
|
|
|
|
checkRunningTransferSTM dstatus t = M.member t . currentTransfers
|
2016-09-30 23:51:16 +00:00
|
|
|
<$> readTVar dstatus
|
2013-04-02 20:17:06 +00:00
|
|
|
|
2012-08-28 18:19:11 +00:00
|
|
|
{- Alters a transfer's info, if the transfer is in the map. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
alterTransferInfo :: Transfer -> (TransferInfo -> TransferInfo) -> Assistant ()
|
|
|
|
alterTransferInfo t a = updateTransferInfo' $ M.adjust a t
|
2012-08-28 18:19:11 +00:00
|
|
|
|
2012-08-29 18:14:57 +00:00
|
|
|
{- Updates a transfer's info. Adds the transfer to the map if necessary,
|
2012-08-31 17:06:27 +00:00
|
|
|
- or if already present, updates it while preserving the old transferTid,
|
|
|
|
- transferPaused, and bytesComplete values, which are not written to disk. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
updateTransferInfo :: Transfer -> TransferInfo -> Assistant ()
|
2018-04-22 17:28:31 +00:00
|
|
|
updateTransferInfo t info = updateTransferInfo' $ M.insertWith merge t info
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
merge new old = new
|
|
|
|
{ transferTid = maybe (transferTid new) Just (transferTid old)
|
|
|
|
, transferPaused = transferPaused new || transferPaused old
|
|
|
|
, bytesComplete = maybe (bytesComplete new) Just (bytesComplete old)
|
|
|
|
}
|
2012-08-28 18:19:11 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
updateTransferInfo' :: (TransferMap -> TransferMap) -> Assistant ()
|
|
|
|
updateTransferInfo' a = notifyTransfer `after` modifyDaemonStatus_ update
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
update s = s { currentTransfers = a (currentTransfers s) }
|
2012-07-06 22:44:13 +00:00
|
|
|
|
|
|
|
{- Removes a transfer from the map, and returns its info. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
removeTransfer :: Transfer -> Assistant (Maybe TransferInfo)
|
|
|
|
removeTransfer t = notifyTransfer `after` modifyDaemonStatus remove
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
remove s =
|
|
|
|
let (info, ts) = M.updateLookupWithKey
|
|
|
|
(\_k _v -> Nothing)
|
|
|
|
t (currentTransfers s)
|
|
|
|
in (s { currentTransfers = ts }, info)
|
2012-07-29 12:52:57 +00:00
|
|
|
|
|
|
|
{- Send a notification when a transfer is changed. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
notifyTransfer :: Assistant ()
|
|
|
|
notifyTransfer = do
|
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ sendNotification
|
2016-09-30 23:51:16 +00:00
|
|
|
=<< transferNotifier <$> atomically (readTVar dstatus)
|
2012-10-30 19:39:15 +00:00
|
|
|
|
2012-07-29 13:35:01 +00:00
|
|
|
{- Send a notification when alerts are changed. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
notifyAlert :: Assistant ()
|
|
|
|
notifyAlert = do
|
|
|
|
dstatus <- getAssistant daemonStatusHandle
|
|
|
|
liftIO $ sendNotification
|
2016-09-30 23:51:16 +00:00
|
|
|
=<< alertNotifier <$> atomically (readTVar dstatus)
|
2012-10-30 18:34:48 +00:00
|
|
|
|
|
|
|
{- Returns the alert's identifier, which can be used to remove it. -}
|
2012-10-30 19:39:15 +00:00
|
|
|
addAlert :: Alert -> Assistant AlertId
|
2021-04-05 17:40:31 +00:00
|
|
|
addAlert alert = notifyAlert `after` modifyDaemonStatus add
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
add s = (s { lastAlertId = i, alertMap = m }, i)
|
|
|
|
where
|
2014-01-06 01:30:48 +00:00
|
|
|
!i = nextAlertId $ lastAlertId s
|
|
|
|
!m = mergeAlert i alert (alertMap s)
|
2012-10-30 18:34:48 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
removeAlert :: AlertId -> Assistant ()
|
|
|
|
removeAlert i = updateAlert i (const Nothing)
|
2012-10-30 18:34:48 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
updateAlert :: AlertId -> (Alert -> Maybe Alert) -> Assistant ()
|
|
|
|
updateAlert i a = updateAlertMap $ \m -> M.update a i m
|
2012-10-30 18:34:48 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
updateAlertMap :: (AlertMap -> AlertMap) -> Assistant ()
|
|
|
|
updateAlertMap a = notifyAlert `after` modifyDaemonStatus_ update
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
2014-01-06 01:30:48 +00:00
|
|
|
update s =
|
|
|
|
let !m = a (alertMap s)
|
2014-01-06 20:04:09 +00:00
|
|
|
in s { alertMap = m }
|
2012-10-30 18:34:48 +00:00
|
|
|
|
|
|
|
{- Displays an alert while performing an activity that returns True on
|
|
|
|
- success.
|
|
|
|
-
|
|
|
|
- The alert is left visible afterwards, as filler.
|
|
|
|
- Old filler is pruned, to prevent the map growing too large. -}
|
|
|
|
alertWhile :: Alert -> Assistant Bool -> Assistant Bool
|
|
|
|
alertWhile alert a = alertWhile' alert $ do
|
|
|
|
r <- a
|
|
|
|
return (r, r)
|
|
|
|
|
|
|
|
{- Like alertWhile, but allows the activity to return a value too. -}
|
|
|
|
alertWhile' :: Alert -> Assistant (Bool, a) -> Assistant a
|
|
|
|
alertWhile' alert a = do
|
|
|
|
let alert' = alert { alertClass = Activity }
|
2012-10-30 19:39:15 +00:00
|
|
|
i <- addAlert alert'
|
2012-10-30 18:34:48 +00:00
|
|
|
(ok, r) <- a
|
2012-10-30 19:39:15 +00:00
|
|
|
updateAlertMap $ mergeAlert i $ makeAlertFiller ok alert'
|
2012-10-30 18:34:48 +00:00
|
|
|
return r
|
|
|
|
|
|
|
|
{- Displays an alert while performing an activity, then removes it. -}
|
|
|
|
alertDuring :: Alert -> Assistant a -> Assistant a
|
|
|
|
alertDuring alert a = do
|
2012-10-30 19:39:15 +00:00
|
|
|
i <- addAlert $ alert { alertClass = Activity }
|
|
|
|
removeAlert i `after` a
|