diff options
Diffstat (limited to 'Presence/Presence.hs')
-rw-r--r-- | Presence/Presence.hs | 183 |
1 files changed, 86 insertions, 97 deletions
diff --git a/Presence/Presence.hs b/Presence/Presence.hs index d2a6b6eb..15775857 100644 --- a/Presence/Presence.hs +++ b/Presence/Presence.hs | |||
@@ -1,6 +1,7 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE ExistentialQuantification #-} |
2 | {-# LANGUAGE TupleSections #-} | 2 | {-# LANGUAGE LambdaCase #-} |
3 | {-# LANGUAGE LambdaCase #-} | 3 | {-# LANGUAGE OverloadedStrings #-} |
4 | {-# LANGUAGE TupleSections #-} | ||
4 | module Presence where | 5 | module Presence where |
5 | 6 | ||
6 | import System.Environment | 7 | import System.Environment |
@@ -47,6 +48,7 @@ import PeerResolve | |||
47 | import ConsoleWriter | 48 | import ConsoleWriter |
48 | import ClientState | 49 | import ClientState |
49 | import Util | 50 | import Util |
51 | import qualified Connection | ||
50 | 52 | ||
51 | isPeerKey :: ConnectionKey -> Bool | 53 | isPeerKey :: ConnectionKey -> Bool |
52 | isPeerKey k = case k of { PeerKey {} -> True ; _ -> False } | 54 | isPeerKey k = case k of { PeerKey {} -> True ; _ -> False } |
@@ -59,18 +61,26 @@ localJID user resource = do | |||
59 | hostname <- textHostName | 61 | hostname <- textHostName |
60 | return $ user <> "@" <> hostname <> "/" <> resource | 62 | return $ user <> "@" <> hostname <> "/" <> resource |
61 | 63 | ||
62 | newPresenceState cw = atomically $ do | 64 | data PresenceState = forall status. PresenceState |
65 | { clients :: TVar (Map ConnectionKey ClientState) | ||
66 | , clientsByUser :: TVar (Map Text LocalPresence) | ||
67 | , remotesByPeer :: TVar (Map ConnectionKey | ||
68 | (Map UserName RemotePresence)) | ||
69 | , server :: TMVar (XMPPServer, Connection.Manager status Text) | ||
70 | , keyToChan :: TVar (Map ConnectionKey Conn) | ||
71 | , consoleWriter :: Maybe ConsoleWriter | ||
72 | } | ||
73 | |||
74 | |||
75 | newPresenceState cw xmpp = atomically $ do | ||
63 | clients <- newTVar Map.empty | 76 | clients <- newTVar Map.empty |
64 | clientsByUser <- newTVar Map.empty | 77 | clientsByUser <- newTVar Map.empty |
65 | remotesByPeer <- newTVar Map.empty | 78 | remotesByPeer <- newTVar Map.empty |
66 | associatedPeers <- newTVar Map.empty | ||
67 | xmpp <- newEmptyTMVar | ||
68 | keyToChan <- newTVar Map.empty | 79 | keyToChan <- newTVar Map.empty |
69 | return PresenceState | 80 | return PresenceState |
70 | { clients = clients | 81 | { clients = clients |
71 | , clientsByUser = clientsByUser | 82 | , clientsByUser = clientsByUser |
72 | , remotesByPeer = remotesByPeer | 83 | , remotesByPeer = remotesByPeer |
73 | , associatedPeers = associatedPeers | ||
74 | , keyToChan = keyToChan | 84 | , keyToChan = keyToChan |
75 | , server = xmpp | 85 | , server = xmpp |
76 | , consoleWriter = cw | 86 | , consoleWriter = cw |
@@ -122,7 +132,7 @@ pcSingletonNetworkClient :: ConnectionKey | |||
122 | pcSingletonNetworkClient key client = | 132 | pcSingletonNetworkClient key client = |
123 | LocalPresence | 133 | LocalPresence |
124 | { networkClients = Map.singleton key client | 134 | { networkClients = Map.singleton key client |
125 | } | 135 | } |
126 | 136 | ||
127 | pcInsertNetworkClient :: ConnectionKey -> ClientState -> LocalPresence -> LocalPresence | 137 | pcInsertNetworkClient :: ConnectionKey -> ClientState -> LocalPresence -> LocalPresence |
128 | pcInsertNetworkClient key client pc = | 138 | pcInsertNetworkClient key client pc = |
@@ -139,21 +149,6 @@ pcIsEmpty :: LocalPresence -> Bool | |||
139 | pcIsEmpty pc = Map.null (networkClients pc) | 149 | pcIsEmpty pc = Map.null (networkClients pc) |
140 | 150 | ||
141 | 151 | ||
142 | data PresenceState = PresenceState | ||
143 | { clients :: TVar (Map ConnectionKey ClientState) | ||
144 | , clientsByUser :: TVar (Map Text LocalPresence) | ||
145 | , remotesByPeer :: TVar (Map ConnectionKey | ||
146 | (Map UserName | ||
147 | RemotePresence)) | ||
148 | , -- | These are the remote peers we are seeking to obtain a connection to. | ||
149 | -- See 'rosterGetStuff'. | ||
150 | associatedPeers :: TVar (Map SockAddr ()) | ||
151 | , server :: TMVar XMPPServer | ||
152 | , keyToChan :: TVar (Map ConnectionKey Conn) | ||
153 | , consoleWriter :: Maybe ConsoleWriter | ||
154 | } | ||
155 | |||
156 | |||
157 | 152 | ||
158 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] | 153 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] |
159 | getConsolePids state = do | 154 | getConsolePids state = do |
@@ -197,7 +192,7 @@ chooseResourceName state k addr desired = do | |||
197 | mb | 192 | mb |
198 | 193 | ||
199 | localJID (clientUser client) (clientResource client) | 194 | localJID (clientUser client) (clientResource client) |
200 | 195 | ||
201 | where | 196 | where |
202 | getTTYandPID muid = do | 197 | getTTYandPID muid = do |
203 | -- us <- fmap (map (second fst) . Map.toList) . readTVarIO $ activeUsers state | 198 | -- us <- fmap (map (second fst) . Map.toList) . readTVarIO $ activeUsers state |
@@ -210,9 +205,9 @@ chooseResourceName state k addr desired = do | |||
210 | return (rsc,pid) | 205 | return (rsc,pid) |
211 | 206 | ||
212 | getJabberUserForId muid = | 207 | getJabberUserForId muid = |
213 | maybe (return "nobody") | 208 | maybe (return "nobody") |
214 | (\(uid,_) -> | 209 | (\(uid,_) -> |
215 | handle (\(SomeException _) -> | 210 | handle (\(SomeException _) -> |
216 | return . (<> "uid.") . Text.pack . show $ uid) | 211 | return . (<> "uid.") . Text.pack . show $ uid) |
217 | $ do | 212 | $ do |
218 | user <- fmap userName $ getUserEntryForID uid | 213 | user <- fmap userName $ getUserEntryForID uid |
@@ -248,19 +243,13 @@ rosterGetStuff what state k = forClient state k (return []) | |||
248 | $ \client -> do | 243 | $ \client -> do |
249 | jids <- configText what (clientUser client) | 244 | jids <- configText what (clientUser client) |
250 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 245 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
251 | addrs <- resolveAllPeers hosts | 246 | case state of |
252 | peers <- atomically $ readTVar (associatedPeers state) | 247 | PresenceState { server = svVar } -> do |
253 | addrs <- return $ addrs `Map.difference` peers | 248 | (sv,conns) <- atomically $ takeTMVar svVar |
254 | sv <- atomically $ takeTMVar $ server state | 249 | -- Grok peers to associate with from the roster: |
255 | -- Grok peers to associate with from the roster: | 250 | forM_ hosts $ \host -> Connection.setPolicy conns host Connection.TryingToConnect |
256 | forM_ (Map.keys addrs) $ \addr -> do | 251 | atomically $ putTMVar svVar (sv,conns) |
257 | putStrLn $ "new addr: "++show addr | 252 | return jids |
258 | addPeer sv addr | ||
259 | -- Update local set of associated peers | ||
260 | atomically $ do | ||
261 | writeTVar (associatedPeers state) (addrs `Map.union` peers) | ||
262 | putTMVar (server state) sv | ||
263 | return jids | ||
264 | 253 | ||
265 | rosterGetBuddies :: PresenceState -> ConnectionKey -> IO [Text] | 254 | rosterGetBuddies :: PresenceState -> ConnectionKey -> IO [Text] |
266 | rosterGetBuddies state k = rosterGetStuff ConfigFiles.getBuddies state k | 255 | rosterGetBuddies state k = rosterGetStuff ConfigFiles.getBuddies state k |
@@ -309,7 +298,7 @@ sendProbesAndSolicitations state k laddr chan = do | |||
309 | -- XXX: The following O(n²) nub may be a little | 298 | -- XXX: The following O(n²) nub may be a little |
310 | -- too onerous. | 299 | -- too onerous. |
311 | forM_ (nub xs) $ \(isbud,u,user) -> do | 300 | forM_ (nub xs) $ \(isbud,u,user) -> do |
312 | let make = if isbud then presenceProbe | 301 | let make = if isbud then presenceProbe |
313 | else presenceSolicitation | 302 | else presenceSolicitation |
314 | toh = peerKeyToText k | 303 | toh = peerKeyToText k |
315 | jid = unsplitJID (u,toh,Nothing) | 304 | jid = unsplitJID (u,toh,Nothing) |
@@ -448,7 +437,7 @@ deliverMessage :: PresenceState | |||
448 | -> IO () | 437 | -> IO () |
449 | -> StanzaWrap (LockedChan Event) | 438 | -> StanzaWrap (LockedChan Event) |
450 | -> IO () | 439 | -> IO () |
451 | deliverMessage state fail msg = | 440 | deliverMessage state fail msg = |
452 | case stanzaOrigin msg of | 441 | case stanzaOrigin msg of |
453 | NetworkOrigin senderk@(ClientKey {}) _ -> do | 442 | NetworkOrigin senderk@(ClientKey {}) _ -> do |
454 | -- Case 1. Client -> Peer | 443 | -- Case 1. Client -> Peer |
@@ -509,14 +498,14 @@ deliverMessage state fail msg = | |||
509 | 498 | ||
510 | 499 | ||
511 | setClientFlag :: PresenceState -> ConnectionKey -> Int8 -> IO () | 500 | setClientFlag :: PresenceState -> ConnectionKey -> Int8 -> IO () |
512 | setClientFlag state k flag = | 501 | setClientFlag state k flag = |
513 | atomically $ do | 502 | atomically $ do |
514 | cmap <- readTVar (clients state) | 503 | cmap <- readTVar (clients state) |
515 | flip (maybe $ return ()) (Map.lookup k cmap) $ \client -> do | 504 | flip (maybe $ return ()) (Map.lookup k cmap) $ \client -> do |
516 | setClientFlag0 client flag | 505 | setClientFlag0 client flag |
517 | 506 | ||
518 | setClientFlag0 :: ClientState -> Int8 -> STM () | 507 | setClientFlag0 :: ClientState -> Int8 -> STM () |
519 | setClientFlag0 client flag = | 508 | setClientFlag0 client flag = |
520 | modifyTVar' (clientFlags client) (\flgs -> flgs .|. flag) | 509 | modifyTVar' (clientFlags client) (\flgs -> flgs .|. flag) |
521 | 510 | ||
522 | informSentRoster :: PresenceState -> ConnectionKey -> IO () | 511 | informSentRoster :: PresenceState -> ConnectionKey -> IO () |
@@ -528,7 +517,7 @@ subscribedPeers :: Text -> IO [SockAddr] | |||
528 | subscribedPeers user = do | 517 | subscribedPeers user = do |
529 | jids <- configText ConfigFiles.getSubscribers user | 518 | jids <- configText ConfigFiles.getSubscribers user |
530 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 519 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
531 | fmap Map.keys $ resolveAllPeers hosts | 520 | fmap Map.keys $ resolveAllPeers hosts |
532 | 521 | ||
533 | -- | this JID is suitable for peers, not clients. | 522 | -- | this JID is suitable for peers, not clients. |
534 | clientJID :: Conn -> ClientState -> Text | 523 | clientJID :: Conn -> ClientState -> Text |
@@ -577,13 +566,13 @@ informPeerPresence :: PresenceState | |||
577 | -> IO () | 566 | -> IO () |
578 | informPeerPresence state k stanza = do | 567 | informPeerPresence state k stanza = do |
579 | -- Presence must indicate full JID with resource... | 568 | -- Presence must indicate full JID with resource... |
580 | putStrLn $ "xmppInformPeerPresence checking from address..." | 569 | putStrLn $ "xmppInformPeerPresence checking from address..." |
581 | flip (maybe $ return ()) (stanzaFrom stanza) $ \from -> do | 570 | flip (maybe $ return ()) (stanzaFrom stanza) $ \from -> do |
582 | let (muser,h,mresource) = splitJID from | 571 | let (muser,h,mresource) = splitJID from |
583 | putStrLn $ "xmppInformPeerPresence from = " ++ show from | 572 | putStrLn $ "xmppInformPeerPresence from = " ++ show from |
584 | -- flip (maybe $ return ()) mresource $ \resource -> do | 573 | -- flip (maybe $ return ()) mresource $ \resource -> do |
585 | flip (maybe $ return ()) muser $ \user -> do | 574 | flip (maybe $ return ()) muser $ \user -> do |
586 | 575 | ||
587 | clients <- atomically $ do | 576 | clients <- atomically $ do |
588 | 577 | ||
589 | -- Update remotesByPeer... | 578 | -- Update remotesByPeer... |
@@ -592,33 +581,33 @@ informPeerPresence state k stanza = do | |||
592 | rp = case (presenceShow $ stanzaType stanza) of | 581 | rp = case (presenceShow $ stanzaType stanza) of |
593 | Offline -> | 582 | Offline -> |
594 | maybe Map.empty | 583 | maybe Map.empty |
595 | (\resource -> | 584 | (\resource -> |
596 | maybe (Map.empty) | 585 | maybe (Map.empty) |
597 | (Map.delete resource . resources) | 586 | (Map.delete resource . resources) |
598 | $ Map.lookup user umap) | 587 | $ Map.lookup user umap) |
599 | mresource | 588 | mresource |
600 | 589 | ||
601 | _ ->maybe Map.empty | 590 | _ ->maybe Map.empty |
602 | (\resource -> | 591 | (\resource -> |
603 | maybe (Map.singleton resource stanza) | 592 | maybe (Map.singleton resource stanza) |
604 | (Map.insert resource stanza . resources ) | 593 | (Map.insert resource stanza . resources ) |
605 | $ Map.lookup user umap) | 594 | $ Map.lookup user umap) |
606 | mresource | 595 | mresource |
607 | umap' = Map.insert user (RemotePresence rp) umap | 596 | umap' = Map.insert user (RemotePresence rp) umap |
608 | 597 | ||
609 | flip (maybe $ return []) (case presenceShow $ stanzaType stanza of | 598 | flip (maybe $ return []) (case presenceShow $ stanzaType stanza of |
610 | Offline -> Just () | 599 | Offline -> Just () |
611 | _ -> mresource >> Just ()) | 600 | _ -> mresource >> Just ()) |
612 | $ \_ -> do | 601 | $ \_ -> do |
613 | writeTVar (remotesByPeer state) $ Map.insert k umap' rbp | 602 | writeTVar (remotesByPeer state) $ Map.insert k umap' rbp |
614 | -- TODO: Store or delete the stanza (remotesByPeer) | 603 | -- TODO: Store or delete the stanza (remotesByPeer) |
615 | 604 | ||
616 | -- all clients, we'll filter available/authorized later | 605 | -- all clients, we'll filter available/authorized later |
617 | 606 | ||
618 | ktc <- readTVar (keyToChan state) | 607 | ktc <- readTVar (keyToChan state) |
619 | runTraversableT $ do | 608 | runTraversableT $ do |
620 | (ck,client) <- liftMT $ fmap Map.toList $ readTVar (clients state) | 609 | (ck,client) <- liftMT $ fmap Map.toList $ readTVar (clients state) |
621 | con <- liftMaybe $ Map.lookup ck ktc | 610 | con <- liftMaybe $ Map.lookup ck ktc |
622 | return (ck,con,client) | 611 | return (ck,con,client) |
623 | putStrLn $ "xmppInformPeerPresence (length clients="++show (length clients)++")" | 612 | putStrLn $ "xmppInformPeerPresence (length clients="++show (length clients)++")" |
624 | forM_ clients $ \(ck,con,client) -> do | 613 | forM_ clients $ \(ck,con,client) -> do |
@@ -631,7 +620,7 @@ informPeerPresence state k stanza = do | |||
631 | let ClientKey laddr = ck | 620 | let ClientKey laddr = ck |
632 | (_,trip) <- multiplyJIDForClient laddr from | 621 | (_,trip) <- multiplyJIDForClient laddr from |
633 | return (map unsplitJID trip) | 622 | return (map unsplitJID trip) |
634 | 623 | ||
635 | putStrLn $ "sending to client: " ++ show (stanzaType stanza,froms) | 624 | putStrLn $ "sending to client: " ++ show (stanzaType stanza,froms) |
636 | forM_ froms $ \from' -> do | 625 | forM_ froms $ \from' -> do |
637 | dup <- cloneStanza stanza | 626 | dup <- cloneStanza stanza |
@@ -706,7 +695,7 @@ sendCachedPresence state k = do | |||
706 | rbp <- atomically $ readTVar (remotesByPeer state) | 695 | rbp <- atomically $ readTVar (remotesByPeer state) |
707 | jids <- configText ConfigFiles.getBuddies (clientUser client) | 696 | jids <- configText ConfigFiles.getBuddies (clientUser client) |
708 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 697 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
709 | addrs <- resolveAllPeers hosts | 698 | addrs <- resolveAllPeers hosts |
710 | let onlines = rbp `Map.intersection` Map.mapKeys PeerKey addrs | 699 | let onlines = rbp `Map.intersection` Map.mapKeys PeerKey addrs |
711 | ClientKey laddr = k | 700 | ClientKey laddr = k |
712 | mcon <- atomically $ do ktc <- readTVar (keyToChan state) | 701 | mcon <- atomically $ do ktc <- readTVar (keyToChan state) |
@@ -790,9 +779,8 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
790 | let (mu,h,_) = splitJID to | 779 | let (mu,h,_) = splitJID to |
791 | to <- return $ unsplitJID (mu,h,Nothing) -- delete resource | 780 | to <- return $ unsplitJID (mu,h,Nothing) -- delete resource |
792 | flip (maybe fail) mu $ \u -> do | 781 | flip (maybe fail) mu $ \u -> do |
793 | addrs <- resolvePeer h | ||
794 | if null addrs then fail else do | ||
795 | -- add to-address to from's solicited | 782 | -- add to-address to from's solicited |
783 | addrs <- resolvePeer h | ||
796 | addToRosterFile ConfigFiles.modifySolicited (clientUser client) to addrs | 784 | addToRosterFile ConfigFiles.modifySolicited (clientUser client) to addrs |
797 | removeFromRosterFile ConfigFiles.modifyBuddies (clientUser client) to addrs | 785 | removeFromRosterFile ConfigFiles.modifyBuddies (clientUser client) to addrs |
798 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers (clientUser client) | 786 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers (clientUser client) |
@@ -800,45 +788,46 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
800 | -- subscribers: "from" | 788 | -- subscribers: "from" |
801 | -- buddies: "to" | 789 | -- buddies: "to" |
802 | 790 | ||
803 | (ktc,ap) <- atomically $ | 791 | case state of |
804 | liftM2 (,) (readTVar $ keyToChan state) | 792 | PresenceState { server = svVar } -> do |
805 | (readTVar $ associatedPeers state) | 793 | |
806 | 794 | (ktc,(sv,conns)) <- atomically $ | |
807 | case stanzaType stanza of | 795 | liftM2 (,) (readTVar $ keyToChan state) |
808 | PresenceRequestSubscription True -> do | 796 | (takeTMVar svVar) |
809 | hostname <- textHostName | 797 | |
810 | let cjid = unsplitJID (Just $ clientUser client, hostname,Nothing) | 798 | case stanzaType stanza of |
811 | chans <- clientCons state ktc (clientUser client) | 799 | PresenceRequestSubscription True -> do |
812 | forM_ chans $ \( Conn { connChan=chan }, client ) -> do | 800 | hostname <- textHostName |
813 | -- roster update ask="subscribe" | 801 | let cjid = unsplitJID (Just $ clientUser client, hostname,Nothing) |
814 | update <- makeRosterUpdate cjid to | 802 | chans <- clientCons state ktc (clientUser client) |
815 | [ ("ask","subscribe") | 803 | forM_ chans $ \( Conn { connChan=chan }, client ) -> do |
816 | , if is_subscribed then ("subscription","from") | 804 | -- roster update ask="subscribe" |
817 | else ("subscription","none") | 805 | update <- makeRosterUpdate cjid to |
818 | ] | 806 | [ ("ask","subscribe") |
819 | sendModifiedStanzaToClient update chan | 807 | , if is_subscribed then ("subscription","from") |
820 | _ -> return () | 808 | else ("subscription","none") |
821 | 809 | ] | |
822 | let dsts = Map.fromList $ map ((,()) . PeerKey) addrs | 810 | sendModifiedStanzaToClient update chan |
823 | cdsts = ktc `Map.intersection` dsts | 811 | _ -> return () |
824 | forM_ (Map.toList cdsts) $ \(pk,con) -> do | 812 | |
825 | -- if already connected, send solicitation ... | 813 | let dsts = Map.fromList $ map ((,()) . PeerKey) addrs |
826 | -- let from = clientJID con client | 814 | cdsts = ktc `Map.intersection` dsts |
827 | let from = unsplitJID ( Just $ clientUser client | 815 | forM_ (Map.toList cdsts) $ \(pk,con) -> do |
828 | , addrToText $ auxAddr con | 816 | -- if already connected, send solicitation ... |
829 | , Nothing ) | 817 | -- let from = clientJID con client |
830 | mb <- rewriteJIDForPeer to | 818 | let from = unsplitJID ( Just $ clientUser client |
831 | flip (maybe $ return ()) mb $ \(to',addr) -> do | 819 | , addrToText $ auxAddr con |
832 | dup <- cloneStanza stanza | 820 | , Nothing ) |
833 | sendModifiedStanzaToPeer (dup { stanzaTo = Just to' | 821 | mb <- rewriteJIDForPeer to |
834 | , stanzaFrom = Just from }) | 822 | flip (maybe $ return ()) mb $ \(to',addr) -> do |
835 | (connChan con) | 823 | dup <- cloneStanza stanza |
836 | let addrm = Map.fromList (map (,()) addrs) | 824 | sendModifiedStanzaToPeer (dup { stanzaTo = Just to' |
837 | when (not . Map.null $ addrm Map.\\ ap) $ do | 825 | , stanzaFrom = Just from }) |
826 | (connChan con) | ||
827 | let addrm = Map.fromList (map (,()) addrs) | ||
838 | -- Add peer if we are not already associated ... | 828 | -- Add peer if we are not already associated ... |
839 | sv <- atomically $ takeTMVar $ server state | 829 | Connection.setPolicy conns h Connection.TryingToConnect |
840 | addPeer sv (head addrs) | 830 | atomically $ putTMVar svVar (sv,conns) |
841 | atomically $ putTMVar (server state) sv | ||
842 | 831 | ||
843 | 832 | ||
844 | resolvedFromRoster | 833 | resolvedFromRoster |
@@ -900,7 +889,7 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
900 | else do | 889 | else do |
901 | 890 | ||
902 | -- TODO: if peer-connection is to self, then auto-approve local user. | 891 | -- TODO: if peer-connection is to self, then auto-approve local user. |
903 | 892 | ||
904 | -- add from-address to to's pending | 893 | -- add from-address to to's pending |
905 | addrs <- resolvePeer from_h | 894 | addrs <- resolvePeer from_h |
906 | 895 | ||
@@ -995,7 +984,7 @@ clientInformSubscription state fail k stanza = do | |||
995 | , stanzaFrom = Just from }) | 984 | , stanzaFrom = Just from }) |
996 | (connChan con) | 985 | (connChan con) |
997 | answerProbe state (Just from) pk (connChan con) | 986 | answerProbe state (Just from) pk (connChan con) |
998 | 987 | ||
999 | peerInformSubscription :: PresenceState | 988 | peerInformSubscription :: PresenceState |
1000 | -> IO () | 989 | -> IO () |
1001 | -> ConnectionKey | 990 | -> ConnectionKey |