summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Presence/Presence.hs21
-rw-r--r--ToxToXMPP.hs69
-rw-r--r--examples/dhtd.hs16
-rw-r--r--src/Network/Tox/NodeId.hs1
4 files changed, 90 insertions, 17 deletions
diff --git a/Presence/Presence.hs b/Presence/Presence.hs
index 41204818..adae567a 100644
--- a/Presence/Presence.hs
+++ b/Presence/Presence.hs
@@ -109,7 +109,7 @@ data PresenceState = forall status. PresenceState
109 109
110 110
111newPresenceState :: Maybe ConsoleWriter 111newPresenceState :: Maybe ConsoleWriter
112 -> Maybe (ToxManager ConnectionKey) 112 -> Maybe (PresenceState -> ToxManager ConnectionKey)
113 -> TMVar (XMPPServer, Connection.Manager status Text) 113 -> TMVar (XMPPServer, Connection.Manager status Text)
114 -> IO PresenceState 114 -> IO PresenceState
115newPresenceState cw toxman xmpp = atomically $ do 115newPresenceState cw toxman xmpp = atomically $ do
@@ -117,15 +117,16 @@ newPresenceState cw toxman xmpp = atomically $ do
117 clientsByUser <- newTVar Map.empty 117 clientsByUser <- newTVar Map.empty
118 remotesByPeer <- newTVar Map.empty 118 remotesByPeer <- newTVar Map.empty
119 keyToChan <- newTVar Map.empty 119 keyToChan <- newTVar Map.empty
120 return PresenceState 120 let st = PresenceState
121 { clients = clients 121 { clients = clients
122 , clientsByUser = clientsByUser 122 , clientsByUser = clientsByUser
123 , remotesByPeer = remotesByPeer 123 , remotesByPeer = remotesByPeer
124 , keyToChan = keyToChan 124 , keyToChan = keyToChan
125 , server = xmpp 125 , server = xmpp
126 , consoleWriter = cw 126 , consoleWriter = cw
127 , toxManager = toxman 127 , toxManager = Nothing
128 } 128 }
129 return $ st { toxManager = fmap ($ st) toxman }
129 130
130 131
131nameForClient :: PresenceState -> ConnectionKey -> IO Text 132nameForClient :: PresenceState -> ConnectionKey -> IO Text
diff --git a/ToxToXMPP.hs b/ToxToXMPP.hs
index b018e47b..fca8ee30 100644
--- a/ToxToXMPP.hs
+++ b/ToxToXMPP.hs
@@ -1,11 +1,80 @@
1{-# LANGUAGE CPP #-}
2{-# LANGUAGE LambdaCase #-}
1module ToxToXMPP where 3module ToxToXMPP where
2 4
3import Data.Conduit as C 5import Data.Conduit as C
4import Data.XML.Types as XML 6import Data.XML.Types as XML
5import Network.Tox.Crypto.Transport as Tox 7import Network.Tox.Crypto.Transport as Tox
6 8
9import Announcer
10import Connection
11import Connection.Tox as Connection
12import Control.Concurrent.STM
13import Control.Concurrent.STM.TChan
14import Control.Monad
15import Crypto.Tox
16import Data.Bits
17import Data.Function
18import qualified Data.HashMap.Strict as HashMap
19import qualified Data.Set as Set
20import qualified Data.Text as T
21 ;import Data.Text (Text)
22import Data.Word
23import Network.Tox
24import Network.Tox.ContactInfo
25import Network.Tox.DHT.Transport (FriendRequest (..))
26import Network.Tox.NodeId
27import Network.Tox.Onion.Transport (OnionData (..))
28import Presence
29import XMPPServer
30#ifdef THREAD_DEBUG
31import Control.Concurrent.Lifted.Instrument
32#else
33import Control.Concurrent.Lifted
34import GHC.Conc (labelThread)
35#endif
36
7xmppToTox :: Conduit XML.Event IO Tox.CryptoMessage 37xmppToTox :: Conduit XML.Event IO Tox.CryptoMessage
8xmppToTox = _todo 38xmppToTox = _todo
9 39
10toxToXmpp :: Conduit Tox.CryptoMessage IO XML.Event 40toxToXmpp :: Conduit Tox.CryptoMessage IO XML.Event
11toxToXmpp = _todo 41toxToXmpp = _todo
42
43accountJID :: Account -> Text
44accountJID acnt = _todo -- Or perhaps this should be passed in from PresenceState
45
46key2jid :: Word32 -> PublicKey -> Text
47key2jid nospam key = T.pack $ show $ NoSpamId nsp key
48 where
49 nsp = NoSpam nospam (Just sum)
50 sum = nlo `xor` nhi `xor` xorsum key
51 nlo = fromIntegral (0x0FFFF .&. nospam) :: Word16
52 nhi = fromIntegral (0x0FFFF .&. (nospam `shiftR` 16)) :: Word16
53
54dispatch acnt conn (PolicyChange theirkey policy ) = return () -- todo
55dispatch acnt conn (OnionRouted theirkey (OnionDHTPublicKey pkey)) = return () -- todo
56dispatch acnt conn (OnionRouted theirkey (OnionFriendRequest fr) ) = do
57 let self = accountJID acnt
58 theirjid = key2jid (friendNoSpam fr) theirkey
59 ask <- presenceSolicitation theirjid self
60 sendModifiedStanzaToClient ask (connChan conn)
61
62forkAccountWatcher :: Account -> Tox -> Conn -> IO ThreadId
63forkAccountWatcher acc tox conn = forkIO $ do
64 myThreadId >>= flip labelThread "tox-account"
65 (chan,contacts) <- atomically $ do
66 chan <- dupTChan $ eventChan acc -- duplicate broadcast channel for reading.
67 contacts <- readTVar (contacts acc)
68 return (chan,contacts)
69 -- TODO: process information in contacts HashMap.
70
71 -- Loop endlessly until clientRefs is null.
72 fix $ \loop -> do
73 mev <- atomically $
74 (Just <$> readTChan chan)
75 `orElse` do
76 refs <- readTVar $ clientRefs acc
77 check $ Set.null refs
78 return Nothing
79 forM_ mev $ \ev -> dispatch acc conn ev >> loop
80
diff --git a/examples/dhtd.hs b/examples/dhtd.hs
index 60d60258..78090794 100644
--- a/examples/dhtd.hs
+++ b/examples/dhtd.hs
@@ -1216,23 +1216,24 @@ toxAnnounceInterval = 15
1216-- 1216--
1217-- These hooks will be invoked in order to connect to *.tox hosts in a user's 1217-- These hooks will be invoked in order to connect to *.tox hosts in a user's
1218-- XMPP roster. 1218-- XMPP roster.
1219toxman :: Announcer -> [(String,TVar (BucketList Tox.NodeInfo))] -> Tox.Tox -> ToxManager ConnectionKey 1219toxman :: Announcer -> [(String,TVar (BucketList Tox.NodeInfo))] -> Tox.Tox -> PresenceState -> ToxManager ConnectionKey
1220toxman announcer toxbkts tox = ToxManager 1220toxman announcer toxbkts tox presence = ToxManager
1221 { activateAccount = \k pubname seckey -> do 1221 { activateAccount = \k pubname seckey -> do
1222 hPutStrLn stderr $ "toxman ACTIVATE " ++ show (Tox.key2id $ toPublic seckey) 1222 hPutStrLn stderr $ "toxman ACTIVATE " ++ show (Tox.key2id $ toPublic seckey)
1223 let ContactInfo{ accounts } = Tox.toxContactInfo tox 1223 let ContactInfo{ accounts } = Tox.toxContactInfo tox
1224 pub = toPublic seckey 1224 pub = toPublic seckey
1225 pubid = Tox.key2id pub 1225 pubid = Tox.key2id pub
1226 newlyActive <- atomically $ do 1226 (mcon,newlyActive) <- atomically $ do
1227 macnt <- HashMap.lookup pubid <$> readTVar accounts 1227 macnt <- HashMap.lookup pubid <$> readTVar accounts
1228 acnt <- maybe (newAccount seckey) return macnt 1228 acnt <- maybe (newAccount seckey) return macnt
1229 rs <- readTVar $ clientRefs acnt 1229 rs <- readTVar $ clientRefs acnt
1230 writeTVar (clientRefs acnt) $! Set.insert k rs 1230 writeTVar (clientRefs acnt) $! Set.insert k rs
1231 modifyTVar accounts (HashMap.insert pubid acnt) 1231 modifyTVar accounts (HashMap.insert pubid acnt)
1232 mcon <- fmap ((,) acnt) . Map.lookup k <$> readTVar (keyToChan presence)
1232 if not (Set.null rs) 1233 if not (Set.null rs)
1233 then return [] 1234 then return (mcon,[])
1234 else do 1235 else do
1235 forM toxbkts $ \(nm,bkts) -> do 1236 fmap ((,) mcon) $ forM toxbkts $ \(nm,bkts) -> do
1236 akey <- packAnnounceKey announcer (nm ++ "id:" ++ show pubid) 1237 akey <- packAnnounceKey announcer (nm ++ "id:" ++ show pubid)
1237 return (akey,bkts) 1238 return (akey,bkts)
1238 forM_ newlyActive $ \(akey,bkts) -> do 1239 forM_ newlyActive $ \(akey,bkts) -> do
@@ -1246,8 +1247,8 @@ toxman announcer toxbkts tox = ToxManager
1246 pubid 1247 pubid
1247 toxAnnounceInterval) 1248 toxAnnounceInterval)
1248 pub 1249 pub
1249 -- 1250
1250 -- Schedule recurring search for all non-connected contacts. 1251 forM_ mcon $ \(acnt,conn) -> forkAccountWatcher acnt tox conn
1251 return () 1252 return ()
1252 , deactivateAccount = \k pubname -> do 1253 , deactivateAccount = \k pubname -> do
1253 bStopped <- fmap (fromMaybe False) $ atomically $ do 1254 bStopped <- fmap (fromMaybe False) $ atomically $ do
@@ -1628,6 +1629,7 @@ main = runResourceT $ liftBaseWith $ \resT -> do
1628 [ lookupBkts "tox4" toxdhts 1629 [ lookupBkts "tox4" toxdhts
1629 , lookupBkts "tox6" toxdhts 1630 , lookupBkts "tox6" toxdhts
1630 ] 1631 ]
1632
1631 state <- newPresenceState cw (toxman announcer toxbkts <$> mbtox) serverVar 1633 state <- newPresenceState cw (toxman announcer toxbkts <$> mbtox) serverVar
1632 1634
1633 sv <- resT $ xmppServer (presenceHooks state (verbosity opts) (Just cport) (Just sport)) 1635 sv <- resT $ xmppServer (presenceHooks state (verbosity opts) (Just cport) (Just sport))
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs
index 1f79d1a5..2728a13d 100644
--- a/src/Network/Tox/NodeId.hs
+++ b/src/Network/Tox/NodeId.hs
@@ -105,6 +105,7 @@ packPublicKey ws = BA.allocAndFreeze (8 * length ws) $
105 [] -> return () 105 [] -> return ()
106 x:xs -> do poke ptr (toBE64 x) 106 x:xs -> do poke ptr (toBE64 x)
107 loop xs (plusPtr ptr 8) 107 loop xs (plusPtr ptr 8)
108{-# NOINLINE packPublicKey #-}
108 109
109-- We represent the node id redundantly in two formats. The [Word64] format is 110-- We represent the node id redundantly in two formats. The [Word64] format is
110-- convenient for short-circuiting xor/distance comparisons. The PublicKey 111-- convenient for short-circuiting xor/distance comparisons. The PublicKey