better handling of lifting from XMPP -> Assistant

This commit is contained in:
Joey Hess 2012-11-05 19:39:08 -04:00
parent fdb6a88877
commit 8f08aa3f45
7 changed files with 81 additions and 88 deletions

View file

@ -177,7 +177,7 @@ startAssistant assistant daemonize webappwaiter = withThreadState $ \st -> do
checkCanWatch checkCanWatch
dstatus <- startDaemonStatus dstatus <- startDaemonStatus
liftIO $ daemonize $ liftIO $ daemonize $
runAssistant go =<< newAssistantData st dstatus flip runAssistant go =<< newAssistantData st dstatus
where where
go = do go = do
d <- getAssistant id d <- getAssistant id
@ -216,6 +216,5 @@ startAssistant assistant daemonize webappwaiter = withThreadState $ \st -> do
assist a = (False, a) assist a = (False, a)
startthread d (watcher, t) startthread d (watcher, t)
| watcher || assistant = void $ liftIO $ forkIO $ | watcher || assistant = void $ liftIO $ forkIO $
flip runAssistant d $ runAssistant d $ runNamedThread t
runNamedThread t
| otherwise = noop | otherwise = noop

View file

@ -79,8 +79,8 @@ newAssistantData st dstatus = AssistantData
<*> newBuddyList <*> newBuddyList
<*> newNetMessagerControl <*> newNetMessagerControl
runAssistant :: Assistant a -> AssistantData -> IO a runAssistant :: AssistantData -> Assistant a -> IO a
runAssistant a = runReaderT (mkAssistant a) runAssistant d a = runReaderT (mkAssistant a) d
getAssistant :: (AssistantData -> a) -> Assistant a getAssistant :: (AssistantData -> a) -> Assistant a
getAssistant = reader getAssistant = reader
@ -97,23 +97,23 @@ liftAnnex a = do
(<~>) :: (IO a -> IO b) -> Assistant a -> Assistant b (<~>) :: (IO a -> IO b) -> Assistant a -> Assistant b
io <~> a = do io <~> a = do
d <- reader id d <- reader id
liftIO $ io $ runAssistant a d liftIO $ io $ runAssistant d a
{- Creates an IO action that will run an Assistant action when run. -} {- Creates an IO action that will run an Assistant action when run. -}
asIO :: Assistant a -> Assistant (IO a) asIO :: Assistant a -> Assistant (IO a)
asIO a = do asIO a = do
d <- reader id d <- reader id
return $ runAssistant a d return $ runAssistant d a
asIO1 :: (a -> Assistant b) -> Assistant (a -> IO b) asIO1 :: (a -> Assistant b) -> Assistant (a -> IO b)
asIO1 a = do asIO1 a = do
d <- reader id d <- reader id
return $ \v -> runAssistant (a v) d return $ \v -> runAssistant d $ a v
asIO2 :: (a -> b -> Assistant c) -> Assistant (a -> b -> IO c) asIO2 :: (a -> b -> Assistant c) -> Assistant (a -> b -> IO c)
asIO2 a = do asIO2 a = do
d <- reader id d <- reader id
return $ \v1 v2 -> runAssistant (a v1 v2) d return $ \v1 v2 -> runAssistant d (a v1 v2)
{- Runs an IO action on a selected field of the AssistantData. -} {- Runs an IO action on a selected field of the AssistantData. -}
(<<~) :: (a -> IO b) -> (AssistantData -> a) -> Assistant b (<<~) :: (a -> IO b) -> (AssistantData -> a) -> Assistant b

View file

@ -19,12 +19,12 @@ runNamedThread (NamedThread name a) = do
liftIO . go $ d { threadName = name } liftIO . go $ d { threadName = name }
where where
go d = do go d = do
r <- E.try (runAssistant a d) :: IO (Either E.SomeException ()) r <- E.try (runAssistant d a) :: IO (Either E.SomeException ())
case r of case r of
Right _ -> noop Right _ -> noop
Left e -> do Left e -> do
let msg = unwords [name, "crashed:", show e] let msg = unwords [name, "crashed:", show e]
hPutStrLn stderr msg hPutStrLn stderr msg
-- TODO click to restart -- TODO click to restart
flip runAssistant d $ void $ runAssistant d $ void $
addAlert $ warningAlert name msg addAlert $ warningAlert name msg

View file

@ -18,7 +18,7 @@ import Assistant.Sync
import Assistant.DaemonStatus import Assistant.DaemonStatus
import qualified Remote import qualified Remote
import Utility.ThreadScheduler import Utility.ThreadScheduler
import Assistant.WebApp import Assistant.WebApp (UrlRenderer, renderUrl)
import Assistant.WebApp.Types import Assistant.WebApp.Types
import Assistant.Alert import Assistant.Alert
import Assistant.Pairing import Assistant.Pairing
@ -34,70 +34,69 @@ import qualified Git.Branch
import Data.Time.Clock import Data.Time.Clock
xmppClientThread :: UrlRenderer -> NamedThread xmppClientThread :: UrlRenderer -> NamedThread
xmppClientThread urlrenderer = NamedThread "XMPPClient" $ do xmppClientThread urlrenderer = NamedThread "XMPPClient" $
{- All Assistant actions have to be converted into IO actions that restartableClient . xmppClient urlrenderer =<< getAssistant id
- can be run from within the XMPP monad using liftIO. Ugly. -}
iodebug <- asIO1 debug {- Runs the client, handing restart events. -}
iopull <- asIO1 pull restartableClient :: IO () -> Assistant ()
iopairMsgReceived <- asIO2 $ pairMsgReceived urlrenderer restartableClient a = forever $ do
ioupdatebuddies <- asIO1 $ \p -> tid <- liftIO $ forkIO a
updateBuddyList (updateBuddies p) <<~ buddyList waitNetMessagerRestart
ioemptybuddies <- asIO $ liftIO $ killThread tid
updateBuddyList (const noBuddies) <<~ buddyList
iorelay <- asIO1 relayNetMessage xmppClient :: UrlRenderer -> AssistantData -> IO ()
ioclientthread <- asIO $ xmppClient urlrenderer d = do
go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairMsgReceived v <- liftAssistant $ liftAnnex getXMPPCreds
restartableClient ioclientthread
where
go iorelay iodebug iopull ioupdatebuddies ioemptybuddies iopairMsgReceived = do
v <- liftAnnex getXMPPCreds
case v of case v of
Nothing -> noop Nothing -> noop -- will be restarted once creds get configured
Just c -> liftIO $ retry (runclient c) =<< getCurrentTime Just c -> retry (runclient c) =<< getCurrentTime
where where
debug' = void . liftIO . iodebug liftAssistant = runAssistant d
xAssistant = liftIO . liftAssistant
{- When the client exits, it's restarted; {- When the client exits, it's restarted;
- if it keeps failing, back off to wait 5 minutes before - if it keeps failing, back off to wait 5 minutes before
- trying it again. -} - trying it again. -}
retry a starttime = do retry client starttime = do
e <- a e <- client
now <- getCurrentTime now <- getCurrentTime
if diffUTCTime now starttime > 300 if diffUTCTime now starttime > 300
then do then do
void $ iodebug ["connection lost; reconnecting", show e] liftAssistant $ debug ["connection lost; reconnecting", show e]
retry a now retry client now
else do else do
void $ iodebug ["connection failed; will retry", show e] liftAssistant $ debug ["connection failed; will retry", show e]
threadDelaySeconds (Seconds 300) threadDelaySeconds (Seconds 300)
retry a =<< getCurrentTime retry client =<< getCurrentTime
runclient c = void $ connectXMPP c $ \jid -> do runclient c = liftIO $ connectXMPP c $ \jid -> do
selfjid <- bindJID jid selfjid <- bindJID jid
debug' ["connected", show selfjid] putStanza gitAnnexSignature
xAssistant $ debug ["connected", show selfjid]
{- The buddy list starts empty each time {- The buddy list starts empty each time
- the client connects, so that stale info - the client connects, so that stale info
- is not retained. -} - is not retained. -}
void $ liftIO ioemptybuddies void $ xAssistant $
putStanza gitAnnexSignature updateBuddyList (const noBuddies) <<~ buddyList
xmppThread $ receivenotifications selfjid xmppThread $ receivenotifications selfjid
forever $ do forever $ do
a <- liftIO $ iorelay selfjid a <- xAssistant $ relayNetMessage selfjid
a a
receivenotifications selfjid = forever $ do receivenotifications selfjid = forever $ do
l <- decodeStanza selfjid <$> getStanza l <- decodeStanza selfjid <$> getStanza
debug' ["received:", show l] xAssistant $ debug ["received:", show l]
mapM_ (handle selfjid) l mapM_ (handle selfjid) l
handle _ (PresenceMessage p) = handle _ (PresenceMessage p) = void $ xAssistant $
void $ liftIO $ ioupdatebuddies p updateBuddyList (updateBuddies p) <<~ buddyList
handle _ (GotNetMessage QueryPresence) = handle _ (GotNetMessage QueryPresence) = putStanza gitAnnexSignature
putStanza gitAnnexSignature handle _ (GotNetMessage (NotifyPush us)) = void $ xAssistant $
handle _ (GotNetMessage (NotifyPush us)) = pull us
void $ liftIO $ iopull us
handle selfjid (GotNetMessage (PairingNotification stage t u)) = handle selfjid (GotNetMessage (PairingNotification stage t u)) =
maybe noop (\jid -> liftIO $ iopairMsgReceived (stage, u) (selfjid, jid)) (parseJID t) maybe noop (xAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID t)
handle _ (Ignorable _) = noop handle _ (Ignorable _) = noop
handle _ (Unknown _) = noop handle _ (Unknown _) = noop
handle _ (ProtocolError _) = noop handle _ (ProtocolError _) = noop
@ -153,13 +152,6 @@ relayNetMessage selfjid = convert =<< waitNetMessage
return $ putStanza $ return $ putStanza $
pairingNotification stage u tojid selfjid pairingNotification stage u tojid selfjid
{- Runs the client, handing restart events. -}
restartableClient :: IO () -> Assistant ()
restartableClient a = forever $ do
tid <- liftIO $ forkIO a
waitNetMessagerRestart
liftIO $ killThread tid
{- Runs a XMPP action in a separate thread, using a session to allow it {- Runs a XMPP action in a separate thread, using a session to allow it
- to access the same XMPP client. -} - to access the same XMPP client. -}
xmppThread :: XMPP () -> XMPP () xmppThread :: XMPP () -> XMPP ()
@ -196,8 +188,8 @@ pull us = do
unlessM (all id . fst <$> manualPull branch [r]) $ unlessM (all id . fst <$> manualPull branch [r]) $
pullone rs branch pullone rs branch
pairMsgReceived :: UrlRenderer -> (PairStage, UUID) -> (JID, JID) -> Assistant () pairMsgReceived :: UrlRenderer -> PairStage -> UUID -> JID -> JID -> Assistant ()
pairMsgReceived urlrenderer (PairReq, theiruuid) (selfjid, theirjid) pairMsgReceived urlrenderer PairReq theiruuid selfjid theirjid
-- PairReq from another client using our JID is automatically accepted. -- PairReq from another client using our JID is automatically accepted.
| baseJID selfjid == baseJID theirjid = do | baseJID selfjid == baseJID theirjid = do
selfuuid <- liftAnnex getUUID selfuuid <- liftAnnex getUUID
@ -215,7 +207,8 @@ pairMsgReceived urlrenderer (PairReq, theiruuid) (selfjid, theirjid)
, buttonLabel = T.pack "Respond" , buttonLabel = T.pack "Respond"
, buttonAction = Just close , buttonAction = Just close
} }
pairMsgReceived _ (PairAck, theiruuid) (_selfjid, theirjid) =
pairMsgReceived _ PairAck theiruuid _selfjid theirjid =
{- PairAck must come from one of the buddies we are pairing with; {- PairAck must come from one of the buddies we are pairing with;
- don't pair with just anyone. -} - don't pair with just anyone. -}
whenM (isBuddyPairing theirjid) $ do whenM (isBuddyPairing theirjid) $ do
@ -224,7 +217,8 @@ pairMsgReceived _ (PairAck, theiruuid) (_selfjid, theirjid) =
sendNetMessage $ sendNetMessage $
PairingNotification PairDone (formatJID theirjid) selfuuid PairingNotification PairDone (formatJID theirjid) selfuuid
finishXMPPPairing theirjid theiruuid finishXMPPPairing theirjid theiruuid
pairMsgReceived _ (PairDone, _theiruuid) (_selfjid, theirjid) =
pairMsgReceived _ PairDone _theiruuid _selfjid theirjid =
changeBuddyPairing theirjid False changeBuddyPairing theirjid False
isBuddyPairing :: JID -> Assistant Bool isBuddyPairing :: JID -> Assistant Bool

View file

@ -69,5 +69,5 @@ runTransferThread' d a = go
Just ResumeTransfer -> go Just ResumeTransfer -> go
_ -> done _ -> done
_ -> done _ -> done
done = flip runAssistant d $ done = runAssistant d $
flip MSemN.signal 1 <<~ transferSlots flip MSemN.signal 1 <<~ transferSlots

View file

@ -71,7 +71,7 @@ newWebAppState = do
, otherRepos = otherrepos } , otherRepos = otherrepos }
liftAssistant :: forall sub a. (Assistant a) -> GHandler sub WebApp a liftAssistant :: forall sub a. (Assistant a) -> GHandler sub WebApp a
liftAssistant a = liftIO . runAssistant a =<< assistantData <$> getYesod liftAssistant a = liftIO . flip runAssistant a =<< assistantData <$> getYesod
getWebAppState :: forall sub. GHandler sub WebApp WebAppState getWebAppState :: forall sub. GHandler sub WebApp WebAppState
getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod

View file

@ -107,7 +107,7 @@ firstRun = do
urlrenderer <- newUrlRenderer urlrenderer <- newUrlRenderer
v <- newEmptyMVar v <- newEmptyMVar
let callback a = Just $ a v let callback a = Just $ a v
void $ flip runAssistant d $ runNamedThread $ void $ runAssistant d $ runNamedThread $
webAppThread d urlrenderer True webAppThread d urlrenderer True
(callback signaler) (callback signaler)
(callback mainthread) (callback mainthread)