summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2014-02-18 01:05:41 -0500
committerjoe <joe@jerkface.net>2014-02-18 01:05:41 -0500
commitd4c8249985f2aa4895a9eb844a357a885c87c749 (patch)
treea2b5ef7a0db165db3c8f1d8bd7b494b1b9dc17e3
parente34385a64f8d0ec431023001c9619994601df0a9 (diff)
end to end messaging
-rw-r--r--Presence/XMPPServer.hs65
-rw-r--r--xmppServer.hs119
2 files changed, 151 insertions, 33 deletions
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs
index eb680002..631f97c3 100644
--- a/Presence/XMPPServer.hs
+++ b/Presence/XMPPServer.hs
@@ -15,6 +15,7 @@ module XMPPServer
15 , peerKeyToResolvedName 15 , peerKeyToResolvedName
16 , addrToText 16 , addrToText
17 , sendModifiedStanzaToPeer 17 , sendModifiedStanzaToPeer
18 , sendModifiedStanzaToClient
18 ) where 19 ) where
19import Debug.Trace 20import Debug.Trace
20import Control.Monad.Trans.Resource (runResourceT) 21import Control.Monad.Trans.Resource (runResourceT)
@@ -147,7 +148,7 @@ data XMPPServerParameters =
147 , xmppTellMyNameToPeer :: SockAddr -> IO Text 148 , xmppTellMyNameToPeer :: SockAddr -> IO Text
148 , xmppTellClientHisName :: ConnectionKey -> IO Text 149 , xmppTellClientHisName :: ConnectionKey -> IO Text
149 , xmppTellPeerHisName :: ConnectionKey -> IO Text 150 , xmppTellPeerHisName :: ConnectionKey -> IO Text
150 , xmppNewConnection :: ConnectionKey -> TChan Stanza -> IO () 151 , xmppNewConnection :: ConnectionKey -> SockAddr -> TChan Stanza -> IO ()
151 , xmppEOF :: ConnectionKey -> IO () 152 , xmppEOF :: ConnectionKey -> IO ()
152 , xmppRosterBuddies :: ConnectionKey -> IO [Text] 153 , xmppRosterBuddies :: ConnectionKey -> IO [Text]
153 , xmppRosterSubscribers :: ConnectionKey -> IO [Text] 154 , xmppRosterSubscribers :: ConnectionKey -> IO [Text]
@@ -181,9 +182,10 @@ peerKeyToText (ClientKey { localAddress=addr }) = "ErrorClIeNt0"
181peerKeyToResolvedName :: ConnectionKey -> IO Text 182peerKeyToResolvedName :: ConnectionKey -> IO Text
182peerKeyToResolvedName k@(ClientKey { localAddress=addr }) = return "ErrorClIeNt1" 183peerKeyToResolvedName k@(ClientKey { localAddress=addr }) = return "ErrorClIeNt1"
183peerKeyToResolvedName k@(PeerKey { callBackAddress=addr }) = do 184peerKeyToResolvedName k@(PeerKey { callBackAddress=addr }) = do
184 ent <- getHostByAddr addr -- AF_UNSPEC addr 185 mname <- handleIO_ (return Nothing) $ do
185 let names = BSD.hostName ent : BSD.hostAliases ent 186 ent <- getHostByAddr addr -- AF_UNSPEC addr
186 mname = listToMaybe names 187 let names = BSD.hostName ent : BSD.hostAliases ent
188 return $ listToMaybe names
187 return $ maybe (peerKeyToText k) Text.pack mname 189 return $ maybe (peerKeyToText k) Text.pack mname
188 190
189 191
@@ -278,6 +280,17 @@ sendModifiedStanzaToPeer stanza chan = do
278 where 280 where
279 c = stanzaToConduit stanza =$= swapNamespace "jabber:client" "jabber:server" =$= fixHeaders stanza 281 c = stanzaToConduit stanza =$= swapNamespace "jabber:client" "jabber:server" =$= fixHeaders stanza
280 282
283sendModifiedStanzaToClient stanza chan = do
284 (echan,clsrs,quitvar) <- conduitToChan c
285 ioWriteChan chan
286 stanza { stanzaChan = echan
287 , stanzaClosers = clsrs
288 , stanzaInterrupt = quitvar
289 -- TODO id? origin?
290 }
291 where
292 c = stanzaToConduit stanza =$= swapNamespace "jabber:server" "jabber:client" =$= fixHeaders stanza
293
281-- id,to, and from are taken as-is from reply list 294-- id,to, and from are taken as-is from reply list
282sendReply donevar stype reply replychan = do 295sendReply donevar stype reply replychan = do
283 if null reply then return () 296 if null reply then return ()
@@ -532,6 +545,7 @@ xmppInbound sv xmpp k laddr pingflag src stanzas output donevar = doNestingXML $
532 pongfrom = maybe me id mto 545 pongfrom = maybe me id mto
533 pong = makePong namespace mid pongto pongfrom 546 pong = makePong namespace mid pongto pongfrom
534 sendReply donevar Pong pong output 547 sendReply donevar Pong pong output
548#ifdef PINGNOISE
535 -- TODO: Remove this, it is only to generate a debug print 549 -- TODO: Remove this, it is only to generate a debug print
536 ioWriteChan stanzas Stanza 550 ioWriteChan stanzas Stanza
537 { stanzaType = Ping 551 { stanzaType = Ping
@@ -543,6 +557,7 @@ xmppInbound sv xmpp k laddr pingflag src stanzas output donevar = doNestingXML $
543 , stanzaInterrupt = donevar 557 , stanzaInterrupt = donevar
544 , stanzaOrigin = NetworkOrigin k output 558 , stanzaOrigin = NetworkOrigin k output
545 } 559 }
560#endif
546 stype -> ioWriteChan stanzas Stanza 561 stype -> ioWriteChan stanzas Stanza
547 { stanzaType = stype 562 { stanzaType = stype
548 , stanzaId = mid 563 , stanzaId = mid
@@ -745,10 +760,20 @@ forkConnection sv xmpp k laddr pingflag src snk stanzas = do
745 fix $ \loop -> do 760 fix $ \loop -> do
746 what <- atomically $ foldr1 orElse 761 what <- atomically $ foldr1 orElse
747 [readTChan output >>= \stanza -> return $ do 762 [readTChan output >>= \stanza -> return $ do
748 dup <- atomically $ cloneStanza stanza 763#ifndef PINGNOISE
749 stanzaToConduit dup $$ prettyPrint $ case k of 764 let notping f = case stanzaType stanza of Pong -> return ()
750 ClientKey {} -> "C<-" <> bshow (stanzaType dup) <> " " 765 _ -> f
751 PeerKey {} -> "P<-" <> bshow (stanzaType dup) <> " " 766#else
767 let notping f = f
768#endif
769 notping $ do
770 dup <- atomically $ cloneStanza stanza
771 let typ = Strict8.pack $ c ++ "<-"++(concat . take 1 . words $ show (stanzaType dup))++" "
772 c = case k of
773 ClientKey {} -> "C"
774 PeerKey {} -> "P"
775 wlog ""
776 stanzaToConduit dup $$ prettyPrint typ
752 stanzaToConduit stanza 777 stanzaToConduit stanza
753 $$ awaitForever 778 $$ awaitForever
754 $ liftIO . atomically . Slotted.push slots Nothing 779 $ liftIO . atomically . Slotted.push slots Nothing
@@ -762,10 +787,12 @@ forkConnection sv xmpp k laddr pingflag src snk stanzas = do
762 ping = makePing namespace mid to from 787 ping = makePing namespace mid to from
763 mapM_ (atomically . Slotted.push slots (Just $ PingSlot)) 788 mapM_ (atomically . Slotted.push slots (Just $ PingSlot))
764 ping 789 ping
790#ifdef PINGNOISE
765 wlog "" 791 wlog ""
766 CL.sourceList ping $$ prettyPrint $ case k of 792 CL.sourceList ping $$ prettyPrint $ case k of
767 ClientKey {} -> "C<-Ping" 793 ClientKey {} -> "C<-Ping"
768 PeerKey {} -> "P<-Ping " 794 PeerKey {} -> "P<-Ping "
795#endif
769 loop 796 loop
770 ,readTMVar rdone >> return (return ()) 797 ,readTMVar rdone >> return (return ())
771 ] 798 ]
@@ -912,7 +939,7 @@ monitor sv params xmpp = do
912 wlog $ tomsg k "Connection" 939 wlog $ tomsg k "Connection"
913 let (xsrc,xsnk) = xmlStream conread conwrite 940 let (xsrc,xsnk) = xmlStream conread conwrite
914 outs <- forkConnection sv xmpp k u pingflag xsrc xsnk stanzas 941 outs <- forkConnection sv xmpp k u pingflag xsrc xsnk stanzas
915 xmppNewConnection xmpp k outs 942 xmppNewConnection xmpp k u outs
916 return () 943 return ()
917 ConnectFailure addr -> return () -- wlog $ tomsg k "ConnectFailure" 944 ConnectFailure addr -> return () -- wlog $ tomsg k "ConnectFailure"
918 EOF -> do wlog $ tomsg k "EOF" 945 EOF -> do wlog $ tomsg k "EOF"
@@ -924,7 +951,17 @@ monitor sv params xmpp = do
924 RequiresPing -> return () -- wlog $ tomsg k "RequiresPing" 951 RequiresPing -> return () -- wlog $ tomsg k "RequiresPing"
925 _ -> return () 952 _ -> return ()
926 , readTChan stanzas >>= \stanza -> return $ do 953 , readTChan stanzas >>= \stanza -> return $ do
954 dup <- case stanzaType stanza of
955 Message {} -> do
956 dup <- atomically $ cloneStanza stanza -- dupped so we can make debug print
957 return dup
958 _ -> return stanza
927 forkIO $ do 959 forkIO $ do
960 case stanzaType stanza of
961 Message {} -> do
962 let fail = wlog $ "Failed delivery id="++show (stanzaId stanza) -- TODO
963 xmppDeliverMessage xmpp fail stanza
964 _ -> return ()
928 case stanzaOrigin stanza of 965 case stanzaOrigin stanza of
929 NetworkOrigin k@(ClientKey {}) replyto -> 966 NetworkOrigin k@(ClientKey {}) replyto ->
930 case stanzaType stanza of 967 case stanzaType stanza of
@@ -940,10 +977,6 @@ monitor sv params xmpp = do
940 RequestRoster -> do 977 RequestRoster -> do
941 sendRoster stanza xmpp replyto 978 sendRoster stanza xmpp replyto
942 xmppSubscribeToRoster xmpp k 979 xmppSubscribeToRoster xmpp k
943 Message {} -> do
944 let fail = wlog $ "Failed delivery id="++show (stanzaId stanza) -- TODO
945 stanza2 <- atomically $ cloneStanza stanza
946 xmppDeliverMessage xmpp fail stanza
947 PresenceStatus {} -> do 980 PresenceStatus {} -> do
948 xmppInformClientPresence xmpp k stanza 981 xmppInformClientPresence xmpp k stanza
949 UnrecognizedQuery query -> do 982 UnrecognizedQuery query -> do
@@ -953,7 +986,11 @@ monitor sv params xmpp = do
953 _ -> return () 986 _ -> return ()
954 _ -> return () 987 _ -> return ()
955 -- We need to clone in the case the stanza is passed on as for Message. 988 -- We need to clone in the case the stanza is passed on as for Message.
956 dup <- atomically $ cloneStanza stanza 989#ifndef PINGNOISE
990 let notping f = case stanzaType stanza of Pong -> return ()
991 _ -> f
992 notping $ do
993#endif
957 let typ = Strict8.pack $ c ++ "->"++(concat . take 1 . words $ show (stanzaType stanza))++" " 994 let typ = Strict8.pack $ c ++ "->"++(concat . take 1 . words $ show (stanzaType stanza))++" "
958 c = case stanzaOrigin stanza of 995 c = case stanzaOrigin stanza of
959 LocalPeer -> "*" 996 LocalPeer -> "*"
diff --git a/xmppServer.hs b/xmppServer.hs
index 69b6cec5..7b352b8a 100644
--- a/xmppServer.hs
+++ b/xmppServer.hs
@@ -10,7 +10,7 @@ import Network.Socket
10 , getAddrInfo 10 , getAddrInfo
11 , defaultHints 11 , defaultHints
12 , addrFlags 12 , addrFlags
13 , AddrInfoFlag(AI_CANONNAME,AI_V4MAPPED) 13 , AddrInfoFlag(AI_CANONNAME,AI_V4MAPPED,AI_NUMERICHOST)
14 , SockAddr(..) 14 , SockAddr(..)
15 ) 15 )
16import System.Endian (fromBE32) 16import System.Endian (fromBE32)
@@ -71,9 +71,10 @@ data ClientState = ClientState
71 71
72data PresenceState = PresenceState 72data PresenceState = PresenceState
73 { clients :: TVar (Map ConnectionKey ClientState) 73 { clients :: TVar (Map ConnectionKey ClientState)
74 , clientsByUser :: TVar (Map Text (ConnectionKey,ClientState)) -- TODO: should be list
74 , associatedPeers :: TVar (Map SockAddr ()) 75 , associatedPeers :: TVar (Map SockAddr ())
75 , server :: TMVar XMPPServer 76 , server :: TMVar XMPPServer
76 , writeTos :: TVar (Map ConnectionKey (TChan Stanza)) 77 , writeTos :: TVar (Map ConnectionKey Conn)
77 } 78 }
78 79
79 80
@@ -84,9 +85,14 @@ resolvePeer :: Text -> IO [SockAddr]
84resolvePeer addrtext = do 85resolvePeer addrtext = do
85 fmap (map $ make6mapped4 . addrAddress) $ 86 fmap (map $ make6mapped4 . addrAddress) $
86 getAddrInfo (Just $ defaultHints { addrFlags = [ AI_CANONNAME, AI_V4MAPPED ]}) 87 getAddrInfo (Just $ defaultHints { addrFlags = [ AI_CANONNAME, AI_V4MAPPED ]})
87 (Just $ Text.unpack addrtext) 88 (Just $ Text.unpack $ strip_brackets addrtext)
88 (Just "5269") 89 (Just "5269")
89 90
91strip_brackets s =
92 case Text.uncons s of
93 Just ('[',t) -> Text.takeWhile (/=']') t
94 _ -> s
95
90 96
91getConsolePids :: PresenceState -> IO [(Text,ProcessID)] 97getConsolePids :: PresenceState -> IO [(Text,ProcessID)]
92getConsolePids state = do 98getConsolePids state = do
@@ -109,8 +115,10 @@ chooseResourceName state k addr desired = do
109 , clientUser = user 115 , clientUser = user
110 , clientPid = pid } 116 , clientPid = pid }
111 117
112 atomically $ 118 atomically $ do
113 modifyTVar' (clients state) $ Map.insert k client 119 modifyTVar' (clients state) $ Map.insert k client
120 modifyTVar' (clientsByUser state) $ Map.insert (clientUser client) (k,client)
121
114 localJID (clientUser client) (clientResource client) 122 localJID (clientUser client) (clientResource client)
115 123
116 where 124 where
@@ -174,11 +182,58 @@ rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited
174rosterGetOthers = rosterGetStuff ConfigFiles.getOthers 182rosterGetOthers = rosterGetStuff ConfigFiles.getOthers
175rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers 183rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers
176 184
177newConn state k outchan = 185data Conn = Conn { connChan :: TChan Stanza
178 atomically $ modifyTVar' (writeTos state) $ Map.insert k outchan 186 , auxAddr :: SockAddr }
187
188newConn state k addr outchan =
189 atomically $ modifyTVar' (writeTos state)
190 $ Map.insert k Conn { connChan = outchan
191 , auxAddr = addr }
179 192
180eofConn state k = atomically $ modifyTVar' (writeTos state) $ Map.delete k 193eofConn state k = atomically $ modifyTVar' (writeTos state) $ Map.delete k
181 194
195rewriteJIDForClient1:: Text -> IO (Maybe ((Maybe Text,Text,Maybe Text),SockAddr))
196rewriteJIDForClient1 jid = do
197 let (n,h,r) = splitJID jid
198 maddr <- fmap listToMaybe $ resolvePeer h
199 flip (maybe $ return Nothing) maddr $ \addr -> do
200 h' <- peerKeyToResolvedName (PeerKey addr)
201 return $ Just ((n,h',r), addr)
202
203parseAddress :: Text -> IO (Maybe SockAddr)
204parseAddress addr_str = do
205 info <- getAddrInfo (Just $ defaultHints { addrFlags = [ AI_NUMERICHOST ] })
206 (Just . Text.unpack $ addr_str)
207 (Just "0")
208 return . listToMaybe $ map addrAddress info
209
210todo = error "Unimplemented"
211
212
213-- | for example: 2001-db8-85a3-8d3-1319-8a2e-370-7348.ipv6-literal.net
214ip6literal :: Text -> Text
215ip6literal addr = Text.map dash addr <> ".ipv6-literal.net"
216 where
217 dash ':' = '-'
218 dash x = x
219
220withPort (SockAddrInet _ a) port = SockAddrInet (toEnum port) a
221withPort (SockAddrInet6 _ a b c) port = SockAddrInet6 (toEnum port) a b c
222
223-- | The given address is taken to be the local address for the socket this JID
224-- came in on. The returned JID parts are suitable for unsplitJID to create a
225-- valid JID for communicating to a client. The returned Bool is True when the
226-- host part refers to this local host (i.e. it equals the given SockAddr).
227rewriteJIDForClient :: SockAddr -> Text -> IO (Bool,(Maybe Text,Text,Maybe Text))
228rewriteJIDForClient laddr jid = do
229 let (n,h,r) = splitJID jid
230 maddr <- parseAddress (strip_brackets h)
231 flip (maybe $ return (False,(n,ip6literal h,r))) maddr $ \addr -> do
232 let mine = laddr `withPort` 0 == addr `withPort` 0
233 h' <- if mine then textHostName
234 else peerKeyToResolvedName (PeerKey addr)
235 return (mine,(n,h',r))
236
182rewriteJIDForPeer :: Text -> IO (Maybe (Text,SockAddr)) 237rewriteJIDForPeer :: Text -> IO (Maybe (Text,SockAddr))
183rewriteJIDForPeer jid = do 238rewriteJIDForPeer jid = do
184 let (n,h,r) = splitJID jid 239 let (n,h,r) = splitJID jid
@@ -188,28 +243,54 @@ rewriteJIDForPeer jid = do
188 to' = unsplitJID (n,h',r) 243 to' = unsplitJID (n,h',r)
189 in (to',addr) 244 in (to',addr)
190 245
191deliverMessage state fail msg = do 246deliverMessage state fail msg =
192 mto <- do 247 case stanzaOrigin msg of
193 flip (maybe $ return Nothing) (stanzaTo msg) $ \to -> do 248 NetworkOrigin senderk@(ClientKey {}) _ -> do
194 rewriteJIDForPeer to 249 mto <- do
195 flip (maybe fail) mto $ \(to',addr) -> do 250 flip (maybe $ return Nothing) (stanzaTo msg) $ \to -> do
196 from' <- do 251 rewriteJIDForPeer to
197 flip (maybe $ return Nothing) (stanzaFrom msg) $ \from -> do 252 flip (maybe fail) mto $ \(to',addr) -> do
198 m <- rewriteJIDForPeer from 253 let k = PeerKey addr
199 return $ fmap fst m 254 chans <- atomically $ readTVar (writeTos state)
200 let k = PeerKey addr 255 flip (maybe fail) (Map.lookup k chans) $ \(Conn { connChan=chan
201 chans <- atomically $ readTVar (writeTos state) 256 , auxAddr=laddr }) -> do
202 flip (maybe fail) (Map.lookup k chans) $ \chan -> do 257 (n,r) <- forClient state senderk (return (Nothing,Nothing))
203 sendModifiedStanzaToPeer (msg { stanzaTo=Just to', stanzaFrom=from' }) chan 258 $ \c -> return (Just (clientUser c), Just (clientResource c))
259 -- original 'from' address is discarded.
260 let from' = unsplitJID (n,addrToText laddr,r)
261 sendModifiedStanzaToPeer (msg { stanzaTo=Just to', stanzaFrom=Just from' }) chan
262 NetworkOrigin senderk@(PeerKey {}) _ -> do
263 chans <- atomically $ readTVar (writeTos state)
264 flip (maybe fail) (Map.lookup senderk chans)
265 $ \(Conn { connChan=sender_chan
266 , auxAddr=laddr }) -> do
267 flip (maybe fail) (stanzaTo msg) $ \to -> do
268 (mine,(n,h,r)) <- rewriteJIDForClient laddr to
269 if not mine then fail else do
270 let to' = unsplitJID (n,h,r)
271 from' <- do
272 flip (maybe $ return Nothing) (stanzaFrom msg) $ \from -> do
273 (_,trip) <- rewriteJIDForClient laddr from
274 return . Just $ unsplitJID trip
275 cmap <- atomically . readTVar $ clientsByUser state
276 flip (maybe fail) n $ \n -> do
277 flip (maybe fail) (Map.lookup n cmap) $ \(k,_) -> do
278 flip (maybe fail) (Map.lookup k chans) $ \Conn { connChan=chan} -> do
279 sendModifiedStanzaToClient (msg { stanzaTo=Just to'
280 , stanzaFrom=from' })
281 chan
282
204 283
205main = runResourceT $ do 284main = runResourceT $ do
206 state <- liftIO . atomically $ do 285 state <- liftIO . atomically $ do
207 clients <- newTVar Map.empty 286 clients <- newTVar Map.empty
287 clientsByUser <- newTVar Map.empty
208 associatedPeers <- newTVar Map.empty 288 associatedPeers <- newTVar Map.empty
209 xmpp <- newEmptyTMVar 289 xmpp <- newEmptyTMVar
210 writeTos <- newTVar Map.empty 290 writeTos <- newTVar Map.empty
211 return PresenceState 291 return PresenceState
212 { clients = clients 292 { clients = clients
293 , clientsByUser = clientsByUser
213 , associatedPeers = associatedPeers 294 , associatedPeers = associatedPeers
214 , writeTos = writeTos 295 , writeTos = writeTos
215 , server = xmpp 296 , server = xmpp