diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/ConnectionKey.hs | 3 | ||||
-rw-r--r-- | Presence/Presence.hs | 258 | ||||
-rw-r--r-- | Presence/XMPPServer.hs | 147 |
3 files changed, 209 insertions, 199 deletions
diff --git a/Presence/ConnectionKey.hs b/Presence/ConnectionKey.hs index f0180455..ad4eeab7 100644 --- a/Presence/ConnectionKey.hs +++ b/Presence/ConnectionKey.hs | |||
@@ -3,9 +3,6 @@ module ConnectionKey where | |||
3 | import Network.Socket ( SockAddr(..) ) | 3 | import Network.Socket ( SockAddr(..) ) |
4 | import SockAddr () | 4 | import SockAddr () |
5 | 5 | ||
6 | newtype PeerAddress = PeerAddress SockAddr | ||
7 | deriving (Eq,Ord,Show) | ||
8 | |||
9 | newtype ClientAddress = ClientAddress SockAddr | 6 | newtype ClientAddress = ClientAddress SockAddr |
10 | deriving (Eq,Ord,Show) | 7 | deriving (Eq,Ord,Show) |
11 | 8 | ||
diff --git a/Presence/Presence.hs b/Presence/Presence.hs index fad87aeb..98d701e9 100644 --- a/Presence/Presence.hs +++ b/Presence/Presence.hs | |||
@@ -39,17 +39,18 @@ import Control.Applicative | |||
39 | import Crypto.PubKey.Curve25519 (SecretKey,toPublic) | 39 | import Crypto.PubKey.Curve25519 (SecretKey,toPublic) |
40 | 40 | ||
41 | import ControlMaybe | 41 | import ControlMaybe |
42 | import DNSCache (parseAddress, strip_brackets, withPort) | ||
42 | import LockedChan (LockedChan) | 43 | import LockedChan (LockedChan) |
43 | import Text.Read (readMaybe) | 44 | import Text.Read (readMaybe) |
44 | import TraversableT | 45 | import TraversableT |
45 | import UTmp (ProcessID,users) | 46 | import UTmp (ProcessID,users) |
46 | import LocalPeerCred | 47 | import LocalPeerCred |
47 | import XMPPServer | 48 | import XMPPServer |
48 | import PeerResolve | ||
49 | import ConsoleWriter | 49 | import ConsoleWriter |
50 | import ClientState | 50 | import ClientState |
51 | import Util | 51 | import Util |
52 | import qualified Connection | 52 | import qualified Connection |
53 | ;import Connection (PeerAddress (..), resolvePeer, reverseAddress) | ||
53 | import Network.Tox.NodeId (key2id,parseNoSpamId,nospam64,NoSpamId(..),ToxProgress,ToxContact(..)) | 54 | import Network.Tox.NodeId (key2id,parseNoSpamId,nospam64,NoSpamId(..),ToxProgress,ToxContact(..)) |
54 | import Crypto.Tox (decodeSecret) | 55 | import Crypto.Tox (decodeSecret) |
55 | import DPut | 56 | import DPut |
@@ -88,13 +89,16 @@ data ToxManager k = ToxManager | |||
88 | , resolveToxPeer :: Text -> Text -> IO (Maybe PeerAddress) | 89 | , resolveToxPeer :: Text -> Text -> IO (Maybe PeerAddress) |
89 | } | 90 | } |
90 | 91 | ||
91 | data PresenceState = forall status. PresenceState | 92 | type ClientProfile = Text |
93 | |||
94 | data PresenceState status = PresenceState | ||
92 | { clients :: TVar (Map ClientAddress ClientState) | 95 | { clients :: TVar (Map ClientAddress ClientState) |
93 | , clientsByUser :: TVar (Map Text LocalPresence) | 96 | , clientsByUser :: TVar (Map Text LocalPresence) |
94 | , clientsByProfile :: TVar (Map Text LocalPresence) | 97 | , clientsByProfile :: TVar (Map Text LocalPresence) |
95 | , remotesByPeer :: TVar (Map PeerAddress | 98 | , remotesByPeer :: TVar (Map PeerAddress |
96 | (Map UserName RemotePresence)) | 99 | (Map UserName RemotePresence)) |
97 | , server :: TMVar (XMPPServer, Connection.Manager status Text) | 100 | , server :: XMPPServer |
101 | , manager :: ClientProfile -> Connection.Manager status Text | ||
98 | , ckeyToChan :: TVar (Map ClientAddress Conn) | 102 | , ckeyToChan :: TVar (Map ClientAddress Conn) |
99 | , pkeyToChan :: TVar (Map PeerAddress Conn) | 103 | , pkeyToChan :: TVar (Map PeerAddress Conn) |
100 | , consoleWriter :: Maybe ConsoleWriter | 104 | , consoleWriter :: Maybe ConsoleWriter |
@@ -103,10 +107,11 @@ data PresenceState = forall status. PresenceState | |||
103 | 107 | ||
104 | 108 | ||
105 | newPresenceState :: Maybe ConsoleWriter | 109 | newPresenceState :: Maybe ConsoleWriter |
106 | -> Maybe (PresenceState -> ToxManager ClientAddress) | 110 | -> Maybe (PresenceState status -> ToxManager ClientAddress) |
107 | -> TMVar (XMPPServer, Connection.Manager status Text) | 111 | -> XMPPServer |
108 | -> IO PresenceState | 112 | -> (ClientProfile -> Connection.Manager status Text) |
109 | newPresenceState cw toxman xmpp = atomically $ do | 113 | -> IO (PresenceState status) |
114 | newPresenceState cw toxman sv man = atomically $ do | ||
110 | clients <- newTVar Map.empty | 115 | clients <- newTVar Map.empty |
111 | clientsByUser <- newTVar Map.empty | 116 | clientsByUser <- newTVar Map.empty |
112 | clientsByProfile <- newTVar Map.empty | 117 | clientsByProfile <- newTVar Map.empty |
@@ -120,14 +125,15 @@ newPresenceState cw toxman xmpp = atomically $ do | |||
120 | , remotesByPeer = remotesByPeer | 125 | , remotesByPeer = remotesByPeer |
121 | , ckeyToChan = ckeyToChan | 126 | , ckeyToChan = ckeyToChan |
122 | , pkeyToChan = pkeyToChan | 127 | , pkeyToChan = pkeyToChan |
123 | , server = xmpp | 128 | , server = sv |
129 | , manager = man | ||
124 | , consoleWriter = cw | 130 | , consoleWriter = cw |
125 | , toxManager = Nothing | 131 | , toxManager = Nothing |
126 | } | 132 | } |
127 | return $ st { toxManager = fmap ($ st) toxman } | 133 | return $ st { toxManager = fmap ($ st) toxman } |
128 | 134 | ||
129 | 135 | ||
130 | nameForClient :: PresenceState -> ClientAddress -> IO Text | 136 | nameForClient :: PresenceState stat -> ClientAddress -> IO Text |
131 | nameForClient state k = do | 137 | nameForClient state k = do |
132 | mc <- atomically $ do | 138 | mc <- atomically $ do |
133 | cmap <- readTVar (clients state) | 139 | cmap <- readTVar (clients state) |
@@ -138,7 +144,7 @@ nameForClient state k = do | |||
138 | "." -> textHostName | 144 | "." -> textHostName |
139 | profile -> return profile | 145 | profile -> return profile |
140 | 146 | ||
141 | presenceHooks :: PresenceState -> Int -> Maybe SockAddr -- ^ client-to-server bind address | 147 | presenceHooks :: PresenceState stat -> Int -> Maybe SockAddr -- ^ client-to-server bind address |
142 | -> Maybe SockAddr -- ^ server-to-server bind address | 148 | -> Maybe SockAddr -- ^ server-to-server bind address |
143 | -> XMPPServerParameters | 149 | -> XMPPServerParameters |
144 | presenceHooks state verbosity mclient mpeer = XMPPServerParameters | 150 | presenceHooks state verbosity mclient mpeer = XMPPServerParameters |
@@ -204,7 +210,7 @@ pcIsEmpty pc = Map.null (networkClients pc) | |||
204 | 210 | ||
205 | 211 | ||
206 | 212 | ||
207 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] | 213 | getConsolePids :: PresenceState stat -> IO [(Text,ProcessID)] |
208 | getConsolePids state = do | 214 | getConsolePids state = do |
209 | us <- UTmp.users | 215 | us <- UTmp.users |
210 | return $ map (\(_,tty,pid)->(lazyByteStringToText tty,pid)) us | 216 | return $ map (\(_,tty,pid)->(lazyByteStringToText tty,pid)) us |
@@ -218,7 +224,7 @@ identifyTTY' ttypids uid inode = ttypid | |||
218 | ttypid = fmap textify $ identifyTTY ttypids' uid inode | 224 | ttypid = fmap textify $ identifyTTY ttypids' uid inode |
219 | textify (tty,pid) = (fmap lazyByteStringToText tty, pid) | 225 | textify (tty,pid) = (fmap lazyByteStringToText tty, pid) |
220 | 226 | ||
221 | chooseResourceName :: PresenceState | 227 | chooseResourceName :: PresenceState stat |
222 | -> ClientAddress -> Remote SockAddr -> Maybe Text -> Maybe Text -> IO Text | 228 | -> ClientAddress -> Remote SockAddr -> Maybe Text -> Maybe Text -> IO Text |
223 | chooseResourceName state k (Remote addr) clientsNameForMe desired = do | 229 | chooseResourceName state k (Remote addr) clientsNameForMe desired = do |
224 | muid <- getLocalPeerCred' addr | 230 | muid <- getLocalPeerCred' addr |
@@ -267,7 +273,7 @@ chooseResourceName state k (Remote addr) clientsNameForMe desired = do | |||
267 | buds <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) | 273 | buds <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
268 | forM_ buds $ \bud -> do | 274 | forM_ buds $ \bud -> do |
269 | let (_,h,_) = splitJID bud | 275 | let (_,h,_) = splitJID bud |
270 | forkIO $ void $ resolvePeer h | 276 | forkIO $ void $ resolvePeer (manager state $ clientProfile client) h |
271 | 277 | ||
272 | atomically $ do | 278 | atomically $ do |
273 | modifyTVar' (clients state) $ Map.insert k client | 279 | modifyTVar' (clients state) $ Map.insert k client |
@@ -304,14 +310,14 @@ chooseResourceName state k (Remote addr) clientsNameForMe desired = do | |||
304 | -- Perform action with 'ClientState' associated with the given 'ClientAddress'. | 310 | -- Perform action with 'ClientState' associated with the given 'ClientAddress'. |
305 | -- If there is no associated 'ClientState', then perform the supplied fallback | 311 | -- If there is no associated 'ClientState', then perform the supplied fallback |
306 | -- action. | 312 | -- action. |
307 | forClient :: PresenceState -> ClientAddress -> IO b -> (ClientState -> IO b) -> IO b | 313 | forClient :: PresenceState stat -> ClientAddress -> IO b -> (ClientState -> IO b) -> IO b |
308 | forClient state k fallback f = do | 314 | forClient state k fallback f = do |
309 | mclient <- atomically $ do | 315 | mclient <- atomically $ do |
310 | cs <- readTVar (clients state) | 316 | cs <- readTVar (clients state) |
311 | return $ Map.lookup k cs | 317 | return $ Map.lookup k cs |
312 | maybe fallback f mclient | 318 | maybe fallback f mclient |
313 | 319 | ||
314 | tellClientHisName :: PresenceState -> ClientAddress -> IO Text | 320 | tellClientHisName :: PresenceState stat -> ClientAddress -> IO Text |
315 | tellClientHisName state k = forClient state k fallback go | 321 | tellClientHisName state k = forClient state k fallback go |
316 | where | 322 | where |
317 | fallback = localJID "nobody" "." "fallback" | 323 | fallback = localJID "nobody" "." "fallback" |
@@ -320,22 +326,22 @@ tellClientHisName state k = forClient state k fallback go | |||
320 | toMapUnit :: Ord k => [k] -> Map k () | 326 | toMapUnit :: Ord k => [k] -> Map k () |
321 | toMapUnit xs = Map.fromList $ map (,()) xs | 327 | toMapUnit xs = Map.fromList $ map (,()) xs |
322 | 328 | ||
323 | resolveAllPeers :: [Text] -> IO (Map PeerAddress ()) | 329 | resolveAllPeers :: Connection.Manager stat Text -> [Text] -> IO (Map PeerAddress ()) |
324 | resolveAllPeers hosts = fmap (toMapUnit . concat) $ Prelude.mapM (fmap (take 1) . resolvePeer) hosts | 330 | resolveAllPeers man hosts = fmap (toMapUnit . concat) $ Prelude.mapM (fmap (take 1) . resolvePeer man) hosts |
325 | 331 | ||
326 | 332 | ||
327 | -- Read a roster file and start trying to connect to all relevent peers. | 333 | -- Read a roster file and start trying to connect to all relevent peers. |
328 | rosterGetStuff | 334 | rosterGetStuff |
329 | :: (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) | 335 | :: (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) |
330 | -> PresenceState -> ClientAddress -> IO [Text] | 336 | -> PresenceState stat -> ClientAddress -> IO [Text] |
331 | rosterGetStuff what state k = forClient state k (return []) | 337 | rosterGetStuff what state k = forClient state k (return []) |
332 | $ \client -> do | 338 | $ \client -> do |
333 | jids0 <- configText what (clientUser client) (clientProfile client) | 339 | jids0 <- configText what (clientUser client) (clientProfile client) |
334 | let jids = map splitJID jids0 | 340 | let jids = map splitJID jids0 |
335 | -- Using case to bring 'status' type variable to Connection.Manager into scope. | 341 | -- Using case to bring 'status' type variable to Connection.Manager into scope. |
336 | case state of | 342 | case state of |
337 | PresenceState { server = svVar } -> do | 343 | PresenceState { server = sv } -> do |
338 | (sv,conns) <- atomically $ takeTMVar svVar | 344 | let conns = manager state $ clientProfile client |
339 | -- Grok peers to associate with from the roster: | 345 | -- Grok peers to associate with from the roster: |
340 | let isTox = do (me , ".tox") <- Just $ Text.splitAt 43 (clientProfile client) | 346 | let isTox = do (me , ".tox") <- Just $ Text.splitAt 43 (clientProfile client) |
341 | return me | 347 | return me |
@@ -353,23 +359,22 @@ rosterGetStuff what state k = forClient state k (return []) | |||
353 | meid <- readMaybe $ Text.unpack $ Text.take 43 (clientProfile client) | 359 | meid <- readMaybe $ Text.unpack $ Text.take 43 (clientProfile client) |
354 | themid <- readMaybe $ Text.unpack them | 360 | themid <- readMaybe $ Text.unpack them |
355 | return $ Connection.setPolicy (toxConnections toxman) | 361 | return $ Connection.setPolicy (toxConnections toxman) |
356 | (ToxContact meid themid) | 362 | (ToxContact meid themid) |
357 | policySetter Connection.TryingToConnect | 363 | policySetter Connection.TryingToConnect |
358 | atomically $ putTMVar svVar (sv,conns) | ||
359 | return $ fromMaybe jids0 $ do isTox | 364 | return $ fromMaybe jids0 $ do isTox |
360 | Just $ map noToxUsers jids | 365 | Just $ map noToxUsers jids |
361 | 366 | ||
362 | rosterGetBuddies :: PresenceState -> ClientAddress -> IO [Text] | 367 | rosterGetBuddies :: PresenceState stat -> ClientAddress -> IO [Text] |
363 | rosterGetBuddies state k = rosterGetStuff ConfigFiles.getBuddies state k | 368 | rosterGetBuddies state k = rosterGetStuff ConfigFiles.getBuddies state k |
364 | 369 | ||
365 | rosterGetSolicited :: PresenceState -> ClientAddress -> IO [Text] | 370 | rosterGetSolicited :: PresenceState stat -> ClientAddress -> IO [Text] |
366 | rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited | 371 | rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited |
367 | 372 | ||
368 | -- XXX: Should we be connecting to these peers? | 373 | -- XXX: Should we be connecting to these peers? |
369 | rosterGetOthers :: PresenceState -> ClientAddress -> IO [Text] | 374 | rosterGetOthers :: PresenceState stat -> ClientAddress -> IO [Text] |
370 | rosterGetOthers = rosterGetStuff ConfigFiles.getOthers | 375 | rosterGetOthers = rosterGetStuff ConfigFiles.getOthers |
371 | 376 | ||
372 | rosterGetSubscribers :: PresenceState -> ClientAddress -> IO [Text] | 377 | rosterGetSubscribers :: PresenceState stat -> ClientAddress -> IO [Text] |
373 | rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers | 378 | rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers |
374 | 379 | ||
375 | data Conn = Conn { connChan :: TChan Stanza | 380 | data Conn = Conn { connChan :: TChan Stanza |
@@ -404,7 +409,7 @@ getSolicited' = configText ConfigFiles.getSolicited | |||
404 | -- | 409 | -- |
405 | -- * Text - Hostname as it appears in roster. | 410 | -- * Text - Hostname as it appears in roster. |
406 | -- | 411 | -- |
407 | getBuddiesAndSolicited :: PresenceState | 412 | getBuddiesAndSolicited :: PresenceState stat |
408 | -> Text -- ^ Config profile: "." or tox host. | 413 | -> Text -- ^ Config profile: "." or tox host. |
409 | -> (Text -> IO Bool) -- ^ Return True if you want this hostname. | 414 | -> (Text -> IO Bool) -- ^ Return True if you want this hostname. |
410 | -> IO [(Bool, Maybe UserName, Text, Text)] | 415 | -> IO [(Bool, Maybe UserName, Text, Text)] |
@@ -425,7 +430,7 @@ getBuddiesAndSolicited state profile pred | |||
425 | then return [(isbud,u,user,h)] | 430 | then return [(isbud,u,user,h)] |
426 | else return [] | 431 | else return [] |
427 | 432 | ||
428 | sendProbesAndSolicitations :: PresenceState -> PeerAddress -> Local SockAddr -> TChan Stanza -> IO () | 433 | sendProbesAndSolicitations :: PresenceState stat -> PeerAddress -> Local SockAddr -> TChan Stanza -> IO () |
429 | sendProbesAndSolicitations state k (Local laddr) chan = do | 434 | sendProbesAndSolicitations state k (Local laddr) chan = do |
430 | prof <- atomically $ do | 435 | prof <- atomically $ do |
431 | pktc <- readTVar (pkeyToChan state) | 436 | pktc <- readTVar (pkeyToChan state) |
@@ -434,7 +439,7 @@ sendProbesAndSolicitations state k (Local laddr) chan = do | |||
434 | xs <- getBuddiesAndSolicited state prof $ \case | 439 | xs <- getBuddiesAndSolicited state prof $ \case |
435 | h | ".tox" `Text.isSuffixOf` h -> return False -- Tox probes/solicitations are handled in ToxToXMPP module. | 440 | h | ".tox" `Text.isSuffixOf` h -> return False -- Tox probes/solicitations are handled in ToxToXMPP module. |
436 | h -> do | 441 | h -> do |
437 | addrs <- nub <$> resolvePeer h | 442 | addrs <- nub <$> resolvePeer (manager state $ prof) h |
438 | return $ k `elem` addrs -- Roster item resolves to /k/ peer. | 443 | return $ k `elem` addrs -- Roster item resolves to /k/ peer. |
439 | forM_ xs $ \(isbud,u,user,h) -> do | 444 | forM_ xs $ \(isbud,u,user,h) -> do |
440 | let make = if isbud then presenceProbe | 445 | let make = if isbud then presenceProbe |
@@ -452,7 +457,7 @@ sendProbesAndSolicitations state k (Local laddr) chan = do | |||
452 | -- reverse xs `seq` return () | 457 | -- reverse xs `seq` return () |
453 | 458 | ||
454 | 459 | ||
455 | newConn :: PresenceState -> SockAddr -> ConnectionData -> TChan Stanza -> IO () | 460 | newConn :: PresenceState stat -> SockAddr -> ConnectionData -> TChan Stanza -> IO () |
456 | newConn state saddr cdta outchan = | 461 | newConn state saddr cdta outchan = |
457 | case classifyConnection saddr cdta of | 462 | case classifyConnection saddr cdta of |
458 | Left (pkey,laddr) -> do | 463 | Left (pkey,laddr) -> do |
@@ -473,7 +478,7 @@ delclient k mlp = do | |||
473 | guard $ not (Map.null nc) | 478 | guard $ not (Map.null nc) |
474 | return $ lp { networkClients = nc } | 479 | return $ lp { networkClients = nc } |
475 | 480 | ||
476 | eofConn :: PresenceState -> SockAddr -> ConnectionData -> IO () | 481 | eofConn :: PresenceState stat -> SockAddr -> ConnectionData -> IO () |
477 | eofConn state saddr cdta = do | 482 | eofConn state saddr cdta = do |
478 | case classifyConnection saddr cdta of | 483 | case classifyConnection saddr cdta of |
479 | Left (k,_) -> do | 484 | Left (k,_) -> do |
@@ -545,9 +550,9 @@ parseRemoteAddress s = fmap Remote <$> parseAddress s | |||
545 | -- domain name as it appears in the roster. It prefers host names that occur | 550 | -- domain name as it appears in the roster. It prefers host names that occur |
546 | -- in the given list of JIDs, but will fall back to any reverse-resolved name | 551 | -- in the given list of JIDs, but will fall back to any reverse-resolved name |
547 | -- and if it was unable to reverse the address, it will yield an ip address. | 552 | -- and if it was unable to reverse the address, it will yield an ip address. |
548 | peerKeyToResolvedName :: [Text] -> PeerAddress -> IO Text | 553 | peerKeyToResolvedName :: Connection.Manager s Text -> [Text] -> PeerAddress -> IO Text |
549 | peerKeyToResolvedName buds pk = do | 554 | peerKeyToResolvedName man buds pk = do |
550 | ns <- peerKeyToResolvedNames pk | 555 | ns <- reverseAddress man pk |
551 | let hs = map (\jid -> let (_,h,_)=splitJID jid in h) buds | 556 | let hs = map (\jid -> let (_,h,_)=splitJID jid in h) buds |
552 | ns' = sortBy (comparing $ not . flip elem hs) ns | 557 | ns' = sortBy (comparing $ not . flip elem hs) ns |
553 | return $ fromMaybe (peerKeyToText pk) (listToMaybe ns') | 558 | return $ fromMaybe (peerKeyToText pk) (listToMaybe ns') |
@@ -559,22 +564,22 @@ peerKeyToResolvedName buds pk = do | |||
559 | -- host part refers to this local host (i.e. it equals the given SockAddr). | 564 | -- host part refers to this local host (i.e. it equals the given SockAddr). |
560 | -- If there are multiple results, it will prefer one which is a member of the | 565 | -- If there are multiple results, it will prefer one which is a member of the |
561 | -- given list in the last argument. | 566 | -- given list in the last argument. |
562 | rewriteJIDForClient :: Local SockAddr -> Text -> [Text] -> IO (Bool,(Maybe Text,Text,Maybe Text)) | 567 | rewriteJIDForClient :: Connection.Manager s Text -> Local SockAddr -> Text -> [Text] -> IO (Bool,(Maybe Text,Text,Maybe Text)) |
563 | rewriteJIDForClient (Local laddr) jid buds = do | 568 | rewriteJIDForClient man (Local laddr) jid buds = do |
564 | let (n,h,r) = splitJID jid | 569 | let (n,h,r) = splitJID jid |
565 | -- dput XJabber $ "rewriteJIDForClient parsing " ++ show h | 570 | -- dput XJabber $ "rewriteJIDForClient parsing " ++ show h |
566 | maddr <- parseAddress (strip_brackets h) | 571 | maddr <- parseAddress (strip_brackets h) |
567 | fromMaybe (return (False,(n,ip6literal h,r))) $ maddr <&> \saddr -> do | 572 | fromMaybe (return (False,(n,ip6literal h,r))) $ maddr <&> \saddr -> do |
568 | let mine = sameAddress laddr saddr | 573 | let mine = sameAddress laddr saddr |
569 | h' <- if mine then textHostName | 574 | h' <- if mine then textHostName |
570 | else peerKeyToResolvedName buds (addrToPeerKey $ Remote saddr) | 575 | else peerKeyToResolvedName man buds (addrToPeerKey $ Remote saddr) |
571 | return (mine,(n,h',r)) | 576 | return (mine,(n,h',r)) |
572 | 577 | ||
573 | -- Given a local address and an IP-address JID, we return True if the JID is | 578 | -- Given a local address and an IP-address JID, we return True if the JID is |
574 | -- local, False otherwise. Additionally, a list of equivalent hostname JIDS | 579 | -- local, False otherwise. Additionally, a list of equivalent hostname JIDS |
575 | -- are returned. | 580 | -- are returned. |
576 | multiplyJIDForClient :: ClientAddress -> Text -> IO (Bool,[(Maybe Text,Text,Maybe Text)]) | 581 | multiplyJIDForClient :: Connection.Manager s Text -> ClientAddress -> Text -> IO (Bool,[(Maybe Text,Text,Maybe Text)]) |
577 | multiplyJIDForClient k jid = do | 582 | multiplyJIDForClient man k jid = do |
578 | let (n,h,r) = splitJID jid | 583 | let (n,h,r) = splitJID jid |
579 | -- dput XJabber $ "multiplyJIDForClient parsing " ++ show h | 584 | -- dput XJabber $ "multiplyJIDForClient parsing " ++ show h |
580 | maddr <- parseAddress (strip_brackets h) | 585 | maddr <- parseAddress (strip_brackets h) |
@@ -582,7 +587,7 @@ multiplyJIDForClient k jid = do | |||
582 | let Local laddr = addrFromClientKey k | 587 | let Local laddr = addrFromClientKey k |
583 | mine = sameAddress laddr saddr | 588 | mine = sameAddress laddr saddr |
584 | names <- if mine then fmap (:[]) textHostName | 589 | names <- if mine then fmap (:[]) textHostName |
585 | else peerKeyToResolvedNames (addrToPeerKey $ Remote saddr) | 590 | else reverseAddress man (addrToPeerKey $ Remote saddr) |
586 | return (mine,map (\h' -> (n,h',r)) names) | 591 | return (mine,map (\h' -> (n,h',r)) names) |
587 | 592 | ||
588 | 593 | ||
@@ -600,16 +605,16 @@ guardPortStrippedAddress h (Local laddr) = do | |||
600 | -- with a PeerAddress with the address part of that JID in | 605 | -- with a PeerAddress with the address part of that JID in |
601 | -- binary form. If no suitable address could be resolved | 606 | -- binary form. If no suitable address could be resolved |
602 | -- for the given name, Nothing is returned. | 607 | -- for the given name, Nothing is returned. |
603 | rewriteJIDForPeer :: Text -> IO (Maybe (Text,PeerAddress)) | 608 | rewriteJIDForPeer :: Connection.Manager s Text -> Text -> IO (Maybe (Text,PeerAddress)) |
604 | rewriteJIDForPeer jid = do | 609 | rewriteJIDForPeer man jid = do |
605 | let (n,h,r) = splitJID jid | 610 | let (n,h,r) = splitJID jid |
606 | maddr <- fmap listToMaybe $ resolvePeer h | 611 | maddr <- fmap listToMaybe $ resolvePeer man h |
607 | return $ flip fmap maddr $ \addr -> | 612 | return $ flip fmap maddr $ \addr -> |
608 | let h' = peerKeyToText addr | 613 | let h' = peerKeyToText addr |
609 | to' = unsplitJID (n,h',r) | 614 | to' = unsplitJID (n,h',r) |
610 | in (to',addr) | 615 | in (to',addr) |
611 | 616 | ||
612 | deliverToConsole :: PresenceState -> IO () -> Stanza -> IO () | 617 | deliverToConsole :: PresenceState stat -> IO () -> Stanza -> IO () |
613 | deliverToConsole PresenceState{ consoleWriter = Just cw } fail msg = do | 618 | deliverToConsole PresenceState{ consoleWriter = Just cw } fail msg = do |
614 | did1 <- writeActiveTTY cw msg | 619 | did1 <- writeActiveTTY cw msg |
615 | did2 <- writeAllPty cw msg | 620 | did2 <- writeAllPty cw msg |
@@ -617,7 +622,7 @@ deliverToConsole PresenceState{ consoleWriter = Just cw } fail msg = do | |||
617 | deliverToConsole _ fail _ = fail | 622 | deliverToConsole _ fail _ = fail |
618 | 623 | ||
619 | -- | deliver <message/> or error stanza | 624 | -- | deliver <message/> or error stanza |
620 | deliverMessage :: PresenceState | 625 | deliverMessage :: PresenceState stat |
621 | -> IO () | 626 | -> IO () |
622 | -> StanzaWrap (LockedChan Event) | 627 | -> StanzaWrap (LockedChan Event) |
623 | -> IO () | 628 | -> IO () |
@@ -630,7 +635,8 @@ deliverMessage state fail msg = | |||
630 | return $ do | 635 | return $ do |
631 | dput XJabber $ "deliverMessage: to="++show (stanzaTo msg,fmap clientProfile mclient) | 636 | dput XJabber $ "deliverMessage: to="++show (stanzaTo msg,fmap clientProfile mclient) |
632 | fromMaybe -- Resolve XMPP peer. | 637 | fromMaybe -- Resolve XMPP peer. |
633 | (fmap join $ mapM rewriteJIDForPeer (stanzaTo msg)) | 638 | (fmap join $ mapM (uncurry $ rewriteJIDForPeer . manager state) |
639 | $ (,) <$> (clientProfile <$> mclient) <*> stanzaTo msg) | ||
634 | $ do | 640 | $ do |
635 | client <- mclient | 641 | client <- mclient |
636 | to <- stanzaTo msg | 642 | to <- stanzaTo msg |
@@ -679,7 +685,7 @@ deliverMessage state fail msg = | |||
679 | (mine,(n,h,r)) <- case (ctyp,cprof) of | 685 | (mine,(n,h,r)) <- case (ctyp,cprof) of |
680 | (Tox,prof) -> let (n,h,r) = splitJID to | 686 | (Tox,prof) -> let (n,h,r) = splitJID to |
681 | in return ( h==prof, (n,h,r) ) | 687 | in return ( h==prof, (n,h,r) ) |
682 | _ -> rewriteJIDForClient laddr to [] | 688 | _ -> rewriteJIDForClient (manager state cprof) laddr to [] |
683 | if not mine then do dput XJabber $ "Address mis-match " ++ show (laddr,to) | 689 | if not mine then do dput XJabber $ "Address mis-match " ++ show (laddr,to) |
684 | fail | 690 | fail |
685 | else do | 691 | else do |
@@ -701,7 +707,7 @@ deliverMessage state fail msg = | |||
701 | Tox -> return $ stanzaFrom msg | 707 | Tox -> return $ stanzaFrom msg |
702 | XMPP -> do | 708 | XMPP -> do |
703 | forM (stanzaFrom msg) $ \from -> do | 709 | forM (stanzaFrom msg) $ \from -> do |
704 | (_,trip) <- rewriteJIDForClient laddr from buds | 710 | (_,trip) <- rewriteJIDForClient (manager state cprof) laddr from buds |
705 | return $ unsplitJID trip | 711 | return $ unsplitJID trip |
706 | to' <- case ctyp of | 712 | to' <- case ctyp of |
707 | XMPP -> return $ stanzaTo msg | 713 | XMPP -> return $ stanzaTo msg |
@@ -715,7 +721,7 @@ deliverMessage state fail msg = | |||
715 | buds <- maybe (return []) | 721 | buds <- maybe (return []) |
716 | (\n -> configText ConfigFiles.getBuddies n ".") | 722 | (\n -> configText ConfigFiles.getBuddies n ".") |
717 | n | 723 | n |
718 | (_,trip) <- rewriteJIDForClient laddr from buds | 724 | (_,trip) <- rewriteJIDForClient (manager state cprof) laddr from buds |
719 | return . Just $ unsplitJID trip | 725 | return . Just $ unsplitJID trip |
720 | let msg' = msg { stanzaTo=Just to' | 726 | let msg' = msg { stanzaTo=Just to' |
721 | , stanzaFrom=from' } | 727 | , stanzaFrom=from' } |
@@ -735,7 +741,7 @@ deliverMessage state fail msg = | |||
735 | chan | 741 | chan |
736 | 742 | ||
737 | 743 | ||
738 | setClientFlag :: PresenceState -> ClientAddress -> Int8 -> IO () | 744 | setClientFlag :: PresenceState stat -> ClientAddress -> Int8 -> IO () |
739 | setClientFlag state k flag = | 745 | setClientFlag state k flag = |
740 | atomically $ do | 746 | atomically $ do |
741 | cmap <- readTVar (clients state) | 747 | cmap <- readTVar (clients state) |
@@ -746,16 +752,16 @@ setClientFlag0 :: ClientState -> Int8 -> STM () | |||
746 | setClientFlag0 client flag = | 752 | setClientFlag0 client flag = |
747 | modifyTVar' (clientFlags client) (\flgs -> flgs .|. flag) | 753 | modifyTVar' (clientFlags client) (\flgs -> flgs .|. flag) |
748 | 754 | ||
749 | informSentRoster :: PresenceState -> ClientAddress -> IO () | 755 | informSentRoster :: PresenceState stat -> ClientAddress -> IO () |
750 | informSentRoster state k = do | 756 | informSentRoster state k = do |
751 | setClientFlag state k cf_interested | 757 | setClientFlag state k cf_interested |
752 | 758 | ||
753 | 759 | ||
754 | subscribedPeers :: Text -> Text -> IO [PeerAddress] | 760 | subscribedPeers :: Connection.Manager s Text -> Text -> Text -> IO [PeerAddress] |
755 | subscribedPeers user profile = do | 761 | subscribedPeers man user profile = do |
756 | jids <- configText ConfigFiles.getSubscribers user profile | 762 | jids <- configText ConfigFiles.getSubscribers user profile |
757 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 763 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
758 | fmap Map.keys $ resolveAllPeers hosts | 764 | fmap Map.keys $ resolveAllPeers man hosts |
759 | 765 | ||
760 | -- | this JID is suitable for peers, not clients. | 766 | -- | this JID is suitable for peers, not clients. |
761 | clientJID :: Conn -> ClientState -> Text | 767 | clientJID :: Conn -> ClientState -> Text |
@@ -769,13 +775,13 @@ clientJID con client = unsplitJID ( Just $ clientUser client | |||
769 | -- | Send presence notification to subscribed peers. | 775 | -- | Send presence notification to subscribed peers. |
770 | -- Note that a full JID from address will be added to the | 776 | -- Note that a full JID from address will be added to the |
771 | -- stanza if it is not present. | 777 | -- stanza if it is not present. |
772 | informClientPresence :: PresenceState | 778 | informClientPresence :: PresenceState stat |
773 | -> ClientAddress -> StanzaWrap (LockedChan Event) -> IO () | 779 | -> ClientAddress -> StanzaWrap (LockedChan Event) -> IO () |
774 | informClientPresence state k stanza = do | 780 | informClientPresence state k stanza = do |
775 | forClient state k (return ()) $ \client -> do | 781 | forClient state k (return ()) $ \client -> do |
776 | informClientPresence0 state (Just k) client stanza | 782 | informClientPresence0 state (Just k) client stanza |
777 | 783 | ||
778 | informClientPresence0 :: PresenceState | 784 | informClientPresence0 :: PresenceState stat |
779 | -> Maybe ClientAddress | 785 | -> Maybe ClientAddress |
780 | -> ClientState | 786 | -> ClientState |
781 | -> StanzaWrap (LockedChan Event) | 787 | -> StanzaWrap (LockedChan Event) |
@@ -787,21 +793,21 @@ informClientPresence0 state mbk client stanza = do | |||
787 | when (not is_avail) $ do | 793 | when (not is_avail) $ do |
788 | atomically $ setClientFlag0 client cf_available | 794 | atomically $ setClientFlag0 client cf_available |
789 | maybe (return ()) (sendCachedPresence state) mbk | 795 | maybe (return ()) (sendCachedPresence state) mbk |
790 | addrs <- subscribedPeers (clientUser client) (clientProfile client) | 796 | addrs <- subscribedPeers (manager state $ clientProfile client) (clientUser client) (clientProfile client) |
791 | ktc <- atomically $ readTVar (pkeyToChan state) | 797 | ktc <- atomically $ readTVar (pkeyToChan state) |
792 | let connected = mapMaybe (flip Map.lookup ktc) addrs | 798 | let connected = mapMaybe (flip Map.lookup ktc) addrs |
793 | forM_ connected $ \con -> do | 799 | forM_ connected $ \con -> do |
794 | let from' = clientJID con client | 800 | let from' = clientJID con client |
795 | mto <- runTraversableT $ do | 801 | mto <- runTraversableT $ do |
796 | to <- liftT $ stanzaTo stanza | 802 | to <- liftT $ stanzaTo stanza |
797 | (to',_) <- liftMT $ rewriteJIDForPeer to | 803 | (to',_) <- liftMT $ rewriteJIDForPeer (manager state $ clientProfile client) to |
798 | return to' | 804 | return to' |
799 | dup <- cloneStanza stanza | 805 | dup <- cloneStanza stanza |
800 | sendModifiedStanzaToPeer dup { stanzaFrom = Just from' | 806 | sendModifiedStanzaToPeer dup { stanzaFrom = Just from' |
801 | , stanzaTo = mto } | 807 | , stanzaTo = mto } |
802 | (connChan con) | 808 | (connChan con) |
803 | 809 | ||
804 | informPeerPresence :: PresenceState | 810 | informPeerPresence :: PresenceState stat |
805 | -> PeerAddress | 811 | -> PeerAddress |
806 | -> StanzaWrap (LockedChan Event) | 812 | -> StanzaWrap (LockedChan Event) |
807 | -> IO () | 813 | -> IO () |
@@ -874,7 +880,7 @@ informPeerPresence state k stanza = do | |||
874 | froms <- case ctyp of | 880 | froms <- case ctyp of |
875 | Tox | clientProfile client == cprof -> return [from] | 881 | Tox | clientProfile client == cprof -> return [from] |
876 | _ -> do -- flip (maybe $ return [from]) k . const $ do | 882 | _ -> do -- flip (maybe $ return [from]) k . const $ do |
877 | (_,trip) <- multiplyJIDForClient ck from | 883 | (_,trip) <- multiplyJIDForClient (manager state $ clientProfile client) ck from |
878 | return (map unsplitJID trip) | 884 | return (map unsplitJID trip) |
879 | 885 | ||
880 | dput XJabber $ "sending to client: " ++ show (stanzaType stanza,froms) | 886 | dput XJabber $ "sending to client: " ++ show (stanzaType stanza,froms) |
@@ -883,12 +889,12 @@ informPeerPresence state k stanza = do | |||
883 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) | 889 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) |
884 | (connChan con) | 890 | (connChan con) |
885 | 891 | ||
886 | consoleClients :: PresenceState -> STM (Map Text ClientState) | 892 | consoleClients :: PresenceState stat -> STM (Map Text ClientState) |
887 | consoleClients PresenceState{ consoleWriter = Just cw } = readTVar (cwClients cw) | 893 | consoleClients PresenceState{ consoleWriter = Just cw } = readTVar (cwClients cw) |
888 | consoleClients _ = return Map.empty | 894 | consoleClients _ = return Map.empty |
889 | 895 | ||
890 | 896 | ||
891 | answerProbe :: PresenceState -> Maybe Text -> PeerAddress -> TChan Stanza -> IO () | 897 | answerProbe :: PresenceState stat -> Maybe Text -> PeerAddress -> TChan Stanza -> IO () |
892 | answerProbe state mto k chan = do | 898 | answerProbe state mto k chan = do |
893 | -- dput XJabber $ "answerProbe! " ++ show (stanzaType stanza) | 899 | -- dput XJabber $ "answerProbe! " ++ show (stanzaType stanza) |
894 | ktc <- atomically $ readTVar (pkeyToChan state) | 900 | ktc <- atomically $ readTVar (pkeyToChan state) |
@@ -911,7 +917,8 @@ answerProbe state mto k chan = do | |||
911 | forM_ profiles $ \profile -> do | 917 | forM_ profiles $ \profile -> do |
912 | 918 | ||
913 | -- only subscribed peers should get probe replies | 919 | -- only subscribed peers should get probe replies |
914 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u profile | 920 | let man = manager state $ cdProfile $ auxData conn |
921 | resolved_subs <- resolvedFromRoster man ConfigFiles.getSubscribers u profile | ||
915 | let gaddrs = groupBy sameHost (sort resolved_subs) | 922 | let gaddrs = groupBy sameHost (sort resolved_subs) |
916 | sameHost a b = (snd a == snd b) -- (==) `on` snd | 923 | sameHost a b = (snd a == snd b) -- (==) `on` snd |
917 | whitelist = do | 924 | whitelist = do |
@@ -951,13 +958,13 @@ answerProbe state mto k chan = do | |||
951 | 958 | ||
952 | -- Send friend requests and remote presences stored in remotesByPeer to XMPP | 959 | -- Send friend requests and remote presences stored in remotesByPeer to XMPP |
953 | -- clients. | 960 | -- clients. |
954 | sendCachedPresence :: PresenceState -> ClientAddress -> IO () | 961 | sendCachedPresence :: PresenceState stat -> ClientAddress -> IO () |
955 | sendCachedPresence state k = do | 962 | sendCachedPresence state k = do |
956 | forClient state k (return ()) $ \client -> do | 963 | forClient state k (return ()) $ \client -> do |
957 | rbp <- atomically $ readTVar (remotesByPeer state) | 964 | rbp <- atomically $ readTVar (remotesByPeer state) |
958 | jids <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) | 965 | jids <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
959 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 966 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
960 | addrs <- resolveAllPeers hosts | 967 | addrs <- resolveAllPeers (manager state $ clientProfile client) hosts |
961 | let onlines = rbp `Map.intersection` addrs | 968 | let onlines = rbp `Map.intersection` addrs |
962 | mcon <- atomically $ do ktc <- readTVar (ckeyToChan state) | 969 | mcon <- atomically $ do ktc <- readTVar (ckeyToChan state) |
963 | return $ Map.lookup k ktc | 970 | return $ Map.lookup k ktc |
@@ -967,7 +974,7 @@ sendCachedPresence state k = do | |||
967 | let h = peerKeyToText pk | 974 | let h = peerKeyToText pk |
968 | forM_ (Map.toList $ resources rp) $ \(resource,stanza) -> do | 975 | forM_ (Map.toList $ resources rp) $ \(resource,stanza) -> do |
969 | let jid = unsplitJID (Just user,h,Just resource) | 976 | let jid = unsplitJID (Just user,h,Just resource) |
970 | (mine,js) <- multiplyJIDForClient k jid | 977 | (mine,js) <- multiplyJIDForClient (manager state $ clientProfile client) k jid |
971 | forM_ js $ \jid -> do | 978 | forM_ js $ \jid -> do |
972 | let from' = unsplitJID jid | 979 | let from' = unsplitJID jid |
973 | dup <- cloneStanza stanza | 980 | dup <- cloneStanza stanza |
@@ -988,37 +995,40 @@ sendCachedPresence state k = do | |||
988 | return () | 995 | return () |
989 | 996 | ||
990 | addToRosterFile :: | 997 | addToRosterFile :: |
991 | (ConfigFiles.User | 998 | Connection.Manager s Text |
992 | -> ConfigFiles.Profile | 999 | -> (ConfigFiles.User |
993 | -> (L.ByteString -> IO (Maybe L.ByteString)) | 1000 | -> ConfigFiles.Profile |
994 | -> Maybe L.ByteString | 1001 | -> (L.ByteString -> IO (Maybe L.ByteString)) |
995 | -> t1) | 1002 | -> Maybe L.ByteString |
1003 | -> t1) | ||
996 | -> Text -- user | 1004 | -> Text -- user |
997 | -> Text -- profile | 1005 | -> Text -- profile |
998 | -> Text -> [PeerAddress] -> t1 | 1006 | -> Text -> [PeerAddress] -> t1 |
999 | addToRosterFile doit whose profile to addrs = | 1007 | addToRosterFile man doit whose profile to addrs = |
1000 | modifyRosterFile doit whose profile to addrs True | 1008 | modifyRosterFile man doit whose profile to addrs True |
1001 | 1009 | ||
1002 | removeFromRosterFile :: | 1010 | removeFromRosterFile :: |
1003 | (ConfigFiles.User | 1011 | Connection.Manager s Text |
1004 | -> ConfigFiles.Profile | 1012 | -> (ConfigFiles.User |
1005 | -> (L.ByteString -> IO (Maybe L.ByteString)) | 1013 | -> ConfigFiles.Profile |
1006 | -> Maybe L.ByteString | 1014 | -> (L.ByteString -> IO (Maybe L.ByteString)) |
1007 | -> t1) | 1015 | -> Maybe L.ByteString |
1016 | -> t1) | ||
1008 | -> Text -- user | 1017 | -> Text -- user |
1009 | -> Text -- profile | 1018 | -> Text -- profile |
1010 | -> Text -> [PeerAddress] -> t1 | 1019 | -> Text -> [PeerAddress] -> t1 |
1011 | removeFromRosterFile doit whose profile to addrs = | 1020 | removeFromRosterFile man doit whose profile to addrs = |
1012 | modifyRosterFile doit whose profile to addrs False | 1021 | modifyRosterFile man doit whose profile to addrs False |
1013 | 1022 | ||
1014 | -- | Sanity-checked roster file manipulation. Primarily, this function handles | 1023 | -- | Sanity-checked roster file manipulation. Primarily, this function handles |
1015 | -- hostname aliases. | 1024 | -- hostname aliases. |
1016 | modifyRosterFile :: | 1025 | modifyRosterFile :: |
1017 | (ConfigFiles.User | 1026 | Connection.Manager s Text |
1018 | -> ConfigFiles.Profile | 1027 | -> (ConfigFiles.User |
1019 | -> (L.ByteString -> IO (Maybe L.ByteString)) | 1028 | -> ConfigFiles.Profile |
1020 | -> Maybe L.ByteString | 1029 | -> (L.ByteString -> IO (Maybe L.ByteString)) |
1021 | -> t1) -- ^ Lower-level modification function | 1030 | -> Maybe L.ByteString |
1031 | -> t1) -- ^ Lower-level modification function | ||
1022 | -- indicating which file is being modified. | 1032 | -- indicating which file is being modified. |
1023 | -- Valid choices from ConfigFiles module: | 1033 | -- Valid choices from ConfigFiles module: |
1024 | -- | 1034 | -- |
@@ -1035,7 +1045,7 @@ modifyRosterFile :: | |||
1035 | -> [PeerAddress] -- ^ Alias addresses for hostname in the JID. | 1045 | -> [PeerAddress] -- ^ Alias addresses for hostname in the JID. |
1036 | -> Bool -- ^ True if adding, otherwise False | 1046 | -> Bool -- ^ True if adding, otherwise False |
1037 | -> t1 | 1047 | -> t1 |
1038 | modifyRosterFile doit whose profile to addrs bAdd = do | 1048 | modifyRosterFile man doit whose profile to addrs bAdd = do |
1039 | let (mu,_,_) = splitJID to | 1049 | let (mu,_,_) = splitJID to |
1040 | -- For each jid in the file, this function will decide whether to keep | 1050 | -- For each jid in the file, this function will decide whether to keep |
1041 | -- it (possibly modified) which is indicated by Just _ or to remove the | 1051 | -- it (possibly modified) which is indicated by Just _ or to remove the |
@@ -1046,7 +1056,7 @@ modifyRosterFile doit whose profile to addrs bAdd = do | |||
1046 | keep = return (Just jid) :: IO (Maybe L.ByteString) | 1056 | keep = return (Just jid) :: IO (Maybe L.ByteString) |
1047 | delete = return Nothing :: IO (Maybe L.ByteString) | 1057 | delete = return Nothing :: IO (Maybe L.ByteString) |
1048 | iocheck = do | 1058 | iocheck = do |
1049 | stored_addrs <- resolvePeer stored_h -- TODO: don't resolve .tox peers. | 1059 | stored_addrs <- resolvePeer man stored_h -- TODO: don't resolve .tox peers. |
1050 | case stored_addrs of | 1060 | case stored_addrs of |
1051 | [] -> keep -- do not delete if failed to resolve | 1061 | [] -> keep -- do not delete if failed to resolve |
1052 | xs | null (xs \\ addrs) -> delete -- hostname alias, delete | 1062 | xs | null (xs \\ addrs) -> delete -- hostname alias, delete |
@@ -1063,7 +1073,7 @@ modifyRosterFile doit whose profile to addrs bAdd = do | |||
1063 | (guard bAdd >> Just (textToLazyByteString to)) | 1073 | (guard bAdd >> Just (textToLazyByteString to)) |
1064 | 1074 | ||
1065 | 1075 | ||
1066 | clientSubscriptionRequest :: PresenceState -> IO () -> ClientAddress -> Stanza -> TChan Stanza -> IO () | 1076 | clientSubscriptionRequest :: PresenceState stat -> IO () -> ClientAddress -> Stanza -> TChan Stanza -> IO () |
1067 | clientSubscriptionRequest state fail k stanza chan = do | 1077 | clientSubscriptionRequest state fail k stanza chan = do |
1068 | forClient state k fail $ \client -> do | 1078 | forClient state k fail $ \client -> do |
1069 | fromMaybe fail $ (splitJID <$> stanzaTo stanza) <&> \(mu,h,_) -> do | 1079 | fromMaybe fail $ (splitJID <$> stanzaTo stanza) <&> \(mu,h,_) -> do |
@@ -1071,6 +1081,7 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
1071 | let to0 = unsplitJID (mu,h,Nothing) -- deleted resource | 1081 | let to0 = unsplitJID (mu,h,Nothing) -- deleted resource |
1072 | cuser = clientUser client | 1082 | cuser = clientUser client |
1073 | cprof = clientProfile client | 1083 | cprof = clientProfile client |
1084 | man = manager state cprof | ||
1074 | mto = if ".tox" `Text.isSuffixOf` cprof | 1085 | mto = if ".tox" `Text.isSuffixOf` cprof |
1075 | then case parseNoSpamId to0 of | 1086 | then case parseNoSpamId to0 of |
1076 | Right toxjid@(NoSpamId nspam _) -> Just ( Text.pack $ '$' : nospam64 nspam | 1087 | Right toxjid@(NoSpamId nspam _) -> Just ( Text.pack $ '$' : nospam64 nspam |
@@ -1079,16 +1090,16 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
1079 | Left _ | Text.isSuffixOf ".tox" h -> Nothing | 1090 | Left _ | Text.isSuffixOf ".tox" h -> Nothing |
1080 | Left _ | Text.all isHexDigit h | 1091 | Left _ | Text.all isHexDigit h |
1081 | && Text.length h == 76 -> Nothing | 1092 | && Text.length h == 76 -> Nothing |
1082 | Left _ -> fmap (\u -> (u, to0 ,resolvePeer h)) mu | 1093 | Left _ -> fmap (\u -> (u, to0 ,resolvePeer man h)) mu |
1083 | else fmap (\u -> (u, to0 ,resolvePeer h)) mu | 1094 | else fmap (\u -> (u, to0 ,resolvePeer man h)) mu |
1084 | fromMaybe fail $ mto <&> \(u,to,resolv) -> do | 1095 | fromMaybe fail $ mto <&> \(u,to,resolv) -> do |
1085 | -- add to-address to from's solicited | 1096 | -- add to-address to from's solicited |
1086 | dput XJabber $ unlines [ "to0=" ++ Text.unpack to0 | 1097 | dput XJabber $ unlines [ "to0=" ++ Text.unpack to0 |
1087 | , "to=" ++ show (Text.unpack to) ] | 1098 | , "to=" ++ show (Text.unpack to) ] |
1088 | addrs <- resolv | 1099 | addrs <- resolv |
1089 | addToRosterFile ConfigFiles.modifySolicited cuser cprof to addrs | 1100 | addToRosterFile man ConfigFiles.modifySolicited cuser cprof to addrs |
1090 | removeFromRosterFile ConfigFiles.modifyBuddies cuser cprof to addrs | 1101 | removeFromRosterFile man ConfigFiles.modifyBuddies cuser cprof to addrs |
1091 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers cuser cprof | 1102 | resolved_subs <- resolvedFromRoster man ConfigFiles.getSubscribers cuser cprof |
1092 | let is_subscribed = not . null $ [ (mu, a) | a <- addrs ] | 1103 | let is_subscribed = not . null $ [ (mu, a) | a <- addrs ] |
1093 | `intersect` resolved_subs | 1104 | `intersect` resolved_subs |
1094 | -- subscribers: "from" | 1105 | -- subscribers: "from" |
@@ -1100,8 +1111,7 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
1100 | (cktc,pktc,(sv,conns)) <- atomically $ do | 1111 | (cktc,pktc,(sv,conns)) <- atomically $ do |
1101 | cktc <- readTVar $ ckeyToChan state | 1112 | cktc <- readTVar $ ckeyToChan state |
1102 | pktc <- readTVar $ pkeyToChan state | 1113 | pktc <- readTVar $ pkeyToChan state |
1103 | sc <- takeTMVar svVar | 1114 | return (cktc,pktc,(server state,man)) |
1104 | return (cktc,pktc,sc) | ||
1105 | 1115 | ||
1106 | -- Update roster for each client. | 1116 | -- Update roster for each client. |
1107 | case stanzaType stanza of | 1117 | case stanzaType stanza of |
@@ -1132,7 +1142,7 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
1132 | from = unsplitJID ( Just $ clientUser client | 1142 | from = unsplitJID ( Just $ clientUser client |
1133 | , (\(Local a) -> addrToText a) $ laddr | 1143 | , (\(Local a) -> addrToText a) $ laddr |
1134 | , Nothing ) | 1144 | , Nothing ) |
1135 | mb <- rewriteJIDForPeer to | 1145 | mb <- rewriteJIDForPeer (manager state $ cdProfile $ auxData con) to |
1136 | forM_ mb $ \(to',addr) -> do | 1146 | forM_ mb $ \(to',addr) -> do |
1137 | dup <- cloneStanza stanza | 1147 | dup <- cloneStanza stanza |
1138 | sendModifiedStanzaToPeer (dup { stanzaTo = Just to' | 1148 | sendModifiedStanzaToPeer (dup { stanzaTo = Just to' |
@@ -1145,9 +1155,8 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
1145 | Just $ Connection.setPolicy (toxConnections toxman) (ToxContact meid themid) | 1155 | Just $ Connection.setPolicy (toxConnections toxman) (ToxContact meid themid) |
1146 | -- Add peer if we are not already associated ... | 1156 | -- Add peer if we are not already associated ... |
1147 | policySetter Connection.TryingToConnect | 1157 | policySetter Connection.TryingToConnect |
1148 | atomically $ putTMVar svVar (sv,conns) | ||
1149 | 1158 | ||
1150 | weAreTox :: PresenceState -> ClientState -> Text -> Maybe (ToxManager ClientAddress,Text{- me -},Text{- them -}) | 1159 | weAreTox :: PresenceState stat -> ClientState -> Text -> Maybe (ToxManager ClientAddress,Text{- me -},Text{- them -}) |
1151 | weAreTox state client h = do | 1160 | weAreTox state client h = do |
1152 | toxman <- toxManager state | 1161 | toxman <- toxManager state |
1153 | (me , ".tox") <- Just $ Text.splitAt 43 (clientProfile client) | 1162 | (me , ".tox") <- Just $ Text.splitAt 43 (clientProfile client) |
@@ -1155,20 +1164,21 @@ weAreTox state client h = do | |||
1155 | return (toxman,me,them) | 1164 | return (toxman,me,them) |
1156 | 1165 | ||
1157 | resolvedFromRoster | 1166 | resolvedFromRoster |
1158 | :: (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) | 1167 | :: Connection.Manager s Text |
1168 | -> (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) | ||
1159 | -> UserName -> Text -> IO [(Maybe UserName, PeerAddress)] | 1169 | -> UserName -> Text -> IO [(Maybe UserName, PeerAddress)] |
1160 | resolvedFromRoster doit u profile = do | 1170 | resolvedFromRoster man doit u profile = do |
1161 | subs <- configText doit u profile | 1171 | subs <- configText doit u profile |
1162 | runTraversableT $ do | 1172 | runTraversableT $ do |
1163 | (mu,h,_) <- liftT $ splitJID `fmap` subs | 1173 | (mu,h,_) <- liftT $ splitJID `fmap` subs |
1164 | addr <- liftMT $ fmap nub $ resolvePeer h | 1174 | addr <- liftMT $ fmap nub $ resolvePeer man h |
1165 | return (mu,addr) | 1175 | return (mu,addr) |
1166 | 1176 | ||
1167 | clientCons :: PresenceState | 1177 | clientCons :: PresenceState stat |
1168 | -> Map ClientAddress t -> Text -> IO [(t, ClientState)] | 1178 | -> Map ClientAddress t -> Text -> IO [(t, ClientState)] |
1169 | clientCons state ktc u = map snd <$> clientCons' state ktc u | 1179 | clientCons state ktc u = map snd <$> clientCons' state ktc u |
1170 | 1180 | ||
1171 | clientCons' :: PresenceState | 1181 | clientCons' :: PresenceState stat |
1172 | -> Map ClientAddress t -> Text -> IO [(ClientAddress,(t, ClientState))] | 1182 | -> Map ClientAddress t -> Text -> IO [(ClientAddress,(t, ClientState))] |
1173 | clientCons' state ktc u = do | 1183 | clientCons' state ktc u = do |
1174 | mlp <- atomically $ do | 1184 | mlp <- atomically $ do |
@@ -1188,7 +1198,7 @@ releventProfiles ctyp user = do | |||
1188 | -- .presence/ directory. | 1198 | -- .presence/ directory. |
1189 | return [] | 1199 | return [] |
1190 | 1200 | ||
1191 | peerSubscriptionRequest :: PresenceState -> IO () -> PeerAddress -> Stanza -> TChan Stanza -> IO () | 1201 | peerSubscriptionRequest :: PresenceState stat -> IO () -> PeerAddress -> Stanza -> TChan Stanza -> IO () |
1192 | peerSubscriptionRequest state fail k stanza chan = do | 1202 | peerSubscriptionRequest state fail k stanza chan = do |
1193 | dput XJabber $ "Handling pending subscription from remote" | 1203 | dput XJabber $ "Handling pending subscription from remote" |
1194 | fromMaybe fail $ (stanzaFrom stanza) <&> \from -> do | 1204 | fromMaybe fail $ (stanzaFrom stanza) <&> \from -> do |
@@ -1207,12 +1217,12 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
1207 | (mine,totup) <- case (ctyp,profile) of | 1217 | (mine,totup) <- case (ctyp,profile) of |
1208 | (Tox,p) -> let (u,h,r) = splitJID to | 1218 | (Tox,p) -> let (u,h,r) = splitJID to |
1209 | in return ( h == p, (u,h,r) ) | 1219 | in return ( h == p, (u,h,r) ) |
1210 | _ -> rewriteJIDForClient laddr to [] | 1220 | _ -> rewriteJIDForClient (manager state profile) laddr to [] |
1211 | if not mine then fail else do | 1221 | if not mine then fail else do |
1212 | (_,fromtup) <- rewriteJIDForClient laddr from [] | 1222 | (_,fromtup) <- rewriteJIDForClient (manager state profile) laddr from [] |
1213 | fromMaybe fail $ mto_u <&> \u -> do | 1223 | fromMaybe fail $ mto_u <&> \u -> do |
1214 | fromMaybe fail $ mfrom_u <&> \from_u -> do | 1224 | fromMaybe fail $ mfrom_u <&> \from_u -> do |
1215 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u profile | 1225 | resolved_subs <- resolvedFromRoster (manager state profile) ConfigFiles.getSubscribers u profile |
1216 | let already_subscribed = elem (mfrom_u,k) resolved_subs | 1226 | let already_subscribed = elem (mfrom_u,k) resolved_subs |
1217 | is_wanted = case stanzaType stanza of | 1227 | is_wanted = case stanzaType stanza of |
1218 | PresenceRequestSubscription b -> b | 1228 | PresenceRequestSubscription b -> b |
@@ -1233,7 +1243,7 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
1233 | -- TODO: if peer-connection is to self, then auto-approve local user. | 1243 | -- TODO: if peer-connection is to self, then auto-approve local user. |
1234 | 1244 | ||
1235 | -- add from-address to to's pending | 1245 | -- add from-address to to's pending |
1236 | addrs <- resolvePeer from_h | 1246 | addrs <- resolvePeer (manager state profile) from_h |
1237 | 1247 | ||
1238 | -- Catch exception in case the user does not exist | 1248 | -- Catch exception in case the user does not exist |
1239 | if null addrs then fail else do | 1249 | if null addrs then fail else do |
@@ -1243,9 +1253,9 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
1243 | -- Update roster files (subscribe: add to pending, unsubscribe: remove from subscribers). | 1253 | -- Update roster files (subscribe: add to pending, unsubscribe: remove from subscribers). |
1244 | already_pending <- | 1254 | already_pending <- |
1245 | if is_wanted then | 1255 | if is_wanted then |
1246 | addToRosterFile ConfigFiles.modifyPending u profile from' addrs | 1256 | addToRosterFile (manager state profile) ConfigFiles.modifyPending u profile from' addrs |
1247 | else do | 1257 | else do |
1248 | removeFromRosterFile ConfigFiles.modifySubscribers u profile from' addrs | 1258 | removeFromRosterFile (manager state profile) ConfigFiles.modifySubscribers u profile from' addrs |
1249 | reply <- makeInformSubscription "jabber:server" to from is_wanted | 1259 | reply <- makeInformSubscription "jabber:server" to from is_wanted |
1250 | sendModifiedStanzaToPeer reply chan | 1260 | sendModifiedStanzaToPeer reply chan |
1251 | return False | 1261 | return False |
@@ -1270,7 +1280,7 @@ myMakeRosterUpdate prf tojid contact as | |||
1270 | myMakeRosterUpdate _ tojid contact as = XMPPServer.makeRosterUpdate tojid contact as | 1280 | myMakeRosterUpdate _ tojid contact as = XMPPServer.makeRosterUpdate tojid contact as |
1271 | 1281 | ||
1272 | 1282 | ||
1273 | clientInformSubscription :: PresenceState | 1283 | clientInformSubscription :: PresenceState stat |
1274 | -> IO () | 1284 | -> IO () |
1275 | -> ClientAddress | 1285 | -> ClientAddress |
1276 | -> StanzaWrap (LockedChan Event) | 1286 | -> StanzaWrap (LockedChan Event) |
@@ -1280,11 +1290,12 @@ clientInformSubscription state fail k stanza = do | |||
1280 | fromMaybe fail $ (stanzaTo stanza) <&> \to -> do | 1290 | fromMaybe fail $ (stanzaTo stanza) <&> \to -> do |
1281 | dput XJabber $ "clientInformSubscription" | 1291 | dput XJabber $ "clientInformSubscription" |
1282 | let (mu,h,mr) = splitJID to | 1292 | let (mu,h,mr) = splitJID to |
1283 | addrs <- resolvePeer h | 1293 | man = manager state $ clientProfile client |
1294 | addrs <- resolvePeer man h | ||
1284 | -- remove from pending | 1295 | -- remove from pending |
1285 | buds <- resolvedFromRoster ConfigFiles.getBuddies (clientUser client) (clientProfile client) | 1296 | buds <- resolvedFromRoster man ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
1286 | let is_buddy = not . null $ map (mu,) addrs `intersect` buds | 1297 | let is_buddy = not . null $ map (mu,) addrs `intersect` buds |
1287 | removeFromRosterFile ConfigFiles.modifyPending (clientUser client) (clientProfile client) to addrs | 1298 | removeFromRosterFile man ConfigFiles.modifyPending (clientUser client) (clientProfile client) to addrs |
1288 | let (relationship,addf,remf) = | 1299 | let (relationship,addf,remf) = |
1289 | case stanzaType stanza of | 1300 | case stanzaType stanza of |
1290 | PresenceInformSubscription True -> | 1301 | PresenceInformSubscription True -> |
@@ -1296,8 +1307,8 @@ clientInformSubscription state fail k stanza = do | |||
1296 | else "none" ) | 1307 | else "none" ) |
1297 | , ConfigFiles.modifyOthers | 1308 | , ConfigFiles.modifyOthers |
1298 | , ConfigFiles.modifySubscribers ) | 1309 | , ConfigFiles.modifySubscribers ) |
1299 | addToRosterFile addf (clientUser client) (clientProfile client) to addrs | 1310 | addToRosterFile man addf (clientUser client) (clientProfile client) to addrs |
1300 | removeFromRosterFile remf (clientUser client) (clientProfile client) to addrs | 1311 | removeFromRosterFile man remf (clientUser client) (clientProfile client) to addrs |
1301 | 1312 | ||
1302 | do | 1313 | do |
1303 | cbu <- atomically $ readTVar (clientsByUser state) | 1314 | cbu <- atomically $ readTVar (clientsByUser state) |
@@ -1335,7 +1346,7 @@ clientInformSubscription state fail k stanza = do | |||
1335 | (connChan con) | 1346 | (connChan con) |
1336 | answerProbe state (Just from) pk (connChan con) | 1347 | answerProbe state (Just from) pk (connChan con) |
1337 | 1348 | ||
1338 | peerInformSubscription :: PresenceState | 1349 | peerInformSubscription :: PresenceState stat |
1339 | -> IO () | 1350 | -> IO () |
1340 | -> PeerAddress | 1351 | -> PeerAddress |
1341 | -> StanzaWrap (LockedChan Event) | 1352 | -> StanzaWrap (LockedChan Event) |
@@ -1352,9 +1363,10 @@ peerInformSubscription state fail k stanza = do | |||
1352 | fromMaybe fail $ Map.lookup k ktc | 1363 | fromMaybe fail $ Map.lookup k ktc |
1353 | <&> \(Conn { connChan=sender_chan | 1364 | <&> \(Conn { connChan=sender_chan |
1354 | , auxData =ConnectionData (Left laddr) ctyp profile _ }) -> do | 1365 | , auxData =ConnectionData (Left laddr) ctyp profile _ }) -> do |
1366 | let man = manager state profile | ||
1355 | (from_u,from_h,_) <- case ctyp of | 1367 | (from_u,from_h,_) <- case ctyp of |
1356 | Tox -> return $ splitJID from | 1368 | Tox -> return $ splitJID from |
1357 | XMPP -> snd <$> rewriteJIDForClient laddr from [] | 1369 | XMPP -> snd <$> rewriteJIDForClient man laddr from [] |
1358 | let from'' = unsplitJID (from_u,from_h,Nothing) | 1370 | let from'' = unsplitJID (from_u,from_h,Nothing) |
1359 | muser = do | 1371 | muser = do |
1360 | to <- stanzaTo stanza | 1372 | to <- stanzaTo stanza |
@@ -1365,10 +1377,10 @@ peerInformSubscription state fail k stanza = do | |||
1365 | -- This would allow us to answer anonymous probes with 'unsubscribed'. | 1377 | -- This would allow us to answer anonymous probes with 'unsubscribed'. |
1366 | fromMaybe fail $ muser <&> \user -> do | 1378 | fromMaybe fail $ muser <&> \user -> do |
1367 | 1379 | ||
1368 | addrs <- resolvePeer from_h | 1380 | addrs <- resolvePeer man from_h |
1369 | was_solicited <- removeFromRosterFile ConfigFiles.modifySolicited user profile from'' addrs | 1381 | was_solicited <- removeFromRosterFile man ConfigFiles.modifySolicited user profile from'' addrs |
1370 | 1382 | ||
1371 | subs <- resolvedFromRoster ConfigFiles.getSubscribers user profile | 1383 | subs <- resolvedFromRoster man ConfigFiles.getSubscribers user profile |
1372 | let is_sub = not . null $ map (from_u,) addrs `intersect` subs | 1384 | let is_sub = not . null $ map (from_u,) addrs `intersect` subs |
1373 | dput XJabber $ "DEBUG peerInformSubscription (is_sub,typ)=" ++ show (is_sub,stanzaType stanza) | 1385 | dput XJabber $ "DEBUG peerInformSubscription (is_sub,typ)=" ++ show (is_sub,stanzaType stanza) |
1374 | let (relationship,addf,remf) = | 1386 | let (relationship,addf,remf) = |
@@ -1382,8 +1394,8 @@ peerInformSubscription state fail k stanza = do | |||
1382 | else "none") | 1394 | else "none") |
1383 | , ConfigFiles.modifyOthers | 1395 | , ConfigFiles.modifyOthers |
1384 | , ConfigFiles.modifyBuddies ) | 1396 | , ConfigFiles.modifyBuddies ) |
1385 | addToRosterFile addf user profile from'' addrs | 1397 | addToRosterFile man addf user profile from'' addrs |
1386 | removeFromRosterFile remf user profile from'' addrs | 1398 | removeFromRosterFile man remf user profile from'' addrs |
1387 | 1399 | ||
1388 | chans <- clientCons' state cktc user | 1400 | chans <- clientCons' state cktc user |
1389 | forM_ chans $ \(ckey,(Conn { connChan=chan }, client)) -> do | 1401 | forM_ chans $ \(ckey,(Conn { connChan=chan }, client)) -> do |
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs index bb0cc912..02c33635 100644 --- a/Presence/XMPPServer.hs +++ b/Presence/XMPPServer.hs | |||
@@ -6,6 +6,7 @@ | |||
6 | {-# LANGUAGE ExistentialQuantification #-} | 6 | {-# LANGUAGE ExistentialQuantification #-} |
7 | module XMPPServer | 7 | module XMPPServer |
8 | ( xmppServer | 8 | ( xmppServer |
9 | , forkXmpp | ||
9 | , quitXmpp | 10 | , quitXmpp |
10 | , ClientAddress | 11 | , ClientAddress |
11 | , PeerAddress | 12 | , PeerAddress |
@@ -42,8 +43,6 @@ module XMPPServer | |||
42 | , greet' | 43 | , greet' |
43 | , (<&>) | 44 | , (<&>) |
44 | , grokStanza | 45 | , grokStanza |
45 | , Uniq24(..) | ||
46 | , uniqueAsKey | ||
47 | ) where | 46 | ) where |
48 | 47 | ||
49 | import ConnectionKey | 48 | import ConnectionKey |
@@ -53,7 +52,7 @@ import Connection.Tcp | |||
53 | import EventUtil | 52 | import EventUtil |
54 | import ControlMaybe | 53 | import ControlMaybe |
55 | import LockedChan | 54 | import LockedChan |
56 | import PeerResolve | 55 | import Connection (PeerAddress(..)) |
57 | import qualified Connection | 56 | import qualified Connection |
58 | import Util | 57 | import Util |
59 | import Network.Address (getBindAddress, sockAddrPort) | 58 | import Network.Address (getBindAddress, sockAddrPort) |
@@ -66,9 +65,9 @@ import Control.Monad.IO.Class (MonadIO, liftIO) | |||
66 | import Control.Monad.Fix (fix) | 65 | import Control.Monad.Fix (fix) |
67 | import Control.Monad | 66 | import Control.Monad |
68 | #ifdef THREAD_DEBUG | 67 | #ifdef THREAD_DEBUG |
69 | import Control.Concurrent.Lifted.Instrument (forkIO,myThreadId,labelThread) | 68 | import Control.Concurrent.Lifted.Instrument (forkIO,myThreadId,labelThread,ThreadId) |
70 | #else | 69 | #else |
71 | import Control.Concurrent.Lifted (forkIO,myThreadId) | 70 | import Control.Concurrent.Lifted (forkIO,myThreadId,ThreadId) |
72 | import GHC.Conc (labelThread) | 71 | import GHC.Conc (labelThread) |
73 | #endif | 72 | #endif |
74 | import Control.Concurrent.STM | 73 | import Control.Concurrent.STM |
@@ -90,6 +89,7 @@ import Data.Conduit.Blaze (builderToByteStringFlush) | |||
90 | #endif | 89 | #endif |
91 | import Control.Monad.Catch (MonadThrow) | 90 | import Control.Monad.Catch (MonadThrow) |
92 | 91 | ||
92 | import DNSCache (withPort) | ||
93 | import qualified Text.XML.Stream.Render as XML hiding (content) | 93 | import qualified Text.XML.Stream.Render as XML hiding (content) |
94 | import qualified Text.XML.Stream.Parse as XML | 94 | import qualified Text.XML.Stream.Parse as XML |
95 | import Data.XML.Types as XML | 95 | import Data.XML.Types as XML |
@@ -1250,9 +1250,9 @@ slotsToSource slots nesting lastStanza needsFlush rdone = | |||
1250 | ,readTMVar rdone >> return (return ()) | 1250 | ,readTMVar rdone >> return (return ()) |
1251 | ] | 1251 | ] |
1252 | 1252 | ||
1253 | forkConnection :: Server SockAddr ConnectionData releaseKey XML.Event | 1253 | forkConnection :: Server PeerAddress ConnectionData releaseKey XML.Event |
1254 | -> XMPPServerParameters | 1254 | -> XMPPServerParameters |
1255 | -> SockAddr -- SockAddr (remote for peer, local for client) | 1255 | -> PeerAddress -- SockAddr (XXX(what?): remote for peer, local for client) |
1256 | -> ConnectionData | 1256 | -> ConnectionData |
1257 | -> FlagCommand | 1257 | -> FlagCommand |
1258 | -> Source IO XML.Event | 1258 | -> Source IO XML.Event |
@@ -1262,12 +1262,12 @@ forkConnection :: Server SockAddr ConnectionData releaseKey XML.Event | |||
1262 | forkConnection sv xmpp saddr cdta pingflag src snk stanzas = do | 1262 | forkConnection sv xmpp saddr cdta pingflag src snk stanzas = do |
1263 | let auxAddr = cdAddr cdta | 1263 | let auxAddr = cdAddr cdta |
1264 | clientOrServer@(namespace,tellmyname,telltheirname,_) = case auxAddr of | 1264 | clientOrServer@(namespace,tellmyname,telltheirname,_) = case auxAddr of |
1265 | Right _ -> ("jabber:client", xmppTellMyNameToClient xmpp (ClientAddress saddr) | 1265 | Right _ -> ("jabber:client", xmppTellMyNameToClient xmpp (ClientAddress $ peerAddress saddr) |
1266 | , xmppTellClientHisName xmpp (ClientAddress saddr) | 1266 | , xmppTellClientHisName xmpp (ClientAddress $ peerAddress saddr) |
1267 | , ClientOrigin (ClientAddress saddr)) | 1267 | , ClientOrigin (ClientAddress $ peerAddress saddr)) |
1268 | Left laddr -> ("jabber:server", xmppTellMyNameToPeer xmpp laddr | 1268 | Left laddr -> ("jabber:server", xmppTellMyNameToPeer xmpp laddr |
1269 | , xmppTellPeerHisName xmpp (PeerAddress saddr) | 1269 | , xmppTellPeerHisName xmpp saddr |
1270 | , PeerOrigin (PeerAddress saddr)) | 1270 | , PeerOrigin saddr) |
1271 | me <- tellmyname | 1271 | me <- tellmyname |
1272 | rdone <- atomically newEmptyTMVar | 1272 | rdone <- atomically newEmptyTMVar |
1273 | let isStarter (Left _) = True | 1273 | let isStarter (Left _) = True |
@@ -1427,7 +1427,7 @@ data PeerState | |||
1427 | | PeerConnected (TChan Stanza) | 1427 | | PeerConnected (TChan Stanza) |
1428 | -} | 1428 | -} |
1429 | 1429 | ||
1430 | peerKey :: SocketLike sock => Maybe SockAddr -> sock -> IO (SockAddr,ConnectionData) | 1430 | peerKey :: SocketLike sock => Maybe SockAddr -> sock -> IO (PeerAddress,ConnectionData) |
1431 | peerKey bind_addr sock = do | 1431 | peerKey bind_addr sock = do |
1432 | laddr <- getSocketName sock | 1432 | laddr <- getSocketName sock |
1433 | raddr <- | 1433 | raddr <- |
@@ -1441,13 +1441,13 @@ peerKey bind_addr sock = do | |||
1441 | -- to distinguish fake address connection keys. | 1441 | -- to distinguish fake address connection keys. |
1442 | return p | 1442 | return p |
1443 | rname <- atomically $ newTVar Nothing | 1443 | rname <- atomically $ newTVar Nothing |
1444 | return $ ( raddr `withPort` peerport | 1444 | return $ ( PeerAddress $ raddr `withPort` peerport |
1445 | , ConnectionData { cdAddr = Left (Local laddr) | 1445 | , ConnectionData { cdAddr = Left (Local laddr) |
1446 | , cdType = XMPP | 1446 | , cdType = XMPP |
1447 | , cdProfile = "." | 1447 | , cdProfile = "." |
1448 | , cdRemoteName = rname } ) | 1448 | , cdRemoteName = rname } ) |
1449 | 1449 | ||
1450 | clientKey :: SocketLike sock => sock -> IO (SockAddr,ConnectionData) | 1450 | clientKey :: SocketLike sock => sock -> IO (PeerAddress,ConnectionData) |
1451 | clientKey sock = do | 1451 | clientKey sock = do |
1452 | laddr <- getSocketName sock | 1452 | laddr <- getSocketName sock |
1453 | raddr <- getPeerName sock | 1453 | raddr <- getPeerName sock |
@@ -1457,27 +1457,13 @@ clientKey sock = do | |||
1457 | , "is using port zero. This could interfere" | 1457 | , "is using port zero. This could interfere" |
1458 | , "with Tox peer sessions." ] | 1458 | , "with Tox peer sessions." ] |
1459 | rname <- atomically $ newTVar Nothing | 1459 | rname <- atomically $ newTVar Nothing |
1460 | return $ ( laddr | 1460 | return $ ( PeerAddress laddr |
1461 | , ConnectionData { cdAddr = Right (Remote raddr) | 1461 | , ConnectionData { cdAddr = Right (Remote raddr) |
1462 | , cdType = XMPP | 1462 | , cdType = XMPP |
1463 | , cdProfile = "." | 1463 | , cdProfile = "." |
1464 | , cdRemoteName = rname } ) | 1464 | , cdRemoteName = rname } ) |
1465 | 1465 | ||
1466 | 1466 | ||
1467 | data Uniq24 = Uniq24 !Word64 !Word64 !Word64 | ||
1468 | deriving (Eq,Ord,Show) | ||
1469 | |||
1470 | uniqueAsKey :: Uniq24 -> SockAddr | ||
1471 | uniqueAsKey (Uniq24 x y z) = SockAddrInet6 (fromIntegral 0) a bcde f | ||
1472 | where | ||
1473 | a = fromIntegral (x `shiftR` 32) | ||
1474 | b = fromIntegral x | ||
1475 | c = fromIntegral (y `shiftR` 32) | ||
1476 | d = fromIntegral y | ||
1477 | e = fromIntegral (z `shiftR` 32) | ||
1478 | f = fromIntegral z | ||
1479 | bcde = (b,c,d,e) | ||
1480 | |||
1481 | xmlifyRosterItems :: Monad m => Set Text -> Text -> Set Text -> ConduitM i Event m () | 1467 | xmlifyRosterItems :: Monad m => Set Text -> Text -> Set Text -> ConduitM i Event m () |
1482 | xmlifyRosterItems solicited stype set = mapM_ item (Set.toList set) | 1468 | xmlifyRosterItems solicited stype set = mapM_ item (Set.toList set) |
1483 | where | 1469 | where |
@@ -1544,10 +1530,10 @@ sendRoster query xmpp clientKey replyto = do | |||
1544 | -} | 1530 | -} |
1545 | 1531 | ||
1546 | 1532 | ||
1547 | socketFromKey :: Server SockAddr ConnectionData releaseKey XML.Event -> ClientAddress -> IO (Remote SockAddr) | 1533 | socketFromKey :: Server PeerAddress ConnectionData releaseKey XML.Event -> ClientAddress -> IO (Remote SockAddr) |
1548 | socketFromKey sv (ClientAddress addr) = do | 1534 | socketFromKey sv (ClientAddress addr) = do |
1549 | map <- atomically $ readTVar (conmap sv) | 1535 | map <- atomically $ readTVar (conmap sv) |
1550 | let mcd = Map.lookup addr map | 1536 | let mcd = Map.lookup (PeerAddress addr) map |
1551 | oops = Remote addr -- No connection data, so using incorrect address. | 1537 | oops = Remote addr -- No connection data, so using incorrect address. |
1552 | case mcd of | 1538 | case mcd of |
1553 | Nothing -> return oops | 1539 | Nothing -> return oops |
@@ -1711,8 +1697,8 @@ makeErrorStanza stanza = do | |||
1711 | ] | 1697 | ] |
1712 | 1698 | ||
1713 | monitor :: | 1699 | monitor :: |
1714 | Server SockAddr ConnectionData releaseKey XML.Event | 1700 | Server PeerAddress ConnectionData releaseKey XML.Event |
1715 | -> ConnectionParameters SockAddr ConnectionData | 1701 | -> ConnectionParameters PeerAddress ConnectionData |
1716 | -> XMPPServerParameters | 1702 | -> XMPPServerParameters |
1717 | -> IO b | 1703 | -> IO b |
1718 | monitor sv params xmpp = do | 1704 | monitor sv params xmpp = do |
@@ -1726,15 +1712,19 @@ monitor sv params xmpp = do | |||
1726 | Connection pingflag xsrc xsnk | 1712 | Connection pingflag xsrc xsnk |
1727 | -> do wlog $ tomsg addr "Connection" | 1713 | -> do wlog $ tomsg addr "Connection" |
1728 | outs <- forkConnection sv xmpp addr u pingflag xsrc xsnk stanzas | 1714 | outs <- forkConnection sv xmpp addr u pingflag xsrc xsnk stanzas |
1729 | xmppNewConnection xmpp addr u outs | 1715 | -- /addr/ may be a peer or a client. So we'll strip off |
1716 | -- the PeerAddress constructor before exposing it. | ||
1717 | xmppNewConnection xmpp (peerAddress addr) u outs | ||
1730 | ConnectFailure addr | 1718 | ConnectFailure addr |
1731 | -> do return () -- wlog $ tomsg k "ConnectFailure" | 1719 | -> do return () -- wlog $ tomsg k "ConnectFailure" |
1732 | EOF -> do wlog $ tomsg addr "EOF" | 1720 | EOF -> do wlog $ tomsg addr "EOF" |
1733 | xmppEOF xmpp addr u | 1721 | -- /addr/ may be a peer or a client. So we'll strip off |
1722 | -- the PeerAddress constructor before exposing it. | ||
1723 | xmppEOF xmpp (peerAddress addr) u | ||
1734 | HalfConnection In | 1724 | HalfConnection In |
1735 | -> do wlog $ tomsg addr "ReadOnly" | 1725 | -> do wlog $ tomsg addr "ReadOnly" |
1736 | case cdAddr u of | 1726 | case cdAddr u of |
1737 | Left (Local _) -> control sv (Connect addr params) | 1727 | Left (Local _) -> control sv (Connect (peerAddress addr) params) |
1738 | _ -> return () -- Don't call-back client connections. | 1728 | _ -> return () -- Don't call-back client connections. |
1739 | HalfConnection Out | 1729 | HalfConnection Out |
1740 | -> do wlog $ tomsg addr "WriteOnly" | 1730 | -> do wlog $ tomsg addr "WriteOnly" |
@@ -1912,55 +1902,66 @@ classifyConnection saddr dta = case cdAddr dta of | |||
1912 | 1902 | ||
1913 | data XMPPServer | 1903 | data XMPPServer |
1914 | = forall releaseKey. | 1904 | = forall releaseKey. |
1915 | XMPPServer { _xmpp_sv :: Server SockAddr ConnectionData releaseKey XML.Event | 1905 | XMPPServer { _xmpp_sv :: Server PeerAddress ConnectionData releaseKey XML.Event |
1916 | , _xmpp_peer_params :: ConnectionParameters SockAddr ConnectionData | 1906 | -- ^ Internally, we're using PeerAddress for both clients |
1907 | -- and peers. For the external interface, we mark client | ||
1908 | -- addresses as 'ClientAddress' and not 'PeerAddress'. | ||
1909 | , _xmpp_man :: Connection.Manager TCPStatus Text | ||
1910 | , _xmpp_peer_params :: ConnectionParameters PeerAddress ConnectionData | ||
1911 | , _xmpp_peer_bind :: SockAddr | ||
1917 | } | 1912 | } |
1918 | 1913 | ||
1919 | grokPeer :: XMPPServer -> SockAddr -> (SockAddr, ConnectionParameters SockAddr ConnectionData, Miliseconds) | ||
1920 | grokPeer sv addr = (addr, _xmpp_peer_params sv, 10000) | ||
1921 | |||
1922 | |||
1923 | xmppConnections :: XMPPServer -> IO (Connection.Manager TCPStatus Text) | 1914 | xmppConnections :: XMPPServer -> IO (Connection.Manager TCPStatus Text) |
1924 | xmppConnections xsv@XMPPServer{_xmpp_sv=sv} = tcpManager (grokPeer xsv) (Just . Text.pack) resolve sv | 1915 | xmppConnections xsv@XMPPServer{_xmpp_man = m} = return m |
1925 | where | ||
1926 | resolve :: Text -> IO (Maybe SockAddr) | ||
1927 | resolve hostname = listToMaybe . map (\(PeerAddress addr) -> addr) <$> resolvePeer hostname | ||
1928 | 1916 | ||
1929 | xmppEventChannel :: XMPPServer -> TChan ((SockAddr, ConnectionData), ConnectionEvent Event) | 1917 | xmppEventChannel :: XMPPServer -> TChan ((PeerAddress, ConnectionData), ConnectionEvent Event) |
1930 | xmppEventChannel XMPPServer{_xmpp_sv=sv} = serverEvent sv | 1918 | xmppEventChannel XMPPServer{_xmpp_sv=sv} = serverEvent sv |
1931 | 1919 | ||
1932 | quitXmpp :: XMPPServer -> IO () | 1920 | quitXmpp :: XMPPServer -> IO () |
1933 | quitXmpp XMPPServer{_xmpp_sv=sv} = control sv Quit | 1921 | quitXmpp XMPPServer{_xmpp_sv=sv} = control sv Quit |
1934 | 1922 | ||
1935 | xmppServer :: MonadIO m => | 1923 | xmppServer :: MonadIO m => Allocate releaseKey m |
1936 | Allocate releaseKey m -> XMPPServerParameters -> m XMPPServer | 1924 | -> Maybe SockAddr -- ^ Listen address for server-to-server protocol. |
1937 | xmppServer allocate xmpp = do | 1925 | -> m XMPPServer |
1926 | xmppServer allocate bind_addr = do | ||
1938 | sv <- server allocate xmlStream | 1927 | sv <- server allocate xmlStream |
1939 | -- some fuzz helps avoid simultaneity | 1928 | liftIO $ do |
1940 | pingfuzz <- liftIO $ do | ||
1941 | gen <- System.Random.getStdGen | 1929 | gen <- System.Random.getStdGen |
1930 | peer_bind <- maybe (getBindAddress "5269" True) return bind_addr | ||
1942 | let (r,gen') = System.Random.next gen | 1931 | let (r,gen') = System.Random.next gen |
1943 | return $ r `mod` 2000 -- maximum 2 seconds of fuzz | 1932 | fuzz = r `mod` 2000 -- maximum 2 seconds of ping fuzz |
1944 | liftIO . wlog $ "pingfuzz = " ++ show pingfuzz | 1933 | peer_params :: ConnectionParameters PeerAddress ConnectionData |
1945 | let peer_params = (connectionDefaults $ peerKey $ xmppPeerBind xmpp) | 1934 | peer_params = (connectionDefaults $ peerKey $ Just peer_bind) |
1946 | { pingInterval = 15000 + pingfuzz | 1935 | { pingInterval = 15000 + fuzz |
1947 | , timeout = 2000 | 1936 | , timeout = 2000 |
1948 | , duplex = False } | 1937 | , duplex = False } |
1949 | client_params = (connectionDefaults clientKey) | 1938 | tcp <- tcpManager (\(PeerAddress addr) -> (addr, peer_params, 10000)) sv |
1950 | { pingInterval = 0 | 1939 | return XMPPServer { _xmpp_sv = sv |
1951 | , timeout = 0 | 1940 | , _xmpp_man = tcp |
1941 | , _xmpp_peer_params = peer_params | ||
1942 | , _xmpp_peer_bind = peer_bind | ||
1952 | } | 1943 | } |
1953 | liftIO $ do | 1944 | |
1954 | forkIO $ do | 1945 | forkXmpp :: MonadIO m => XMPPServer -> XMPPServerParameters -> m ThreadId |
1955 | myThreadId >>= flip labelThread ("XMPP.monitor") | 1946 | forkXmpp XMPPServer { _xmpp_sv = sv |
1956 | monitor sv peer_params xmpp | 1947 | , _xmpp_peer_params = peer_params |
1957 | dput XMisc $ "Starting peer listen" | 1948 | , _xmpp_peer_bind = peer_bind |
1958 | peer_bind <- maybe (getBindAddress "5269" True) return $ xmppPeerBind xmpp | 1949 | } |
1959 | control sv (Listen peer_bind peer_params) | 1950 | xmpp = liftIO $ do |
1960 | dput XMisc $ "Starting client listen" | 1951 | let client_params :: ConnectionParameters PeerAddress ConnectionData |
1961 | client_bind <- maybe (getBindAddress "5222" True) return $ xmppClientBind xmpp | 1952 | client_params = (connectionDefaults clientKey) |
1962 | control sv (Listen client_bind client_params) | 1953 | { pingInterval = 0 |
1963 | return XMPPServer { _xmpp_sv = sv, _xmpp_peer_params = peer_params } | 1954 | , timeout = 0 |
1955 | } | ||
1956 | mt <- forkIO $ do myThreadId >>= flip labelThread ("XMPP.monitor") | ||
1957 | monitor sv peer_params xmpp | ||
1958 | dput XMisc $ "Starting peer listen" | ||
1959 | control sv (Listen peer_bind peer_params) | ||
1960 | dput XMisc $ "Starting client listen" | ||
1961 | client_bind <- maybe (getBindAddress "5222" True) return $ xmppClientBind xmpp | ||
1962 | control sv (Listen client_bind client_params) | ||
1963 | return mt | ||
1964 | |||
1964 | 1965 | ||
1965 | #if MIN_VERSION_stm(2,4,0) | 1966 | #if MIN_VERSION_stm(2,4,0) |
1966 | #else | 1967 | #else |