cleanup daemonStatus accessors
This commit is contained in:
parent
68118b8986
commit
ea8df8fe9f
15 changed files with 29 additions and 29 deletions
|
@ -24,11 +24,12 @@ import Data.Time
|
||||||
import System.Locale
|
import System.Locale
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
daemonStatus :: Assistant DaemonStatus
|
-- TODO remove this
|
||||||
daemonStatus = getDaemonStatus <<~ daemonStatusHandle
|
getDaemonStatusOld :: DaemonStatusHandle -> IO DaemonStatus
|
||||||
|
getDaemonStatusOld = atomically . readTMVar
|
||||||
|
|
||||||
getDaemonStatus :: DaemonStatusHandle -> IO DaemonStatus
|
getDaemonStatus :: Assistant DaemonStatus
|
||||||
getDaemonStatus = atomically . readTMVar
|
getDaemonStatus = (atomically . readTMVar) <<~ daemonStatusHandle
|
||||||
|
|
||||||
modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> IO ()
|
modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> IO ()
|
||||||
modifyDaemonStatus_ dstatus a = modifyDaemonStatus dstatus $ \s -> (a s, ())
|
modifyDaemonStatus_ dstatus a = modifyDaemonStatus dstatus $ \s -> (a s, ())
|
||||||
|
|
|
@ -23,7 +23,7 @@ import Config
|
||||||
handleDrops :: DaemonStatusHandle -> Bool -> Key -> AssociatedFile -> Annex ()
|
handleDrops :: DaemonStatusHandle -> Bool -> Key -> AssociatedFile -> Annex ()
|
||||||
handleDrops _ _ _ Nothing = noop
|
handleDrops _ _ _ Nothing = noop
|
||||||
handleDrops dstatus fromhere key f = do
|
handleDrops dstatus fromhere key f = do
|
||||||
syncrs <- liftIO $ syncRemotes <$> getDaemonStatus dstatus
|
syncrs <- liftIO $ syncRemotes <$> getDaemonStatusOld dstatus
|
||||||
locs <- loggedLocations key
|
locs <- loggedLocations key
|
||||||
handleDrops' locs syncrs fromhere key f
|
handleDrops' locs syncrs fromhere key f
|
||||||
|
|
||||||
|
|
|
@ -18,7 +18,7 @@ import Utility.NotificationBroadcaster
|
||||||
daemonStatusThread :: NamedThread
|
daemonStatusThread :: NamedThread
|
||||||
daemonStatusThread = NamedThread "DaemonStatus" $ do
|
daemonStatusThread = NamedThread "DaemonStatus" $ do
|
||||||
notifier <- liftIO . newNotificationHandle
|
notifier <- liftIO . newNotificationHandle
|
||||||
=<< changeNotifier <$> daemonStatus
|
=<< changeNotifier <$> getDaemonStatus
|
||||||
checkpoint
|
checkpoint
|
||||||
runEvery (Seconds tenMinutes) <~> do
|
runEvery (Seconds tenMinutes) <~> do
|
||||||
liftIO $ waitNotification notifier
|
liftIO $ waitNotification notifier
|
||||||
|
@ -26,4 +26,4 @@ daemonStatusThread = NamedThread "DaemonStatus" $ do
|
||||||
where
|
where
|
||||||
checkpoint = do
|
checkpoint = do
|
||||||
file <- liftAnnex $ fromRepo gitAnnexDaemonStatusFile
|
file <- liftAnnex $ fromRepo gitAnnexDaemonStatusFile
|
||||||
liftIO . writeDaemonStatusFile file =<< daemonStatus
|
liftIO . writeDaemonStatusFile file =<< getDaemonStatus
|
||||||
|
|
|
@ -41,7 +41,7 @@ pairListenerThread urlrenderer = NamedThread "PairListener" $ do
|
||||||
Just m -> do
|
Just m -> do
|
||||||
sane <- checkSane msg
|
sane <- checkSane msg
|
||||||
(pip, verified) <- verificationCheck m
|
(pip, verified) <- verificationCheck m
|
||||||
=<< (pairingInProgress <$> daemonStatus)
|
=<< (pairingInProgress <$> getDaemonStatus)
|
||||||
let wrongstage = maybe False (\p -> pairMsgStage m <= inProgressPairStage p) pip
|
let wrongstage = maybe False (\p -> pairMsgStage m <= inProgressPairStage p) pip
|
||||||
case (wrongstage, sane, pairMsgStage m) of
|
case (wrongstage, sane, pairMsgStage m) of
|
||||||
-- ignore our own messages, and
|
-- ignore our own messages, and
|
||||||
|
|
|
@ -89,7 +89,7 @@ xmppClient iowaitpush iodebug iopull = do
|
||||||
pull :: [UUID] -> Assistant ()
|
pull :: [UUID] -> Assistant ()
|
||||||
pull [] = noop
|
pull [] = noop
|
||||||
pull us = do
|
pull us = do
|
||||||
rs <- filter matching . syncRemotes <$> daemonStatus
|
rs <- filter matching . syncRemotes <$> getDaemonStatus
|
||||||
debug $ "push notification for" : map (fromUUID . Remote.uuid ) rs
|
debug $ "push notification for" : map (fromUUID . Remote.uuid ) rs
|
||||||
pullone rs =<< liftAnnex (inRepo Git.Branch.current)
|
pullone rs =<< liftAnnex (inRepo Git.Branch.current)
|
||||||
where
|
where
|
||||||
|
|
|
@ -46,7 +46,7 @@ pushThread = NamedThread "Pusher" $ runEvery (Seconds 2) <~> do
|
||||||
-- Now see if now's a good time to push.
|
-- Now see if now's a good time to push.
|
||||||
if shouldPush commits
|
if shouldPush commits
|
||||||
then do
|
then do
|
||||||
remotes <- filter pushable . syncRemotes <$> daemonStatus
|
remotes <- filter pushable . syncRemotes <$> getDaemonStatus
|
||||||
unless (null remotes) $
|
unless (null remotes) $
|
||||||
void $ alertWhile (pushAlert remotes) $ do
|
void $ alertWhile (pushAlert remotes) $ do
|
||||||
now <- liftIO $ getCurrentTime
|
now <- liftIO $ getCurrentTime
|
||||||
|
|
|
@ -49,7 +49,7 @@ sanityCheckerThread = NamedThread "SanityChecker" $ forever $ do
|
||||||
{- Only run one check per day, from the time of the last check. -}
|
{- Only run one check per day, from the time of the last check. -}
|
||||||
waitForNextCheck :: Assistant ()
|
waitForNextCheck :: Assistant ()
|
||||||
waitForNextCheck = do
|
waitForNextCheck = do
|
||||||
v <- lastSanityCheck <$> daemonStatus
|
v <- lastSanityCheck <$> getDaemonStatus
|
||||||
now <- liftIO getPOSIXTime
|
now <- liftIO getPOSIXTime
|
||||||
liftIO $ threadDelaySeconds $ Seconds $ calcdelay now v
|
liftIO $ threadDelaySeconds $ Seconds $ calcdelay now v
|
||||||
where
|
where
|
||||||
|
|
|
@ -22,10 +22,10 @@ transferPollerThread :: NamedThread
|
||||||
transferPollerThread = NamedThread "TransferPoller" $ do
|
transferPollerThread = NamedThread "TransferPoller" $ do
|
||||||
g <- liftAnnex gitRepo
|
g <- liftAnnex gitRepo
|
||||||
tn <- liftIO . newNotificationHandle =<<
|
tn <- liftIO . newNotificationHandle =<<
|
||||||
transferNotifier <$> daemonStatus
|
transferNotifier <$> getDaemonStatus
|
||||||
forever $ do
|
forever $ do
|
||||||
liftIO $ threadDelay 500000 -- 0.5 seconds
|
liftIO $ threadDelay 500000 -- 0.5 seconds
|
||||||
ts <- currentTransfers <$> daemonStatus
|
ts <- currentTransfers <$> getDaemonStatus
|
||||||
if M.null ts
|
if M.null ts
|
||||||
-- block until transfers running
|
-- block until transfers running
|
||||||
then liftIO $ waitNotification tn
|
then liftIO $ waitNotification tn
|
||||||
|
|
|
@ -57,7 +57,7 @@ transferScannerThread = NamedThread "TransferScanner" $ do
|
||||||
- and then the system (or us) crashed, and that info was
|
- and then the system (or us) crashed, and that info was
|
||||||
- lost.
|
- lost.
|
||||||
-}
|
-}
|
||||||
startupScan = addScanRemotes True =<< syncRemotes <$> daemonStatus
|
startupScan = addScanRemotes True =<< syncRemotes <$> getDaemonStatus
|
||||||
|
|
||||||
{- This is a cheap scan for failed transfers involving a remote. -}
|
{- This is a cheap scan for failed transfers involving a remote. -}
|
||||||
failedTransferScan :: Remote -> Assistant ()
|
failedTransferScan :: Remote -> Assistant ()
|
||||||
|
@ -122,7 +122,7 @@ expensiveScan rs = unless onlyweb $ do
|
||||||
locs <- loggedLocations key
|
locs <- loggedLocations key
|
||||||
{- The syncable remotes may have changed since this
|
{- The syncable remotes may have changed since this
|
||||||
- scan began. -}
|
- scan began. -}
|
||||||
syncrs <- liftIO $ syncRemotes <$> getDaemonStatus dstatus
|
syncrs <- liftIO $ syncRemotes <$> getDaemonStatusOld dstatus
|
||||||
present <- inAnnex key
|
present <- inAnnex key
|
||||||
|
|
||||||
handleDrops' locs syncrs present key (Just f)
|
handleDrops' locs syncrs present key (Just f)
|
||||||
|
|
|
@ -133,18 +133,18 @@ onAddSymlink file filestatus = go =<< liftAnnex (Backend.lookupFile file)
|
||||||
link <- liftAnnex $ calcGitLink file key
|
link <- liftAnnex $ calcGitLink file key
|
||||||
ifM ((==) link <$> liftIO (readSymbolicLink file))
|
ifM ((==) link <$> liftIO (readSymbolicLink file))
|
||||||
( do
|
( do
|
||||||
s <- daemonStatus
|
s <- getDaemonStatus
|
||||||
checkcontent key s
|
checkcontent key s
|
||||||
ensurestaged link s
|
ensurestaged link s
|
||||||
, do
|
, do
|
||||||
liftIO $ removeFile file
|
liftIO $ removeFile file
|
||||||
liftIO $ createSymbolicLink link file
|
liftIO $ createSymbolicLink link file
|
||||||
checkcontent key =<< daemonStatus
|
checkcontent key =<< getDaemonStatus
|
||||||
addlink link
|
addlink link
|
||||||
)
|
)
|
||||||
go Nothing = do -- other symlink
|
go Nothing = do -- other symlink
|
||||||
link <- liftIO (readSymbolicLink file)
|
link <- liftIO (readSymbolicLink file)
|
||||||
ensurestaged link =<< daemonStatus
|
ensurestaged link =<< getDaemonStatus
|
||||||
|
|
||||||
{- This is often called on symlinks that are already
|
{- This is often called on symlinks that are already
|
||||||
- staged correctly. A symlink may have been deleted
|
- staged correctly. A symlink may have been deleted
|
||||||
|
|
|
@ -58,7 +58,7 @@ queueTransfersMatching matching schedule q dstatus k f direction
|
||||||
where
|
where
|
||||||
go = do
|
go = do
|
||||||
rs <- sufficientremotes
|
rs <- sufficientremotes
|
||||||
=<< syncRemotes <$> liftIO (getDaemonStatus dstatus)
|
=<< syncRemotes <$> liftIO (getDaemonStatusOld dstatus)
|
||||||
let matchingrs = filter (matching . Remote.uuid) rs
|
let matchingrs = filter (matching . Remote.uuid) rs
|
||||||
if null matchingrs
|
if null matchingrs
|
||||||
then defer
|
then defer
|
||||||
|
@ -92,7 +92,7 @@ queueTransfersMatching matching schedule q dstatus k f direction
|
||||||
queueDeferredDownloads :: Schedule -> TransferQueue -> DaemonStatusHandle -> Annex ()
|
queueDeferredDownloads :: Schedule -> TransferQueue -> DaemonStatusHandle -> Annex ()
|
||||||
queueDeferredDownloads schedule q dstatus = do
|
queueDeferredDownloads schedule q dstatus = do
|
||||||
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
|
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
|
||||||
rs <- syncRemotes <$> liftIO (getDaemonStatus dstatus)
|
rs <- syncRemotes <$> liftIO (getDaemonStatusOld dstatus)
|
||||||
left <- filterM (queue rs) l
|
left <- filterM (queue rs) l
|
||||||
unless (null left) $
|
unless (null left) $
|
||||||
liftIO $ atomically $ modifyTVar' (deferreddownloads q) $
|
liftIO $ atomically $ modifyTVar' (deferreddownloads q) $
|
||||||
|
|
|
@ -74,9 +74,6 @@ newWebAppState = do
|
||||||
getAssistantY :: forall sub a. (AssistantData -> a) -> GHandler sub WebApp a
|
getAssistantY :: forall sub a. (AssistantData -> a) -> GHandler sub WebApp a
|
||||||
getAssistantY f = f <$> (assistantData <$> getYesod)
|
getAssistantY f = f <$> (assistantData <$> getYesod)
|
||||||
|
|
||||||
getDaemonStatusY :: forall sub. GHandler sub WebApp DaemonStatus
|
|
||||||
getDaemonStatusY = liftIO . getDaemonStatus =<< getAssistantY daemonStatusHandle
|
|
||||||
|
|
||||||
runAssistantY :: forall sub a. (Assistant a) -> GHandler sub WebApp a
|
runAssistantY :: forall sub a. (Assistant a) -> GHandler sub WebApp a
|
||||||
runAssistantY a = liftIO . runAssistant a =<< assistantData <$> getYesod
|
runAssistantY a = liftIO . runAssistant a =<< assistantData <$> getYesod
|
||||||
|
|
||||||
|
@ -112,7 +109,7 @@ newNotifier selector = do
|
||||||
liftIO $ notificationHandleToId <$> newNotificationHandle notifier
|
liftIO $ notificationHandleToId <$> newNotificationHandle notifier
|
||||||
|
|
||||||
getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster
|
getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster
|
||||||
getNotifier selector = selector <$> getDaemonStatusY
|
getNotifier selector = selector <$> runAssistantY getDaemonStatus
|
||||||
|
|
||||||
{- Adds the auth parameter as a hidden field on a form. Must be put into
|
{- Adds the auth parameter as a hidden field on a form. Must be put into
|
||||||
- every form. -}
|
- every form. -}
|
||||||
|
|
|
@ -10,6 +10,7 @@
|
||||||
module Assistant.WebApp.Configurators where
|
module Assistant.WebApp.Configurators where
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
|
import Assistant.DaemonStatus
|
||||||
import Assistant.WebApp
|
import Assistant.WebApp
|
||||||
import Assistant.WebApp.Types
|
import Assistant.WebApp.Types
|
||||||
import Assistant.WebApp.SideBar
|
import Assistant.WebApp.SideBar
|
||||||
|
@ -101,7 +102,7 @@ repoList onlyconfigured includehere
|
||||||
where
|
where
|
||||||
configured = do
|
configured = do
|
||||||
rs <- filter (not . Remote.readonly) . syncRemotes
|
rs <- filter (not . Remote.readonly) . syncRemotes
|
||||||
<$> getDaemonStatusY
|
<$> runAssistantY getDaemonStatus
|
||||||
runAnnex [] $ do
|
runAnnex [] $ do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
let l = map Remote.uuid rs
|
let l = map Remote.uuid rs
|
||||||
|
|
|
@ -27,7 +27,8 @@ sideBarDisplay :: Widget
|
||||||
sideBarDisplay = do
|
sideBarDisplay = do
|
||||||
let content = do
|
let content = do
|
||||||
{- Add newest alerts to the sidebar. -}
|
{- Add newest alerts to the sidebar. -}
|
||||||
alertpairs <- lift $ M.toList . alertMap <$> getDaemonStatusY
|
alertpairs <- lift $ M.toList . alertMap
|
||||||
|
<$> runAssistantY getDaemonStatus
|
||||||
mapM_ renderalert $
|
mapM_ renderalert $
|
||||||
take displayAlerts $ reverse $ sortAlertPairs alertpairs
|
take displayAlerts $ reverse $ sortAlertPairs alertpairs
|
||||||
let ident = "sidebar"
|
let ident = "sidebar"
|
||||||
|
@ -79,7 +80,7 @@ getCloseAlert i = do
|
||||||
{- When an alert with a button is clicked on, the button takes us here. -}
|
{- When an alert with a button is clicked on, the button takes us here. -}
|
||||||
getClickAlert :: AlertId -> Handler ()
|
getClickAlert :: AlertId -> Handler ()
|
||||||
getClickAlert i = do
|
getClickAlert i = do
|
||||||
m <- alertMap <$> getDaemonStatusY
|
m <- alertMap <$> runAssistantY getDaemonStatus
|
||||||
case M.lookup i m of
|
case M.lookup i m of
|
||||||
Just (Alert { alertButton = Just b }) -> do
|
Just (Alert { alertButton = Just b }) -> do
|
||||||
{- Spawn a thread to run the action while redirecting. -}
|
{- Spawn a thread to run the action while redirecting. -}
|
||||||
|
|
|
@ -44,7 +44,7 @@ changeSyncable (Just r) False = do
|
||||||
void $ liftIO $ dequeueTransfers (transferQueue d) dstatus tofrom
|
void $ liftIO $ dequeueTransfers (transferQueue d) dstatus tofrom
|
||||||
mapM_ (cancelTransfer False) =<<
|
mapM_ (cancelTransfer False) =<<
|
||||||
filter tofrom . M.keys <$>
|
filter tofrom . M.keys <$>
|
||||||
liftIO (currentTransfers <$> getDaemonStatus dstatus)
|
runAssistantY (currentTransfers <$> getDaemonStatus)
|
||||||
where
|
where
|
||||||
tofrom t = transferUUID t == Remote.uuid r
|
tofrom t = transferUUID t == Remote.uuid r
|
||||||
|
|
||||||
|
@ -128,4 +128,4 @@ startTransfer t = do
|
||||||
Transferrer.startTransfer program t info
|
Transferrer.startTransfer program t info
|
||||||
|
|
||||||
getCurrentTransfers :: Handler TransferMap
|
getCurrentTransfers :: Handler TransferMap
|
||||||
getCurrentTransfers = currentTransfers <$> getDaemonStatusY
|
getCurrentTransfers = currentTransfers <$> runAssistantY getDaemonStatus
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue