git-annex/Assistant/DaemonStatus.hs

276 lines
9.8 KiB
Haskell
Raw Normal View History

2012-06-13 16:36:33 +00:00
{- git-annex assistant daemon status
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
2012-06-23 05:20:40 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
2012-06-13 16:36:33 +00:00
-}
module Assistant.DaemonStatus where
import Common.Annex
2012-06-13 18:02:40 +00:00
import Assistant.ThreadedMonad
2012-07-29 13:35:01 +00:00
import Assistant.Alert
import Utility.ThreadScheduler
import Utility.TempFile
import Utility.NotificationBroadcaster
import Logs.Transfer
import Logs.Trust
import qualified Remote
2012-06-13 16:36:33 +00:00
import Control.Concurrent.STM
2012-06-13 16:36:33 +00:00
import System.Posix.Types
import Data.Time.Clock.POSIX
import Data.Time
import System.Locale
2012-07-02 20:11:04 +00:00
import qualified Data.Map as M
2012-06-13 16:36:33 +00:00
data DaemonStatus = DaemonStatus
-- False when the daemon is performing its startup scan
{ scanComplete :: Bool
-- Time when a previous process of the daemon was running ok
, lastRunning :: Maybe POSIXTime
-- True when the sanity checker is running
, sanityCheckRunning :: Bool
-- Last time the sanity checker ran
, lastSanityCheck :: Maybe POSIXTime
2012-07-02 20:11:04 +00:00
-- Currently running file content transfers
2012-07-05 20:34:20 +00:00
, currentTransfers :: TransferMap
2012-07-29 13:35:01 +00:00
-- Messages to display to the user.
, alertMap :: AlertMap
2012-08-06 21:09:23 +00:00
, lastAlertId :: AlertId
-- Ordered list of remotes to talk to.
, knownRemotes :: [Remote]
2012-07-29 12:52:57 +00:00
-- Broadcasts notifications about all changes to the DaemonStatus
, changeNotifier :: NotificationBroadcaster
2012-07-29 13:35:01 +00:00
-- Broadcasts notifications when queued or current transfers change.
2012-07-29 12:52:57 +00:00
, transferNotifier :: NotificationBroadcaster
2012-07-29 13:35:01 +00:00
-- Broadcasts notifications when there's a change to the alerts
, alertNotifier :: NotificationBroadcaster
2012-06-13 16:36:33 +00:00
}
2012-07-05 20:34:20 +00:00
type TransferMap = M.Map Transfer TransferInfo
{- This TMVar is never left empty, so accessing it will never block. -}
type DaemonStatusHandle = TMVar DaemonStatus
2012-06-13 16:36:33 +00:00
newDaemonStatus :: IO DaemonStatus
2012-07-29 13:35:01 +00:00
newDaemonStatus = DaemonStatus
<$> pure False
<*> pure Nothing
<*> pure False
<*> pure Nothing
<*> pure M.empty
<*> pure M.empty
<*> pure firstAlertId
2012-07-29 13:35:01 +00:00
<*> pure []
<*> newNotificationBroadcaster
<*> newNotificationBroadcaster
<*> newNotificationBroadcaster
2012-06-13 16:36:33 +00:00
getDaemonStatus :: DaemonStatusHandle -> IO DaemonStatus
getDaemonStatus = atomically . readTMVar
2012-06-13 16:36:33 +00:00
modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> IO ()
2012-07-29 13:35:01 +00:00
modifyDaemonStatus_ dstatus a = modifyDaemonStatus dstatus $ \s -> (a s, ())
modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> IO b
2012-07-29 13:35:01 +00:00
modifyDaemonStatus dstatus a = do
2012-07-29 12:52:57 +00:00
(s, b) <- atomically $ do
2012-07-29 13:35:01 +00:00
r@(s, _) <- a <$> takeTMVar dstatus
putTMVar dstatus s
2012-07-29 12:52:57 +00:00
return r
sendNotification $ changeNotifier s
return b
{- Remotes ordered by cost, with dead ones thrown out. -}
calcKnownRemotes :: Annex [Remote]
calcKnownRemotes = do
rs <- concat . Remote.byCost <$> Remote.enabledRemoteList
alive <- snd <$> trustPartition DeadTrusted (map Remote.uuid rs)
let good r = Remote.uuid r `elem` alive
return $ filter good rs
2012-07-22 19:06:18 +00:00
{- Updates the cached ordered list of remotes from the list in Annex
- state. -}
updateKnownRemotes :: DaemonStatusHandle -> Annex ()
updateKnownRemotes dstatus = do
remotes <- calcKnownRemotes
liftIO $ modifyDaemonStatus_ dstatus $
2012-07-22 19:06:18 +00:00
\s -> s { knownRemotes = remotes }
{- 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 $
catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus
2012-07-02 20:11:04 +00:00
transfers <- M.fromList <$> getTransfers
remotes <- calcKnownRemotes
liftIO $ atomically $ newTMVar status
{ scanComplete = False
, sanityCheckRunning = False
2012-07-02 20:11:04 +00:00
, currentTransfers = transfers
, knownRemotes = remotes
}
2012-06-13 18:02:40 +00:00
{- This writes the daemon status to disk, when it changes, but no more
- frequently than once every ten minutes.
-}
2012-06-13 18:02:40 +00:00
daemonStatusThread :: ThreadState -> DaemonStatusHandle -> IO ()
2012-07-29 13:35:01 +00:00
daemonStatusThread st dstatus = do
2012-07-29 12:52:57 +00:00
notifier <- newNotificationHandle
2012-07-29 13:35:01 +00:00
=<< changeNotifier <$> getDaemonStatus dstatus
2012-06-13 18:02:40 +00:00
checkpoint
runEvery (Seconds tenMinutes) $ do
2012-07-29 12:52:57 +00:00
waitNotification notifier
checkpoint
2012-06-13 18:02:40 +00:00
where
checkpoint = do
2012-07-29 13:35:01 +00:00
status <- getDaemonStatus dstatus
file <- runThreadState st $ fromRepo gitAnnexDaemonStatusFile
writeDaemonStatusFile file status
2012-06-13 18:02:40 +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
where
serialized now = unlines
[ "lastRunning:" ++ show now
, "scanComplete:" ++ show (scanComplete status)
, "sanityCheckRunning:" ++ show (sanityCheckRunning status)
, "lastSanityCheck:" ++ maybe "" show (lastSanityCheck status)
]
readDaemonStatusFile :: FilePath -> IO DaemonStatus
readDaemonStatusFile file = parse <$> newDaemonStatus <*> readFile file
where
parse status = foldr parseline status . lines
parseline line status
| key == "lastRunning" = parseval readtime $ \v ->
status { lastRunning = Just v }
| key == "scanComplete" = parseval readish $ \v ->
status { scanComplete = v }
| key == "sanityCheckRunning" = parseval readish $ \v ->
status { sanityCheckRunning = v }
| key == "lastSanityCheck" = parseval readtime $ \v ->
status { lastSanityCheck = Just v }
| otherwise = status -- unparsable line
where
(key, value) = separate (== ':') line
parseval parser a = maybe status a (parser value)
readtime s = do
d <- parseTime defaultTimeLocale "%s%Qs" s
Just $ utcTimeToPOSIXSeconds d
{- 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)
where
t = realToFrac (timestamp + slop) :: POSIXTime
2012-06-13 18:19:21 +00:00
slop = fromIntegral tenMinutes
tenMinutes :: Int
tenMinutes = 10 * 60
2012-07-05 20:34:20 +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
s <- takeTMVar dstatus
putTMVar dstatus $ s { currentTransfers = a (currentTransfers s) }
{- Alters a transfer's info, if the transfer is in the map. -}
alterTransferInfo :: DaemonStatusHandle -> Transfer -> (TransferInfo -> TransferInfo) -> IO ()
alterTransferInfo dstatus t a = updateTransferInfo' dstatus $ M.adjust a t
{- Updates a transfer's info. Adds the transfer to the map if necessary,
- or if already present, updates it while preserving the old transferTid,
- transferPaused, and bytesComplete values, which are not written to disk. -}
updateTransferInfo :: DaemonStatusHandle -> Transfer -> TransferInfo -> IO ()
updateTransferInfo dstatus t info = updateTransferInfo' dstatus $
M.insertWith' merge t info
where
merge new old = new
{ transferTid = maybe (transferTid new) Just (transferTid old)
, transferPaused = transferPaused new || transferPaused old
, bytesComplete = maybe (bytesComplete new) Just (bytesComplete old)
}
updateTransferInfo' :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> IO ()
updateTransferInfo' dstatus a =
2012-07-29 12:52:57 +00:00
notifyTransfer dstatus `after` modifyDaemonStatus_ dstatus go
where
go s = s { currentTransfers = a (currentTransfers s) }
{- Removes a transfer from the map, and returns its info. -}
removeTransfer :: DaemonStatusHandle -> Transfer -> IO (Maybe TransferInfo)
2012-07-29 12:52:57 +00:00
removeTransfer dstatus t =
notifyTransfer dstatus `after` modifyDaemonStatus dstatus go
where
go 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. -}
notifyTransfer :: DaemonStatusHandle -> IO ()
2012-07-29 13:35:01 +00:00
notifyTransfer dstatus = sendNotification
=<< transferNotifier <$> atomically (readTMVar dstatus)
{- Send a notification when alerts are changed. -}
notifyAlert :: DaemonStatusHandle -> IO ()
notifyAlert dstatus = sendNotification
=<< alertNotifier <$> atomically (readTMVar dstatus)
{- Returns the alert's identifier, which can be used to remove it. -}
addAlert :: DaemonStatusHandle -> Alert -> IO AlertId
addAlert dstatus alert = notifyAlert dstatus `after` modifyDaemonStatus dstatus go
where
2012-08-06 21:09:23 +00:00
go s = (s { lastAlertId = i, alertMap = m }, i)
2012-07-29 13:35:01 +00:00
where
2012-08-06 21:09:23 +00:00
i = nextAlertId $ lastAlertId s
m = mergeAlert i alert (alertMap s)
2012-07-29 13:35:01 +00:00
removeAlert :: DaemonStatusHandle -> AlertId -> IO ()
removeAlert dstatus i = updateAlert dstatus i (const Nothing)
updateAlert :: DaemonStatusHandle -> AlertId -> (Alert -> Maybe Alert) -> IO ()
updateAlert dstatus i a = updateAlertMap dstatus $ \m -> M.update a i m
updateAlertMap :: DaemonStatusHandle -> (AlertMap -> AlertMap) -> IO ()
updateAlertMap dstatus a = notifyAlert dstatus `after` modifyDaemonStatus_ dstatus go
2012-07-29 13:35:01 +00:00
where
go s = s { alertMap = a (alertMap s) }
2012-07-29 13:35:01 +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 :: DaemonStatusHandle -> Alert -> IO Bool -> IO Bool
2012-07-30 20:32:32 +00:00
alertWhile dstatus alert a = alertWhile' dstatus alert $ do
r <- a
2012-08-23 19:48:14 +00:00
return (r, r)
2012-07-30 20:32:32 +00:00
{- Like alertWhile, but allows the activity to return a value too. -}
2012-07-30 20:32:32 +00:00
alertWhile' :: DaemonStatusHandle -> Alert -> IO (Bool, a) -> IO a
alertWhile' dstatus alert a = do
2012-07-29 13:35:01 +00:00
let alert' = alert { alertClass = Activity }
i <- addAlert dstatus alert'
2012-08-23 19:48:14 +00:00
(ok, r) <- a
2012-08-06 21:09:23 +00:00
updateAlertMap dstatus $ mergeAlert i $ makeAlertFiller ok alert'
return r