show when a buddy is already paired
This commit is contained in:
parent
d303190979
commit
fd22734392
5 changed files with 30 additions and 20 deletions
|
@ -9,12 +9,15 @@ module Assistant.NetMessager where
|
||||||
|
|
||||||
import Assistant.Common
|
import Assistant.Common
|
||||||
import Assistant.Types.NetMessager
|
import Assistant.Types.NetMessager
|
||||||
|
import qualified Types.Remote as Remote
|
||||||
|
import qualified Git
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Control.Concurrent.MSampleVar
|
import Control.Concurrent.MSampleVar
|
||||||
import Control.Exception as E
|
import Control.Exception as E
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
sendNetMessage :: NetMessage -> Assistant ()
|
sendNetMessage :: NetMessage -> Assistant ()
|
||||||
sendNetMessage m =
|
sendNetMessage m =
|
||||||
|
@ -93,3 +96,12 @@ queueNetPushMessage m = do
|
||||||
|
|
||||||
waitNetPushMessage :: Assistant (NetMessage)
|
waitNetPushMessage :: Assistant (NetMessage)
|
||||||
waitNetPushMessage = (atomically . readTChan) <<~ (netMessagesPush . netMessager)
|
waitNetPushMessage = (atomically . readTChan) <<~ (netMessagesPush . netMessager)
|
||||||
|
|
||||||
|
{- Remotes using the XMPP transport have urls like xmpp::user@host -}
|
||||||
|
isXMPPRemote :: Remote -> Bool
|
||||||
|
isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
|
||||||
|
where
|
||||||
|
r = Remote.repo remote
|
||||||
|
|
||||||
|
getXMPPClientID :: Remote -> ClientID
|
||||||
|
getXMPPClientID r = T.pack $ drop (length "xmpp::") (Git.repoLocation (Remote.repo r))
|
||||||
|
|
|
@ -27,7 +27,6 @@ import Annex.UUID
|
||||||
|
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import qualified Data.Text as T
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
|
||||||
{- Syncs with remotes that may have been disconnected for a while.
|
{- Syncs with remotes that may have been disconnected for a while.
|
||||||
|
@ -176,12 +175,3 @@ syncNewRemote remote = do
|
||||||
thread <- asIO $ do
|
thread <- asIO $ do
|
||||||
reconnectRemotes False [remote]
|
reconnectRemotes False [remote]
|
||||||
void $ liftIO $ forkIO $ thread
|
void $ liftIO $ forkIO $ thread
|
||||||
|
|
||||||
{- Remotes using the XMPP transport have urls like xmpp::user@host -}
|
|
||||||
isXMPPRemote :: Remote -> Bool
|
|
||||||
isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
|
|
||||||
where
|
|
||||||
r = Remote.repo remote
|
|
||||||
|
|
||||||
getXMPPClientID :: Remote -> ClientID
|
|
||||||
getXMPPClientID r = T.pack $ drop (length "xmpp::") (Git.repoLocation (Remote.repo r))
|
|
||||||
|
|
|
@ -99,8 +99,11 @@ buddyListDisplay :: Widget
|
||||||
buddyListDisplay = do
|
buddyListDisplay = do
|
||||||
autoUpdate ident NotifierBuddyListR (10 :: Int) (10 :: Int)
|
autoUpdate ident NotifierBuddyListR (10 :: Int) (10 :: Int)
|
||||||
#ifdef WITH_XMPP
|
#ifdef WITH_XMPP
|
||||||
buddies <- lift $ liftAssistant $ catMaybes . map buddySummary
|
buddies <- lift $ liftAssistant $ do
|
||||||
<$> (getBuddyList <<~ buddyList)
|
rs <- filter isXMPPRemote . syncRemotes <$> getDaemonStatus
|
||||||
|
let pairedwith = catMaybes $ map (parseJID . getXMPPClientID) rs
|
||||||
|
catMaybes . map (buddySummary pairedwith)
|
||||||
|
<$> (getBuddyList <<~ buddyList)
|
||||||
#else
|
#else
|
||||||
let buddies = []
|
let buddies = []
|
||||||
#endif
|
#endif
|
||||||
|
|
|
@ -26,14 +26,15 @@ buddyName j = maybe (T.pack "") strNode (jidNode j)
|
||||||
{- Summary of info about a buddy.
|
{- Summary of info about a buddy.
|
||||||
-
|
-
|
||||||
- If the buddy has no clients at all anymore, returns Nothing. -}
|
- If the buddy has no clients at all anymore, returns Nothing. -}
|
||||||
buddySummary :: Buddy -> Maybe (Text, Bool, Bool, BuddyKey)
|
buddySummary :: [JID] -> Buddy -> Maybe (Text, Bool, Bool, Bool, BuddyKey)
|
||||||
buddySummary b = case clients of
|
buddySummary pairedwith b = case clients of
|
||||||
((Client j):_) -> Just (buddyName j, away, canpair, genBuddyKey j)
|
((Client j):_) -> Just (buddyName j, away, canpair, alreadypaired j, genBuddyKey j)
|
||||||
[] -> Nothing
|
[] -> Nothing
|
||||||
where
|
where
|
||||||
away = S.null (buddyPresent b) && S.null (buddyAssistants b)
|
away = S.null (buddyPresent b) && S.null (buddyAssistants b)
|
||||||
canpair = not $ S.null (buddyAssistants b)
|
canpair = not $ S.null (buddyAssistants b)
|
||||||
clients = S.toList $ buddyPresent b `S.union` buddyAway b `S.union` buddyAssistants b
|
clients = S.toList $ buddyPresent b `S.union` buddyAway b `S.union` buddyAssistants b
|
||||||
|
alreadypaired j = baseJID j `elem` pairedwith
|
||||||
|
|
||||||
{- Updates the buddies with XMPP presence info. -}
|
{- Updates the buddies with XMPP presence info. -}
|
||||||
updateBuddies :: Presence -> Buddies -> Buddies
|
updateBuddies :: Presence -> Buddies -> Buddies
|
||||||
|
|
|
@ -6,7 +6,7 @@
|
||||||
<td>
|
<td>
|
||||||
Nobody is currently available.
|
Nobody is currently available.
|
||||||
$else
|
$else
|
||||||
$forall (name, away, canpair, buddyid) <- buddies
|
$forall (name, away, canpair, paired, buddyid) <- buddies
|
||||||
<tr>
|
<tr>
|
||||||
<td>
|
<td>
|
||||||
<i .icon-user></i> #
|
<i .icon-user></i> #
|
||||||
|
@ -20,8 +20,12 @@
|
||||||
<span .muted>
|
<span .muted>
|
||||||
away
|
away
|
||||||
$else
|
$else
|
||||||
$if canpair
|
$if paired
|
||||||
<a .btn .btn-primary .btn-small href="@{StartXMPPPairR buddyid}">
|
<span .label .label-success>
|
||||||
Start pairing
|
paired
|
||||||
$else
|
$else
|
||||||
not using git-annex
|
$if canpair
|
||||||
|
<a .btn .btn-primary .btn-small href="@{StartXMPPPairR buddyid}">
|
||||||
|
Start pairing
|
||||||
|
$else
|
||||||
|
not using git-annex
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue