diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/Presence.hs | 1045 | ||||
-rw-r--r-- | Presence/Util.hs | 59 |
2 files changed, 1104 insertions, 0 deletions
diff --git a/Presence/Presence.hs b/Presence/Presence.hs new file mode 100644 index 00000000..2344fb75 --- /dev/null +++ b/Presence/Presence.hs | |||
@@ -0,0 +1,1045 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | {-# LANGUAGE TupleSections #-} | ||
3 | {-# LANGUAGE LambdaCase #-} | ||
4 | module Presence where | ||
5 | |||
6 | import System.Environment | ||
7 | import System.Posix.Signals | ||
8 | import Control.Concurrent (threadDelay,forkIO,forkOS,killThread,throwTo) | ||
9 | import Control.Concurrent.STM | ||
10 | import Control.Concurrent.STM.TMVar | ||
11 | import Control.Monad.Trans.Resource (runResourceT) | ||
12 | import Control.Monad.Trans | ||
13 | import Control.Monad.IO.Class (MonadIO, liftIO) | ||
14 | import Network.Socket ( SockAddr(..) ) | ||
15 | import System.Endian (fromBE32) | ||
16 | import Data.List (nub, (\\), intersect, groupBy, sort, sortBy ) | ||
17 | import Data.Ord (comparing ) | ||
18 | import Data.Monoid ( (<>), Sum(..), getSum ) | ||
19 | import qualified Data.Text as Text | ||
20 | import qualified Data.Text.IO as Text | ||
21 | import qualified Data.Text.Encoding as Text | ||
22 | import Control.Monad | ||
23 | import Control.Monad.Fix | ||
24 | import qualified Network.BSD as BSD | ||
25 | import qualified Data.Text as Text | ||
26 | import Data.Text (Text) | ||
27 | import qualified Data.Map as Map | ||
28 | import Data.Map (Map) | ||
29 | import Control.Exception ({-evaluate,-}handle,SomeException(..),bracketOnError,ErrorCall(..)) | ||
30 | import System.IO.Error (isDoesNotExistError) | ||
31 | import System.Posix.User (getUserEntryForID,userName) | ||
32 | import qualified Data.ByteString.Lazy.Char8 as L | ||
33 | import qualified ConfigFiles | ||
34 | import Data.Maybe (maybeToList,listToMaybe,mapMaybe) | ||
35 | import Data.Bits | ||
36 | import Data.Int (Int8) | ||
37 | import Data.XML.Types (Event) | ||
38 | import System.Posix.Types (UserID,CPid) | ||
39 | import Control.Applicative | ||
40 | |||
41 | import LockedChan (LockedChan) | ||
42 | import TraversableT | ||
43 | import UTmp (ProcessID,users) | ||
44 | import LocalPeerCred | ||
45 | import XMPPServer | ||
46 | import PeerResolve | ||
47 | import ConsoleWriter | ||
48 | import ClientState | ||
49 | import Util | ||
50 | |||
51 | isPeerKey :: ConnectionKey -> Bool | ||
52 | isPeerKey k = case k of { PeerKey {} -> True ; _ -> False } | ||
53 | |||
54 | isClientKey :: ConnectionKey -> Bool | ||
55 | isClientKey k = case k of { ClientKey {} -> True ; _ -> False } | ||
56 | |||
57 | localJID :: Text -> Text -> IO Text | ||
58 | localJID user resource = do | ||
59 | hostname <- textHostName | ||
60 | return $ user <> "@" <> hostname <> "/" <> resource | ||
61 | |||
62 | newPresenceState cw = atomically $ do | ||
63 | clients <- newTVar Map.empty | ||
64 | clientsByUser <- newTVar Map.empty | ||
65 | remotesByPeer <- newTVar Map.empty | ||
66 | associatedPeers <- newTVar Map.empty | ||
67 | xmpp <- newEmptyTMVar | ||
68 | keyToChan <- newTVar Map.empty | ||
69 | return PresenceState | ||
70 | { clients = clients | ||
71 | , clientsByUser = clientsByUser | ||
72 | , remotesByPeer = remotesByPeer | ||
73 | , associatedPeers = associatedPeers | ||
74 | , keyToChan = keyToChan | ||
75 | , server = xmpp | ||
76 | , consoleWriter = cw | ||
77 | } | ||
78 | |||
79 | |||
80 | presenceHooks state verbosity = XMPPServerParameters | ||
81 | { xmppChooseResourceName = chooseResourceName state | ||
82 | , xmppTellClientHisName = tellClientHisName state | ||
83 | , xmppTellMyNameToClient = textHostName | ||
84 | , xmppTellMyNameToPeer = \addr -> return $ addrToText addr | ||
85 | , xmppTellPeerHisName = return . peerKeyToText | ||
86 | , xmppTellClientNameOfPeer = flip peerKeyToResolvedName | ||
87 | , xmppNewConnection = newConn state | ||
88 | , xmppEOF = eofConn state | ||
89 | , xmppRosterBuddies = rosterGetBuddies state | ||
90 | , xmppRosterSubscribers = rosterGetSubscribers state | ||
91 | , xmppRosterSolicited = rosterGetSolicited state | ||
92 | , xmppRosterOthers = rosterGetOthers state | ||
93 | , xmppSubscribeToRoster = informSentRoster state | ||
94 | , xmppDeliverMessage = deliverMessage state | ||
95 | , xmppInformClientPresence = informClientPresence state | ||
96 | , xmppInformPeerPresence = informPeerPresence state | ||
97 | , xmppAnswerProbe = \k stanza chan -> answerProbe state (stanzaTo stanza) k chan | ||
98 | , xmppClientSubscriptionRequest = clientSubscriptionRequest state | ||
99 | , xmppPeerSubscriptionRequest = peerSubscriptionRequest state | ||
100 | , xmppClientInformSubscription = clientInformSubscription state | ||
101 | , xmppPeerInformSubscription = peerInformSubscription state | ||
102 | , xmppVerbosity = return verbosity | ||
103 | } | ||
104 | |||
105 | |||
106 | data LocalPresence = LocalPresence | ||
107 | { networkClients :: Map ConnectionKey ClientState | ||
108 | -- TODO: loginClients | ||
109 | } | ||
110 | |||
111 | data RemotePresence = RemotePresence | ||
112 | { resources :: Map Text Stanza | ||
113 | -- , localSubscribers :: Map Text () | ||
114 | -- ^ subset of clientsByUser who should be | ||
115 | -- notified about this presence. | ||
116 | } | ||
117 | |||
118 | |||
119 | |||
120 | pcSingletonNetworkClient :: ConnectionKey | ||
121 | -> ClientState -> LocalPresence | ||
122 | pcSingletonNetworkClient key client = | ||
123 | LocalPresence | ||
124 | { networkClients = Map.singleton key client | ||
125 | } | ||
126 | |||
127 | pcInsertNetworkClient :: ConnectionKey -> ClientState -> LocalPresence -> LocalPresence | ||
128 | pcInsertNetworkClient key client pc = | ||
129 | pc { networkClients = Map.insert key client (networkClients pc) } | ||
130 | |||
131 | pcRemoveNewtworkClient :: ConnectionKey | ||
132 | -> LocalPresence -> Maybe LocalPresence | ||
133 | pcRemoveNewtworkClient key pc = if pcIsEmpty pc' then Nothing | ||
134 | else Just pc' | ||
135 | where | ||
136 | pc' = pc { networkClients = Map.delete key (networkClients pc) } | ||
137 | |||
138 | pcIsEmpty :: LocalPresence -> Bool | ||
139 | pcIsEmpty pc = Map.null (networkClients pc) | ||
140 | |||
141 | |||
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 | , associatedPeers :: TVar (Map SockAddr ()) | ||
149 | , server :: TMVar XMPPServer | ||
150 | , keyToChan :: TVar (Map ConnectionKey Conn) | ||
151 | , consoleWriter :: ConsoleWriter | ||
152 | } | ||
153 | |||
154 | |||
155 | |||
156 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] | ||
157 | getConsolePids state = do | ||
158 | us <- UTmp.users | ||
159 | return $ map (\(_,tty,pid)->(lazyByteStringToText tty,pid)) us | ||
160 | |||
161 | identifyTTY' :: [(Text, ProcessID)] | ||
162 | -> System.Posix.Types.UserID | ||
163 | -> L.ByteString | ||
164 | -> IO (Maybe Text, Maybe System.Posix.Types.CPid) | ||
165 | identifyTTY' ttypids uid inode = ttypid | ||
166 | where ttypids' = map (\(tty,pid)->(L.fromChunks [Text.encodeUtf8 tty], pid)) ttypids | ||
167 | ttypid = fmap textify $ identifyTTY ttypids' uid inode | ||
168 | textify (tty,pid) = (fmap lazyByteStringToText tty, pid) | ||
169 | |||
170 | chooseResourceName :: PresenceState | ||
171 | -> ConnectionKey -> SockAddr -> t -> IO Text | ||
172 | chooseResourceName state k addr desired = do | ||
173 | muid <- getLocalPeerCred' addr | ||
174 | (mtty,pid) <- getTTYandPID muid | ||
175 | user <- getJabberUserForId muid | ||
176 | status <- atomically $ newTVar Nothing | ||
177 | flgs <- atomically $ newTVar 0 | ||
178 | let client = ClientState { clientResource = maybe "fallback" id mtty | ||
179 | , clientUser = user | ||
180 | , clientPid = pid | ||
181 | , clientStatus = status | ||
182 | , clientFlags = flgs } | ||
183 | |||
184 | do -- forward-lookup of the buddies so that it is cached for reversing. | ||
185 | buds <- configText ConfigFiles.getBuddies (clientUser client) | ||
186 | forM_ buds $ \bud -> do | ||
187 | let (_,h,_) = splitJID bud | ||
188 | forkIO $ void $ resolvePeer h | ||
189 | |||
190 | atomically $ do | ||
191 | modifyTVar' (clients state) $ Map.insert k client | ||
192 | modifyTVar' (clientsByUser state) $ flip Map.alter (clientUser client) | ||
193 | $ \mb -> Just $ maybe (pcSingletonNetworkClient k client) | ||
194 | (pcInsertNetworkClient k client) | ||
195 | mb | ||
196 | |||
197 | localJID (clientUser client) (clientResource client) | ||
198 | |||
199 | where | ||
200 | getTTYandPID muid = do | ||
201 | -- us <- fmap (map (second fst) . Map.toList) . readTVarIO $ activeUsers state | ||
202 | ttypids <- getConsolePids state | ||
203 | -- let tailOf3 ((_,a),b) = (a,b) | ||
204 | (t,pid) <- case muid of | ||
205 | Just (uid,inode) -> identifyTTY' ttypids uid inode | ||
206 | Nothing -> return (Nothing,Nothing) | ||
207 | let rsc = t `mplus` fmap ( ("pid."<>) . Text.pack . show ) pid | ||
208 | return (rsc,pid) | ||
209 | |||
210 | getJabberUserForId muid = | ||
211 | maybe (return "nobody") | ||
212 | (\(uid,_) -> | ||
213 | handle (\(SomeException _) -> | ||
214 | return . (<> "uid.") . Text.pack . show $ uid) | ||
215 | $ do | ||
216 | user <- fmap userName $ getUserEntryForID uid | ||
217 | return (Text.pack user) | ||
218 | ) | ||
219 | muid | ||
220 | |||
221 | forClient :: PresenceState | ||
222 | -> ConnectionKey -> IO b -> (ClientState -> IO b) -> IO b | ||
223 | forClient state k fallback f = do | ||
224 | mclient <- atomically $ do | ||
225 | cs <- readTVar (clients state) | ||
226 | return $ Map.lookup k cs | ||
227 | maybe fallback f mclient | ||
228 | |||
229 | tellClientHisName :: PresenceState -> ConnectionKey -> IO Text | ||
230 | tellClientHisName state k = forClient state k fallback go | ||
231 | where | ||
232 | fallback = localJID "nobody" "fallback" | ||
233 | go client = localJID (clientUser client) (clientResource client) | ||
234 | |||
235 | toMapUnit :: Ord k => [k] -> Map k () | ||
236 | toMapUnit xs = Map.fromList $ map (,()) xs | ||
237 | |||
238 | resolveAllPeers :: [Text] -> IO (Map SockAddr ()) | ||
239 | resolveAllPeers hosts = fmap (toMapUnit . concat) $ Prelude.mapM (fmap (take 1) . resolvePeer) hosts | ||
240 | |||
241 | |||
242 | rosterGetStuff | ||
243 | :: (L.ByteString -> IO [L.ByteString]) | ||
244 | -> PresenceState -> ConnectionKey -> IO [Text] | ||
245 | rosterGetStuff what state k = forClient state k (return []) | ||
246 | $ \client -> do | ||
247 | jids <- configText what (clientUser client) | ||
248 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | ||
249 | addrs <- resolveAllPeers hosts | ||
250 | peers <- atomically $ readTVar (associatedPeers state) | ||
251 | addrs <- return $ addrs `Map.difference` peers | ||
252 | sv <- atomically $ takeTMVar $ server state | ||
253 | -- Grok peers to associate with from the roster: | ||
254 | forM_ (Map.keys addrs) $ \addr -> do | ||
255 | putStrLn $ "new addr: "++show addr | ||
256 | addPeer sv addr | ||
257 | -- Update local set of associated peers | ||
258 | atomically $ do | ||
259 | writeTVar (associatedPeers state) (addrs `Map.union` peers) | ||
260 | putTMVar (server state) sv | ||
261 | return jids | ||
262 | |||
263 | rosterGetBuddies :: PresenceState -> ConnectionKey -> IO [Text] | ||
264 | rosterGetBuddies state k = rosterGetStuff ConfigFiles.getBuddies state k | ||
265 | |||
266 | rosterGetSolicited :: PresenceState -> ConnectionKey -> IO [Text] | ||
267 | rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited | ||
268 | |||
269 | rosterGetOthers :: PresenceState -> ConnectionKey -> IO [Text] | ||
270 | rosterGetOthers = rosterGetStuff ConfigFiles.getOthers | ||
271 | |||
272 | rosterGetSubscribers :: PresenceState -> ConnectionKey -> IO [Text] | ||
273 | rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers | ||
274 | |||
275 | data Conn = Conn { connChan :: TChan Stanza | ||
276 | , auxAddr :: SockAddr } | ||
277 | |||
278 | configText :: Functor f => | ||
279 | (L.ByteString -> f [L.ByteString]) -> Text -> f [Text] | ||
280 | configText what u = fmap (map lazyByteStringToText) | ||
281 | $ what (textToLazyByteString u) | ||
282 | |||
283 | getBuddies' :: Text -> IO [Text] | ||
284 | getBuddies' = configText ConfigFiles.getBuddies | ||
285 | getSolicited' :: Text -> IO [Text] | ||
286 | getSolicited' = configText ConfigFiles.getSolicited | ||
287 | |||
288 | sendProbesAndSolicitations :: PresenceState | ||
289 | -> ConnectionKey -> SockAddr -> TChan Stanza -> IO () | ||
290 | sendProbesAndSolicitations state k laddr chan = do | ||
291 | -- get all buddies & solicited matching k for all users | ||
292 | xs <- runTraversableT $ do | ||
293 | cbu <- lift $ atomically $ readTVar $ clientsByUser state | ||
294 | user <- liftT $ Map.keys cbu | ||
295 | (isbud,getter) <- liftT [(True ,getBuddies' ) | ||
296 | ,(False,getSolicited')] | ||
297 | bud <- liftMT $ getter user | ||
298 | let (u,h,r) = splitJID bud | ||
299 | addr <- liftMT $ nub `fmap` resolvePeer h | ||
300 | liftT $ guard (PeerKey addr == k) | ||
301 | -- Note: Earlier I was tempted to do all the IO | ||
302 | -- within the TraversableT monad. That apparently | ||
303 | -- is a bad idea. Perhaps due to laziness and an | ||
304 | -- unforced list? Instead, we will return a list | ||
305 | -- of (Bool,Text) for processing outside. | ||
306 | return (isbud,u,if isbud then "" else user) | ||
307 | -- XXX: The following O(n²) nub may be a little | ||
308 | -- too onerous. | ||
309 | forM_ (nub xs) $ \(isbud,u,user) -> do | ||
310 | let make = if isbud then presenceProbe | ||
311 | else presenceSolicitation | ||
312 | toh = peerKeyToText k | ||
313 | jid = unsplitJID (u,toh,Nothing) | ||
314 | me = addrToText laddr | ||
315 | from = if isbud then me -- probe from server | ||
316 | else -- solicitation from particular user | ||
317 | unsplitJID (Just user,me,Nothing) | ||
318 | stanza <- make from jid | ||
319 | -- send probes for buddies, solicitations for solicited. | ||
320 | putStrLn $ "probing "++show k++" for: " ++ show (isbud,jid) | ||
321 | atomically $ writeTChan chan stanza | ||
322 | -- reverse xs `seq` return () | ||
323 | |||
324 | newConn :: PresenceState -> ConnectionKey -> SockAddr -> TChan Stanza -> IO () | ||
325 | newConn state k addr outchan = do | ||
326 | atomically $ modifyTVar' (keyToChan state) | ||
327 | $ Map.insert k Conn { connChan = outchan | ||
328 | , auxAddr = addr } | ||
329 | when (isPeerKey k) | ||
330 | $ sendProbesAndSolicitations state k addr outchan | ||
331 | |||
332 | delclient :: (Alternative m, Monad m) => | ||
333 | ConnectionKey -> m LocalPresence -> m LocalPresence | ||
334 | delclient k mlp = do | ||
335 | lp <- mlp | ||
336 | let nc = Map.delete k $ networkClients lp | ||
337 | guard $ not (Map.null nc) | ||
338 | return $ lp { networkClients = nc } | ||
339 | |||
340 | eofConn :: PresenceState -> ConnectionKey -> IO () | ||
341 | eofConn state k = do | ||
342 | atomically $ modifyTVar' (keyToChan state) $ Map.delete k | ||
343 | case k of | ||
344 | ClientKey {} -> do | ||
345 | forClient state k (return ()) $ \client -> do | ||
346 | stanza <- makePresenceStanza "jabber:server" Nothing Offline | ||
347 | informClientPresence state k stanza | ||
348 | atomically $ do | ||
349 | modifyTVar' (clientsByUser state) | ||
350 | $ Map.alter (delclient k) (clientUser client) | ||
351 | PeerKey {} -> do | ||
352 | let h = peerKeyToText k | ||
353 | jids <- atomically $ do | ||
354 | rbp <- readTVar (remotesByPeer state) | ||
355 | return $ do | ||
356 | umap <- maybeToList $ Map.lookup k rbp | ||
357 | (u,rp) <- Map.toList umap | ||
358 | r <- Map.keys (resources rp) | ||
359 | return $ unsplitJID (Just u, h, Just r) | ||
360 | forM_ jids $ \jid -> do | ||
361 | stanza <- makePresenceStanza "jabber:client" (Just jid) Offline | ||
362 | informPeerPresence state k stanza | ||
363 | |||
364 | {- | ||
365 | rewriteJIDForClient1:: Text -> IO (Maybe ((Maybe Text,Text,Maybe Text),SockAddr)) | ||
366 | rewriteJIDForClient1 jid = do | ||
367 | let (n,h,r) = splitJID jid | ||
368 | maddr <- fmap listToMaybe $ resolvePeer h | ||
369 | flip (maybe $ return Nothing) maddr $ \addr -> do | ||
370 | h' <- peerKeyToResolvedName (PeerKey addr) | ||
371 | return $ Just ((n,h',r), addr) | ||
372 | -} | ||
373 | |||
374 | -- | The given address is taken to be the local address for the socket this JID | ||
375 | -- came in on. The returned JID parts are suitable for unsplitJID to create a | ||
376 | -- valid JID for communicating to a client. The returned Bool is True when the | ||
377 | -- host part refers to this local host (i.e. it equals the given SockAddr). | ||
378 | -- If there are multiple results, it will prefer one which is a member of the | ||
379 | -- given list in the last argument. | ||
380 | rewriteJIDForClient :: SockAddr -> Text -> [Text] -> IO (Bool,(Maybe Text,Text,Maybe Text)) | ||
381 | rewriteJIDForClient laddr jid buds = do | ||
382 | let (n,h,r) = splitJID jid | ||
383 | maddr <- parseAddress (strip_brackets h) | ||
384 | flip (maybe $ return (False,(n,ip6literal h,r))) maddr $ \addr -> do | ||
385 | let mine = laddr `withPort` 0 == addr `withPort` 0 | ||
386 | h' <- if mine then textHostName | ||
387 | else peerKeyToResolvedName buds (PeerKey addr) | ||
388 | return (mine,(n,h',r)) | ||
389 | |||
390 | peerKeyToResolvedName :: [Text] -> ConnectionKey -> IO Text | ||
391 | peerKeyToResolvedName buds k@(ClientKey { localAddress=addr }) = return "ErrorClIeNt1" | ||
392 | peerKeyToResolvedName buds pk = do | ||
393 | ns <- peerKeyToResolvedNames pk | ||
394 | let hs = map (\jid -> let (_,h,_)=splitJID jid in h) buds | ||
395 | ns' = sortBy (comparing $ not . flip elem hs) ns | ||
396 | return $ maybe (peerKeyToText pk) id (listToMaybe ns') | ||
397 | |||
398 | |||
399 | multiplyJIDForClient :: SockAddr -> Text -> IO (Bool,[(Maybe Text,Text,Maybe Text)]) | ||
400 | multiplyJIDForClient laddr jid = do | ||
401 | let (n,h,r) = splitJID jid | ||
402 | maddr <- parseAddress (strip_brackets h) | ||
403 | flip (maybe $ return (False,[(n,ip6literal h,r)])) maddr $ \addr -> do | ||
404 | let mine = sameAddress laddr addr | ||
405 | names <- if mine then fmap (:[]) textHostName | ||
406 | else peerKeyToResolvedNames (PeerKey addr) | ||
407 | return (mine,map (\h' -> (n,h',r)) names) | ||
408 | |||
409 | |||
410 | addrTextToKey :: Text -> IO (Maybe ConnectionKey) | ||
411 | addrTextToKey h = do | ||
412 | maddr <- parseAddress (strip_brackets h) | ||
413 | return (fmap PeerKey maddr) | ||
414 | |||
415 | guardPortStrippedAddress :: Text -> SockAddr -> IO (Maybe ()) | ||
416 | guardPortStrippedAddress h laddr = do | ||
417 | maddr <- fmap (fmap (`withPort` 0)) $ parseAddress (strip_brackets h) | ||
418 | let laddr' = laddr `withPort` 0 | ||
419 | return $ maddr >>= guard . (==laddr') | ||
420 | |||
421 | |||
422 | -- | Accepts a textual representation of a domainname | ||
423 | -- JID suitable for client connections, and returns the | ||
424 | -- coresponding ipv6 address JID suitable for peers paired | ||
425 | -- with a SockAddr with the address part of that JID in | ||
426 | -- binary form. If no suitable address could be resolved | ||
427 | -- for the given name, Nothing is returned. | ||
428 | rewriteJIDForPeer :: Text -> IO (Maybe (Text,SockAddr)) | ||
429 | rewriteJIDForPeer jid = do | ||
430 | let (n,h,r) = splitJID jid | ||
431 | maddr <- fmap listToMaybe $ resolvePeer h | ||
432 | return $ flip fmap maddr $ \addr -> | ||
433 | let h' = addrToText addr | ||
434 | to' = unsplitJID (n,h',r) | ||
435 | in (to',addr) | ||
436 | |||
437 | deliverToConsole :: PresenceState -> IO () -> Stanza -> IO () | ||
438 | deliverToConsole state fail msg = do | ||
439 | putStrLn $ "TODO: deliver to console" | ||
440 | did1 <- writeActiveTTY (consoleWriter state) msg | ||
441 | did2 <- writeAllPty (consoleWriter state) msg | ||
442 | if not (did1 || did2) then fail else return () | ||
443 | |||
444 | -- | deliver <message/> or error stanza | ||
445 | deliverMessage :: PresenceState | ||
446 | -> IO () | ||
447 | -> StanzaWrap (LockedChan Event) | ||
448 | -> IO () | ||
449 | deliverMessage state fail msg = | ||
450 | case stanzaOrigin msg of | ||
451 | NetworkOrigin senderk@(ClientKey {}) _ -> do | ||
452 | -- Case 1. Client -> Peer | ||
453 | mto <- do | ||
454 | flip (maybe $ return Nothing) (stanzaTo msg) $ \to -> do | ||
455 | rewriteJIDForPeer to | ||
456 | flip (maybe fail {- reverse lookup failure -}) | ||
457 | mto | ||
458 | $ \(to',addr) -> do | ||
459 | let k = PeerKey addr | ||
460 | chans <- atomically $ readTVar (keyToChan state) | ||
461 | flip (maybe fail) (Map.lookup k chans) $ \(Conn { connChan=chan | ||
462 | , auxAddr=laddr }) -> do | ||
463 | (n,r) <- forClient state senderk (return (Nothing,Nothing)) | ||
464 | $ \c -> return (Just (clientUser c), Just (clientResource c)) | ||
465 | -- original 'from' address is discarded. | ||
466 | let from' = unsplitJID (n,addrToText laddr,r) | ||
467 | -- dup <- atomically $ cloneStanza (msg { stanzaTo=Just to', stanzaFrom=Just from' }) | ||
468 | let dup = (msg { stanzaTo=Just to', stanzaFrom=Just from' }) | ||
469 | sendModifiedStanzaToPeer dup chan | ||
470 | NetworkOrigin senderk@(PeerKey {}) _ -> do | ||
471 | key_to_chan <- atomically $ readTVar (keyToChan state) | ||
472 | flip (maybe fail) (Map.lookup senderk key_to_chan) | ||
473 | $ \(Conn { connChan=sender_chan | ||
474 | , auxAddr=laddr }) -> do | ||
475 | flip (maybe fail) (stanzaTo msg) $ \to -> do | ||
476 | (mine,(n,h,r)) <- rewriteJIDForClient laddr to [] | ||
477 | if not mine then fail else do | ||
478 | let to' = unsplitJID (n,h,r) | ||
479 | cmap <- atomically . readTVar $ clientsByUser state | ||
480 | (from',chans,ks) <- do | ||
481 | flip (maybe $ return (Nothing,[],[])) n $ \n -> do | ||
482 | buds <- configText ConfigFiles.getBuddies n | ||
483 | from' <- do | ||
484 | flip (maybe $ return Nothing) (stanzaFrom msg) $ \from -> do | ||
485 | (_,trip) <- rewriteJIDForClient laddr from buds | ||
486 | return . Just $ unsplitJID trip | ||
487 | let nope = return (from',[],[]) | ||
488 | flip (maybe nope) (Map.lookup n cmap) $ \presence_container -> do | ||
489 | let ks = Map.keys (networkClients presence_container) | ||
490 | chans = mapMaybe (flip Map.lookup key_to_chan) ks | ||
491 | return (from',chans,ks) | ||
492 | putStrLn $ "chan count: " ++ show (length chans) | ||
493 | let msg' = msg { stanzaTo=Just to' | ||
494 | , stanzaFrom=from' } | ||
495 | if null chans then deliverToConsole state fail msg' else do | ||
496 | forM_ chans $ \Conn { connChan=chan} -> do | ||
497 | putStrLn $ "sending "++show (stanzaId msg)++" to clients "++show ks | ||
498 | -- TODO: Cloning isn't really neccessary unless there are multiple | ||
499 | -- destinations and we should probably transition to minimal cloning, | ||
500 | -- or else we should distinguish between announcable stanzas and | ||
501 | -- consumable stanzas and announcables use write-only broadcast | ||
502 | -- channels that must be cloned in order to be consumed. | ||
503 | -- For now, we are doing redundant cloning. | ||
504 | dup <- cloneStanza msg' | ||
505 | sendModifiedStanzaToClient dup | ||
506 | chan | ||
507 | |||
508 | |||
509 | setClientFlag :: PresenceState -> ConnectionKey -> Int8 -> IO () | ||
510 | setClientFlag state k flag = | ||
511 | atomically $ do | ||
512 | cmap <- readTVar (clients state) | ||
513 | flip (maybe $ return ()) (Map.lookup k cmap) $ \client -> do | ||
514 | setClientFlag0 client flag | ||
515 | |||
516 | setClientFlag0 :: ClientState -> Int8 -> STM () | ||
517 | setClientFlag0 client flag = | ||
518 | modifyTVar' (clientFlags client) (\flgs -> flgs .|. flag) | ||
519 | |||
520 | informSentRoster :: PresenceState -> ConnectionKey -> IO () | ||
521 | informSentRoster state k = do | ||
522 | setClientFlag state k cf_interested | ||
523 | |||
524 | |||
525 | subscribedPeers :: Text -> IO [SockAddr] | ||
526 | subscribedPeers user = do | ||
527 | jids <- configText ConfigFiles.getSubscribers user | ||
528 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | ||
529 | fmap Map.keys $ resolveAllPeers hosts | ||
530 | |||
531 | -- | this JID is suitable for peers, not clients. | ||
532 | clientJID :: Conn -> ClientState -> Text | ||
533 | clientJID con client = unsplitJID ( Just $ clientUser client | ||
534 | , addrToText $ auxAddr con | ||
535 | , Just $ clientResource client) | ||
536 | |||
537 | -- | Send presence notification to subscribed peers. | ||
538 | -- Note that a full JID from address will be added to the | ||
539 | -- stanza if it is not present. | ||
540 | informClientPresence :: PresenceState | ||
541 | -> ConnectionKey -> StanzaWrap (LockedChan Event) -> IO () | ||
542 | informClientPresence state k stanza = do | ||
543 | forClient state k (return ()) $ \client -> do | ||
544 | informClientPresence0 state (Just k) client stanza | ||
545 | |||
546 | informClientPresence0 :: PresenceState | ||
547 | -> Maybe ConnectionKey | ||
548 | -> ClientState | ||
549 | -> StanzaWrap (LockedChan Event) | ||
550 | -> IO () | ||
551 | informClientPresence0 state mbk client stanza = do | ||
552 | dup <- cloneStanza stanza | ||
553 | atomically $ writeTVar (clientStatus client) $ Just dup | ||
554 | is_avail <- atomically $ clientIsAvailable client | ||
555 | when (not is_avail) $ do | ||
556 | atomically $ setClientFlag0 client cf_available | ||
557 | maybe (return ()) (sendCachedPresence state) mbk | ||
558 | addrs <- subscribedPeers (clientUser client) | ||
559 | ktc <- atomically $ readTVar (keyToChan state) | ||
560 | let connected = mapMaybe (flip Map.lookup ktc . PeerKey) addrs | ||
561 | forM_ connected $ \con -> do | ||
562 | let from' = clientJID con client | ||
563 | mto <- runTraversableT $ do | ||
564 | to <- liftT $ stanzaTo stanza | ||
565 | (to',_) <- liftMT $ rewriteJIDForPeer to | ||
566 | return to' | ||
567 | dup <- cloneStanza stanza | ||
568 | sendModifiedStanzaToPeer dup { stanzaFrom = Just from' | ||
569 | , stanzaTo = mto } | ||
570 | (connChan con) | ||
571 | |||
572 | informPeerPresence :: PresenceState | ||
573 | -> ConnectionKey | ||
574 | -> StanzaWrap (LockedChan Event) | ||
575 | -> IO () | ||
576 | informPeerPresence state k stanza = do | ||
577 | -- Presence must indicate full JID with resource... | ||
578 | putStrLn $ "xmppInformPeerPresence checking from address..." | ||
579 | flip (maybe $ return ()) (stanzaFrom stanza) $ \from -> do | ||
580 | let (muser,h,mresource) = splitJID from | ||
581 | putStrLn $ "xmppInformPeerPresence from = " ++ show from | ||
582 | -- flip (maybe $ return ()) mresource $ \resource -> do | ||
583 | flip (maybe $ return ()) muser $ \user -> do | ||
584 | |||
585 | clients <- atomically $ do | ||
586 | |||
587 | -- Update remotesByPeer... | ||
588 | rbp <- readTVar (remotesByPeer state) | ||
589 | let umap = maybe Map.empty id $ Map.lookup k rbp | ||
590 | rp = case (presenceShow $ stanzaType stanza) of | ||
591 | Offline -> | ||
592 | maybe Map.empty | ||
593 | (\resource -> | ||
594 | maybe (Map.empty) | ||
595 | (Map.delete resource . resources) | ||
596 | $ Map.lookup user umap) | ||
597 | mresource | ||
598 | |||
599 | _ ->maybe Map.empty | ||
600 | (\resource -> | ||
601 | maybe (Map.singleton resource stanza) | ||
602 | (Map.insert resource stanza . resources ) | ||
603 | $ Map.lookup user umap) | ||
604 | mresource | ||
605 | umap' = Map.insert user (RemotePresence rp) umap | ||
606 | |||
607 | flip (maybe $ return []) (case presenceShow $ stanzaType stanza of | ||
608 | Offline -> Just () | ||
609 | _ -> mresource >> Just ()) | ||
610 | $ \_ -> do | ||
611 | writeTVar (remotesByPeer state) $ Map.insert k umap' rbp | ||
612 | -- TODO: Store or delete the stanza (remotesByPeer) | ||
613 | |||
614 | -- all clients, we'll filter available/authorized later | ||
615 | |||
616 | ktc <- readTVar (keyToChan state) | ||
617 | runTraversableT $ do | ||
618 | (ck,client) <- liftMT $ fmap Map.toList $ readTVar (clients state) | ||
619 | con <- liftMaybe $ Map.lookup ck ktc | ||
620 | return (ck,con,client) | ||
621 | putStrLn $ "xmppInformPeerPresence (length clients="++show (length clients)++")" | ||
622 | forM_ clients $ \(ck,con,client) -> do | ||
623 | -- (TODO: appropriately authorized clients only.) | ||
624 | -- For now, all "available" clients (available = sent initial presence) | ||
625 | is_avail <- atomically $ clientIsAvailable client | ||
626 | when is_avail $ do | ||
627 | putStrLn $ "reversing for client: " ++ show from | ||
628 | froms <- do -- flip (maybe $ return [from]) k . const $ do | ||
629 | let ClientKey laddr = ck | ||
630 | (_,trip) <- multiplyJIDForClient laddr from | ||
631 | return (map unsplitJID trip) | ||
632 | |||
633 | putStrLn $ "sending to client: " ++ show (stanzaType stanza,froms) | ||
634 | forM_ froms $ \from' -> do | ||
635 | dup <- cloneStanza stanza | ||
636 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) | ||
637 | (connChan con) | ||
638 | |||
639 | answerProbe :: PresenceState | ||
640 | -> Maybe Text -> ConnectionKey -> TChan Stanza -> IO () | ||
641 | answerProbe state mto k chan = do | ||
642 | -- putStrLn $ "answerProbe! " ++ show (stanzaType stanza) | ||
643 | ktc <- atomically $ readTVar (keyToChan state) | ||
644 | muser <- runTraversableT $ do | ||
645 | to <- liftT $ mto | ||
646 | conn <- liftT $ Map.lookup k ktc | ||
647 | let (mu,h,_) = splitJID to -- TODO: currently resource-id is ignored on presence | ||
648 | -- probes. Is this correct? Check the spec. | ||
649 | liftMT $ guardPortStrippedAddress h (auxAddr conn) | ||
650 | u <- liftT mu | ||
651 | let ch = addrToText (auxAddr conn) | ||
652 | return (u,conn,ch) | ||
653 | |||
654 | flip (maybe $ return ()) muser $ \(u,conn,ch) -> do | ||
655 | |||
656 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u | ||
657 | let gaddrs = groupBy (\a b -> snd a == snd b) (sort resolved_subs) | ||
658 | whitelist = do | ||
659 | xs <- gaddrs | ||
660 | x <- take 1 xs | ||
661 | guard $ snd x==k | ||
662 | mapMaybe fst xs | ||
663 | |||
664 | -- -- only subscribed peers should get probe replies | ||
665 | -- addrs <- subscribedPeers u | ||
666 | |||
667 | -- TODO: notify remote peer that they are unsubscribed? | ||
668 | -- reply <- makeInformSubscription "jabber:server" to from False | ||
669 | when (not $ null whitelist) $ do | ||
670 | |||
671 | replies <- runTraversableT $ do | ||
672 | cbu <- lift . atomically $ readTVar (clientsByUser state) | ||
673 | let lpres = maybeToList $ Map.lookup u cbu | ||
674 | cw <- lift . atomically $ readTVar (cwClients $ consoleWriter state) | ||
675 | clientState <- liftT $ (lpres >>= Map.elems . networkClients) | ||
676 | ++ Map.elems cw | ||
677 | stanza <- liftIOMaybe $ atomically (readTVar (clientStatus clientState)) | ||
678 | stanza <- lift $ cloneStanza stanza | ||
679 | let jid = unsplitJID (Just $ clientUser clientState | ||
680 | , ch | ||
681 | ,Just $ clientResource clientState) | ||
682 | return stanza { stanzaFrom = Just jid | ||
683 | , stanzaType = (stanzaType stanza) | ||
684 | { presenceWhiteList = whitelist } | ||
685 | } | ||
686 | |||
687 | forM_ replies $ \reply -> do | ||
688 | sendModifiedStanzaToPeer reply chan | ||
689 | |||
690 | -- if no presence, send offline message | ||
691 | when (null replies) $ do | ||
692 | let jid = unsplitJID (Just u,ch,Nothing) | ||
693 | pstanza <- makePresenceStanza "jabber:server" (Just jid) Offline | ||
694 | atomically $ writeTChan (connChan conn) pstanza | ||
695 | |||
696 | sendCachedPresence :: PresenceState -> ConnectionKey -> IO () | ||
697 | sendCachedPresence state k = do | ||
698 | forClient state k (return ()) $ \client -> do | ||
699 | rbp <- atomically $ readTVar (remotesByPeer state) | ||
700 | jids <- configText ConfigFiles.getBuddies (clientUser client) | ||
701 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | ||
702 | addrs <- resolveAllPeers hosts | ||
703 | let onlines = rbp `Map.intersection` Map.mapKeys PeerKey addrs | ||
704 | ClientKey laddr = k | ||
705 | mcon <- atomically $ do ktc <- readTVar (keyToChan state) | ||
706 | return $ Map.lookup k ktc | ||
707 | flip (maybe $ return ()) mcon $ \con -> do | ||
708 | -- me <- textHostName | ||
709 | forM_ (Map.toList onlines) $ \(pk, umap) -> do | ||
710 | forM_ (Map.toList umap) $ \(user,rp) -> do | ||
711 | let h = peerKeyToText pk | ||
712 | forM_ (Map.toList $ resources rp) $ \(resource,stanza) -> do | ||
713 | let jid = unsplitJID (Just user,h,Just resource) | ||
714 | (mine,js) <- multiplyJIDForClient laddr jid | ||
715 | forM_ js $ \jid -> do | ||
716 | let from' = unsplitJID jid | ||
717 | dup <- cloneStanza stanza | ||
718 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) | ||
719 | (connChan con) | ||
720 | |||
721 | pending <- configText ConfigFiles.getPending (clientUser client) | ||
722 | hostname <- textHostName | ||
723 | forM_ pending $ \pending_jid -> do | ||
724 | let cjid = unsplitJID ( Just $ clientUser client | ||
725 | , hostname | ||
726 | , Nothing ) | ||
727 | ask <- presenceSolicitation pending_jid cjid | ||
728 | sendModifiedStanzaToClient ask (connChan con) | ||
729 | |||
730 | -- Note: relying on self peer connection to send | ||
731 | -- send local buddies. | ||
732 | return () | ||
733 | |||
734 | addToRosterFile :: (MonadPlus t, Traversable t) => | ||
735 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | ||
736 | -> Maybe L.ByteString | ||
737 | -> t1) | ||
738 | -> Text -> Text -> [SockAddr] -> t1 | ||
739 | addToRosterFile doit whose to addrs = | ||
740 | modifyRosterFile doit whose to addrs True | ||
741 | |||
742 | removeFromRosterFile :: (MonadPlus t, Traversable t) => | ||
743 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | ||
744 | -> Maybe L.ByteString | ||
745 | -> t1) | ||
746 | -> Text -> Text -> [SockAddr] -> t1 | ||
747 | removeFromRosterFile doit whose to addrs = | ||
748 | modifyRosterFile doit whose to addrs False | ||
749 | |||
750 | modifyRosterFile :: (Traversable t, MonadPlus t) => | ||
751 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | ||
752 | -> Maybe L.ByteString | ||
753 | -> t1) | ||
754 | -> Text -> Text -> [SockAddr] -> Bool -> t1 | ||
755 | modifyRosterFile doit whose to addrs bAdd = do | ||
756 | let (mu,_,_) = splitJID to | ||
757 | cmp jid = runTraversableT $ do | ||
758 | let (msu,stored_h,mr) = splitJID (lazyByteStringToText jid) | ||
759 | -- Delete from file if a resource is present in file | ||
760 | (\f -> maybe f (const mzero) mr) $ do | ||
761 | -- Delete from file if no user is present in file | ||
762 | flip (maybe mzero) msu $ \stored_u -> do | ||
763 | -- do not delete anything if no user was specified | ||
764 | flip (maybe $ return jid) mu $ \u -> do | ||
765 | -- do not delete if stored user is same as specified | ||
766 | if stored_u /= u then return jid else do | ||
767 | stored_addrs <- lift $ resolvePeer stored_h | ||
768 | -- do not delete if failed to resolve | ||
769 | if null stored_addrs then return jid else do | ||
770 | -- delete if specified address matches stored | ||
771 | if null (stored_addrs \\ addrs) then mzero else do | ||
772 | -- keep | ||
773 | return jid | ||
774 | doit (textToLazyByteString whose) | ||
775 | cmp | ||
776 | (guard bAdd >> Just (textToLazyByteString to)) | ||
777 | |||
778 | clientSubscriptionRequest :: PresenceState -> IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () | ||
779 | clientSubscriptionRequest state fail k stanza chan = do | ||
780 | forClient state k fail $ \client -> do | ||
781 | flip (maybe fail) (stanzaTo stanza) $ \to -> do | ||
782 | putStrLn $ "Forwarding solictation to peer" | ||
783 | let (mu,h,_) = splitJID to | ||
784 | to <- return $ unsplitJID (mu,h,Nothing) -- delete resource | ||
785 | flip (maybe fail) mu $ \u -> do | ||
786 | addrs <- resolvePeer h | ||
787 | if null addrs then fail else do | ||
788 | -- add to-address to from's solicited | ||
789 | addToRosterFile ConfigFiles.modifySolicited (clientUser client) to addrs | ||
790 | removeFromRosterFile ConfigFiles.modifyBuddies (clientUser client) to addrs | ||
791 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers (clientUser client) | ||
792 | let is_subscribed = not . null $ intersect (map ((mu,).PeerKey) addrs) resolved_subs | ||
793 | -- subscribers: "from" | ||
794 | -- buddies: "to" | ||
795 | |||
796 | (ktc,ap) <- atomically $ | ||
797 | liftM2 (,) (readTVar $ keyToChan state) | ||
798 | (readTVar $ associatedPeers state) | ||
799 | |||
800 | case stanzaType stanza of | ||
801 | PresenceRequestSubscription True -> do | ||
802 | hostname <- textHostName | ||
803 | let cjid = unsplitJID (Just $ clientUser client, hostname,Nothing) | ||
804 | chans <- clientCons state ktc (clientUser client) | ||
805 | forM_ chans $ \( Conn { connChan=chan }, client ) -> do | ||
806 | -- roster update ask="subscribe" | ||
807 | update <- makeRosterUpdate cjid to | ||
808 | [ ("ask","subscribe") | ||
809 | , if is_subscribed then ("subscription","from") | ||
810 | else ("subscription","none") | ||
811 | ] | ||
812 | sendModifiedStanzaToClient update chan | ||
813 | _ -> return () | ||
814 | |||
815 | let dsts = Map.fromList $ map ((,()) . PeerKey) addrs | ||
816 | cdsts = ktc `Map.intersection` dsts | ||
817 | forM_ (Map.toList cdsts) $ \(pk,con) -> do | ||
818 | -- if already connected, send solicitation ... | ||
819 | -- let from = clientJID con client | ||
820 | let from = unsplitJID ( Just $ clientUser client | ||
821 | , addrToText $ auxAddr con | ||
822 | , Nothing ) | ||
823 | mb <- rewriteJIDForPeer to | ||
824 | flip (maybe $ return ()) mb $ \(to',addr) -> do | ||
825 | dup <- cloneStanza stanza | ||
826 | sendModifiedStanzaToPeer (dup { stanzaTo = Just to' | ||
827 | , stanzaFrom = Just from }) | ||
828 | (connChan con) | ||
829 | let addrm = Map.fromList (map (,()) addrs) | ||
830 | when (not . Map.null $ addrm Map.\\ ap) $ do | ||
831 | -- Add peer if we are not already associated ... | ||
832 | sv <- atomically $ takeTMVar $ server state | ||
833 | addPeer sv (head addrs) | ||
834 | atomically $ putTMVar (server state) sv | ||
835 | |||
836 | |||
837 | resolvedFromRoster | ||
838 | :: (L.ByteString -> IO [L.ByteString]) | ||
839 | -> UserName -> IO [(Maybe UserName, ConnectionKey)] | ||
840 | resolvedFromRoster doit u = do | ||
841 | subs <- configText doit u | ||
842 | runTraversableT $ do | ||
843 | (mu,h,_) <- liftT $ splitJID `fmap` subs | ||
844 | addr <- liftMT $ fmap nub $ resolvePeer h | ||
845 | return (mu,PeerKey addr) | ||
846 | |||
847 | clientCons :: PresenceState | ||
848 | -> Map ConnectionKey t -> Text -> IO [(t, ClientState)] | ||
849 | clientCons state ktc u = do | ||
850 | mlp <- atomically $ do | ||
851 | cmap <- readTVar $ clientsByUser state | ||
852 | return $ Map.lookup u cmap | ||
853 | let ks = do lp <- maybeToList mlp | ||
854 | Map.toList (networkClients lp) | ||
855 | doit (k,client) = do | ||
856 | con <- Map.lookup k ktc | ||
857 | return (con,client) | ||
858 | return $ mapMaybe doit ks | ||
859 | |||
860 | peerSubscriptionRequest :: PresenceState -> IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () | ||
861 | peerSubscriptionRequest state fail k stanza chan = do | ||
862 | putStrLn $ "Handling pending subscription from remote" | ||
863 | flip (maybe fail) (stanzaFrom stanza) $ \from -> do | ||
864 | flip (maybe fail) (stanzaTo stanza) $ \to -> do | ||
865 | let (mto_u,h,_) = splitJID to | ||
866 | (mfrom_u,from_h,_) = splitJID from | ||
867 | to <- return $ unsplitJID (mto_u,h,Nothing) -- delete resource | ||
868 | from <- return $ unsplitJID (mfrom_u,from_h,Nothing) -- delete resource | ||
869 | ktc <- atomically . readTVar $ keyToChan state | ||
870 | flip (maybe fail) (Map.lookup k ktc) | ||
871 | $ \Conn { auxAddr=laddr } -> do | ||
872 | (mine,totup) <- rewriteJIDForClient laddr to [] | ||
873 | if not mine then fail else do | ||
874 | (_,fromtup) <- rewriteJIDForClient laddr from [] | ||
875 | flip (maybe fail) mto_u $ \u -> do | ||
876 | flip (maybe fail) mfrom_u $ \from_u -> do | ||
877 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u | ||
878 | let already_subscribed = elem (mfrom_u,k) resolved_subs | ||
879 | is_wanted = case stanzaType stanza of | ||
880 | PresenceRequestSubscription b -> b | ||
881 | _ -> False -- Shouldn't happen. | ||
882 | -- Section 8 says (for presence of type "subscribe", the server MUST | ||
883 | -- adhere to the rules defined under Section 3 and summarized under | ||
884 | -- see Appendix A. (pariticularly Appendex A.3.1) | ||
885 | if already_subscribed == is_wanted | ||
886 | then do | ||
887 | -- contact ∈ subscribers --> SHOULD NOT, already handled | ||
888 | -- already subscribed, reply and quit | ||
889 | -- (note: swapping to and from for reply) | ||
890 | reply <- makeInformSubscription "jabber:server" to from is_wanted | ||
891 | sendModifiedStanzaToPeer reply chan | ||
892 | answerProbe state (Just to) k chan | ||
893 | else do | ||
894 | |||
895 | -- TODO: if peer-connection is to self, then auto-approve local user. | ||
896 | |||
897 | -- add from-address to to's pending | ||
898 | addrs <- resolvePeer from_h | ||
899 | |||
900 | -- Catch exception in case the user does not exist | ||
901 | if null addrs then fail else do | ||
902 | |||
903 | let from' = unsplitJID fromtup | ||
904 | |||
905 | already_pending <- | ||
906 | if is_wanted then | ||
907 | addToRosterFile ConfigFiles.modifyPending u from' addrs | ||
908 | else do | ||
909 | removeFromRosterFile ConfigFiles.modifySubscribers u from' addrs | ||
910 | reply <- makeInformSubscription "jabber:server" to from is_wanted | ||
911 | sendModifiedStanzaToPeer reply chan | ||
912 | return False | ||
913 | |||
914 | -- contact ∉ subscribers & contact ∈ pending --> SHOULD NOT | ||
915 | when (not already_pending) $ do | ||
916 | -- contact ∉ subscribers & contact ∉ pending --> MUST | ||
917 | |||
918 | chans <- clientCons state ktc u | ||
919 | forM_ chans $ \( Conn { connChan=chan }, client ) -> do | ||
920 | -- send to clients | ||
921 | -- TODO: interested/available clients only? | ||
922 | dup <- cloneStanza stanza | ||
923 | sendModifiedStanzaToClient dup { stanzaFrom = Just $ from' | ||
924 | , stanzaTo = Just $ unsplitJID totup } | ||
925 | chan | ||
926 | |||
927 | |||
928 | clientInformSubscription :: PresenceState | ||
929 | -> IO () | ||
930 | -> ConnectionKey | ||
931 | -> StanzaWrap (LockedChan Event) | ||
932 | -> IO () | ||
933 | clientInformSubscription state fail k stanza = do | ||
934 | forClient state k fail $ \client -> do | ||
935 | flip (maybe fail) (stanzaTo stanza) $ \to -> do | ||
936 | putStrLn $ "clientInformSubscription" | ||
937 | let (mu,h,mr) = splitJID to | ||
938 | addrs <- resolvePeer h | ||
939 | -- remove from pending | ||
940 | buds <- resolvedFromRoster ConfigFiles.getBuddies (clientUser client) | ||
941 | let is_buddy = not . null $ map ((mu,) . PeerKey) addrs `intersect` buds | ||
942 | removeFromRosterFile ConfigFiles.modifyPending (clientUser client) to addrs | ||
943 | let (relationship,addf,remf) = | ||
944 | case stanzaType stanza of | ||
945 | PresenceInformSubscription True -> | ||
946 | ( ("subscription", if is_buddy then "both" | ||
947 | else "from" ) | ||
948 | , ConfigFiles.modifySubscribers | ||
949 | , ConfigFiles.modifyOthers ) | ||
950 | _ -> ( ("subscription", if is_buddy then "to" | ||
951 | else "none" ) | ||
952 | , ConfigFiles.modifyOthers | ||
953 | , ConfigFiles.modifySubscribers ) | ||
954 | addToRosterFile addf (clientUser client) to addrs | ||
955 | removeFromRosterFile remf (clientUser client) to addrs | ||
956 | |||
957 | do | ||
958 | cbu <- atomically $ readTVar (clientsByUser state) | ||
959 | putStrLn $ "cbu = " ++ show (fmap (fmap clientPid . networkClients) cbu) | ||
960 | |||
961 | -- send roster update to clients | ||
962 | (clients,ktc) <- atomically $ do | ||
963 | cbu <- readTVar (clientsByUser state) | ||
964 | let mlp = Map.lookup (clientUser client) cbu | ||
965 | let cs = maybe [] (Map.toList . networkClients) mlp | ||
966 | ktc <- readTVar (keyToChan state) | ||
967 | return (cs,ktc) | ||
968 | forM_ clients $ \(ck, client) -> do | ||
969 | is_intereseted <- atomically $ clientIsInterested client | ||
970 | putStrLn $ "clientIsInterested: "++show is_intereseted | ||
971 | is_intereseted <- atomically $ clientIsInterested client | ||
972 | when is_intereseted $ do | ||
973 | flip (maybe $ return ()) (Map.lookup ck ktc) $ \con -> do | ||
974 | hostname <- textHostName | ||
975 | -- TODO: Should cjid include the resource? | ||
976 | let cjid = unsplitJID (mu, hostname, Nothing) | ||
977 | update <- makeRosterUpdate cjid to [relationship] | ||
978 | sendModifiedStanzaToClient update (connChan con) | ||
979 | |||
980 | -- notify peer | ||
981 | let dsts = Map.fromList $ map ((,()) . PeerKey) addrs | ||
982 | cdsts = ktc `Map.intersection` dsts | ||
983 | forM_ (Map.toList cdsts) $ \(pk,con) -> do | ||
984 | let from = clientJID con client | ||
985 | to' = unsplitJID (mu, peerKeyToText pk, Nothing) | ||
986 | dup <- cloneStanza stanza | ||
987 | sendModifiedStanzaToPeer (dup { stanzaTo = Just $ to' | ||
988 | , stanzaFrom = Just from }) | ||
989 | (connChan con) | ||
990 | answerProbe state (Just from) pk (connChan con) | ||
991 | |||
992 | peerInformSubscription :: PresenceState | ||
993 | -> IO () | ||
994 | -> ConnectionKey | ||
995 | -> StanzaWrap (LockedChan Event) | ||
996 | -> IO () | ||
997 | peerInformSubscription state fail k stanza = do | ||
998 | putStrLn $ "TODO: peerInformSubscription" | ||
999 | -- remove from solicited | ||
1000 | flip (maybe fail) (stanzaFrom stanza) $ \from -> do | ||
1001 | ktc <- atomically $ readTVar (keyToChan state) | ||
1002 | flip (maybe fail) (Map.lookup k ktc) | ||
1003 | $ \(Conn { connChan=sender_chan | ||
1004 | , auxAddr=laddr }) -> do | ||
1005 | (_,(from_u,from_h,_)) <- rewriteJIDForClient laddr from [] | ||
1006 | let from'' = unsplitJID (from_u,from_h,Nothing) | ||
1007 | muser = do | ||
1008 | to <- stanzaTo stanza | ||
1009 | let (mu,to_h,to_r) = splitJID to | ||
1010 | mu | ||
1011 | -- TODO muser = Nothing when wanted=False | ||
1012 | -- should probably mean unsubscribed for all users. | ||
1013 | -- This would allow us to answer anonymous probes with 'unsubscribed'. | ||
1014 | flip (maybe fail) muser $ \user -> do | ||
1015 | addrs <- resolvePeer from_h | ||
1016 | was_solicited <- removeFromRosterFile ConfigFiles.modifySolicited user from'' addrs | ||
1017 | subs <- resolvedFromRoster ConfigFiles.getSubscribers user | ||
1018 | let is_sub = not . null $ map ((from_u,) . PeerKey) addrs `intersect` subs | ||
1019 | let (relationship,addf,remf) = | ||
1020 | case stanzaType stanza of | ||
1021 | PresenceInformSubscription True -> | ||
1022 | ( ("subscription", if is_sub then "both" | ||
1023 | else "to" ) | ||
1024 | , ConfigFiles.modifyBuddies | ||
1025 | , ConfigFiles.modifyOthers ) | ||
1026 | _ -> ( ("subscription", if is_sub then "from" | ||
1027 | else "none") | ||
1028 | , ConfigFiles.modifyOthers | ||
1029 | , ConfigFiles.modifyBuddies ) | ||
1030 | addToRosterFile addf user from'' addrs | ||
1031 | removeFromRosterFile remf user from'' addrs | ||
1032 | |||
1033 | hostname <- textHostName | ||
1034 | let to' = unsplitJID (Just user, hostname, Nothing) | ||
1035 | chans <- clientCons state ktc user | ||
1036 | forM_ chans $ \(Conn { connChan=chan }, client) -> do | ||
1037 | update <- makeRosterUpdate to' from'' [relationship] | ||
1038 | is_intereseted <- atomically $ clientIsInterested client | ||
1039 | when is_intereseted $ do | ||
1040 | sendModifiedStanzaToClient update chan | ||
1041 | -- TODO: interested/availabe clients only? | ||
1042 | dup <- cloneStanza stanza | ||
1043 | sendModifiedStanzaToClient dup { stanzaFrom = Just $ from'' | ||
1044 | , stanzaTo = Just to' } | ||
1045 | chan | ||
diff --git a/Presence/Util.hs b/Presence/Util.hs new file mode 100644 index 00000000..8d9a9494 --- /dev/null +++ b/Presence/Util.hs | |||
@@ -0,0 +1,59 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | module Util where | ||
3 | |||
4 | import qualified Data.ByteString.Lazy as L | ||
5 | import Data.Monoid | ||
6 | import qualified Data.Text as Text | ||
7 | ;import Data.Text (Text) | ||
8 | import qualified Data.Text.Encoding as Text | ||
9 | import qualified Network.BSD as BSD | ||
10 | import Network.Socket | ||
11 | |||
12 | import Network.Address (setPort) | ||
13 | |||
14 | type UserName = Text | ||
15 | type ResourceName = Text | ||
16 | |||
17 | |||
18 | unsplitJID :: (Maybe UserName,Text,Maybe ResourceName) -> Text | ||
19 | unsplitJID (n,h,r) = username <> h <> resource | ||
20 | where | ||
21 | username = maybe "" (<>"@") n | ||
22 | resource = maybe "" ("/"<>) r | ||
23 | |||
24 | splitJID :: Text -> (Maybe UserName,Text,Maybe ResourceName) | ||
25 | splitJID bjid = | ||
26 | let xs = splitAll '@' bjid | ||
27 | ys = splitAll '/' (last xs) | ||
28 | splitAll c bjid = take 1 xs0 ++ map (Text.drop 1) (drop 1 xs0) | ||
29 | where xs0 = Text.groupBy (\x y-> y/=c) bjid | ||
30 | server = head ys | ||
31 | name = case xs of | ||
32 | (n:s:_) -> Just n | ||
33 | (s:_) -> Nothing | ||
34 | rsrc = case ys of | ||
35 | (s:_:_) -> Just $ last ys | ||
36 | _ -> Nothing | ||
37 | in (name,server,rsrc) | ||
38 | |||
39 | |||
40 | textHostName :: IO Text | ||
41 | textHostName = fmap Text.pack BSD.getHostName | ||
42 | |||
43 | textToLazyByteString :: Text -> L.ByteString | ||
44 | textToLazyByteString s = L.fromChunks [Text.encodeUtf8 s] | ||
45 | |||
46 | lazyByteStringToText :: L.ByteString -> Text | ||
47 | lazyByteStringToText = (foldr1 (<>) . map Text.decodeUtf8 . L.toChunks) | ||
48 | |||
49 | -- | for example: 2001-db8-85a3-8d3-1319-8a2e-370-7348.ipv6-literal.net | ||
50 | ip6literal :: Text -> Text | ||
51 | ip6literal addr = Text.map dash addr <> ".ipv6-literal.net" | ||
52 | where | ||
53 | dash ':' = '-' | ||
54 | dash x = x | ||
55 | |||
56 | sameAddress :: SockAddr -> SockAddr -> Bool | ||
57 | sameAddress laddr addr = setPort 0 laddr == setPort 0 addr | ||
58 | |||
59 | |||