summaryrefslogtreecommitdiff
path: root/ToxToXMPP.hs
diff options
context:
space:
mode:
Diffstat (limited to 'ToxToXMPP.hs')
-rw-r--r--ToxToXMPP.hs104
1 files changed, 94 insertions, 10 deletions
diff --git a/ToxToXMPP.hs b/ToxToXMPP.hs
index edbf35ca..ac24ce6d 100644
--- a/ToxToXMPP.hs
+++ b/ToxToXMPP.hs
@@ -1,5 +1,6 @@
1{-# LANGUAGE CPP #-} 1{-# LANGUAGE CPP #-}
2{-# LANGUAGE LambdaCase #-} 2{-# LANGUAGE LambdaCase #-}
3{-# LANGUAGE NamedFieldPuns #-}
3module ToxToXMPP where 4module ToxToXMPP where
4 5
5import Data.Conduit as C 6import Data.Conduit as C
@@ -9,23 +10,52 @@ import Network.Tox.Crypto.Transport as Tox
9import XMPPServer as XMPP 10import XMPPServer as XMPP
10import EventUtil 11import EventUtil
11 12
13import Announcer
14import Announcer.Tox
15import Connection
16import Network.QueryResponse
17-- import Control.Concurrent
18import Control.Concurrent.STM
19import Control.Monad
20import Crypto.Tox
21import qualified Data.HashMap.Strict as HashMap
22import Data.Maybe
23import qualified Data.Set as Set
24import qualified Data.Text as T
25import Data.Time.Clock.POSIX
26import Network.Address
27import Network.Kademlia.Search
28import qualified Network.Tox as Tox
29import Network.Tox.ContactInfo as Tox
30import qualified Network.Tox.Crypto.Handlers as Tox
31-- import qualified Network.Tox.DHT.Handlers as Tox
32import Announcer
12import ClientState 33import ClientState
13import Control.Concurrent.STM 34import Control.Concurrent.STM
14import Control.Monad 35import Control.Monad
15import Crypto.Tox 36import Crypto.Tox
16import Data.Bits 37import Data.Bits
17import Data.Function 38import Data.Function
18import qualified Data.Map as Map 39import qualified Data.Map as Map
19import qualified Data.Set as Set 40import qualified Data.Set as Set
20import qualified Data.Text as T 41import qualified Data.Text as T
21 ;import Data.Text (Text) 42 ;import Data.Text (Text)
22import Data.Word 43import Data.Word
44import qualified Network.Kademlia.Routing as R
23import Network.Tox 45import Network.Tox
24import Network.Tox.ContactInfo 46import Network.Tox.ContactInfo
25import Network.Tox.DHT.Transport (FriendRequest (..)) 47import Network.Tox.DHT.Handlers
48import qualified Network.Tox.DHT.Transport as Tox
49 ;import Network.Tox.DHT.Transport (FriendRequest (..))
26import Network.Tox.NodeId 50import Network.Tox.NodeId
27import Network.Tox.Onion.Transport (OnionData (..)) 51import qualified Network.Tox.Onion.Handlers as Tox
52import qualified Network.Tox.Onion.Transport as Tox
53 ;import Network.Tox.Onion.Transport (OnionData (..))
54import Presence
28import Presence 55import Presence
56import System.IO
57import Text.Read
58import XMPPServer (ConnectionKey)
29#ifdef THREAD_DEBUG 59#ifdef THREAD_DEBUG
30import Control.Concurrent.Lifted.Instrument 60import Control.Concurrent.Lifted.Instrument
31#else 61#else
@@ -93,8 +123,13 @@ dispatch acnt st (OnionRouted theirkey (OnionFriendRequest fr) ) = do
93 -- embed it in the stanza as a <status> element. 123 -- embed it in the stanza as a <status> element.
94 sendModifiedStanzaToClient ask (connChan conn) 124 sendModifiedStanzaToClient ask (connChan conn)
95 125
96forkAccountWatcher :: Account -> Tox -> PresenceState -> IO ThreadId 126interweave :: [a] -> [a] -> [a]
97forkAccountWatcher acc tox st = forkIO $ do 127interweave [] ys = ys
128interweave (x:xs) ys = x : interweave ys xs
129
130
131forkAccountWatcher :: Account -> Tox -> PresenceState -> Announcer -> IO ThreadId
132forkAccountWatcher acc tox st announcer = forkIO $ do
98 myThreadId >>= flip labelThread ("tox-xmpp:" 133 myThreadId >>= flip labelThread ("tox-xmpp:"
99 ++ show (key2id $ toPublic $ userSecret acc)) 134 ++ show (key2id $ toPublic $ userSecret acc))
100 (chan,contacts) <- atomically $ do 135 (chan,contacts) <- atomically $ do
@@ -103,6 +138,49 @@ forkAccountWatcher acc tox st = forkIO $ do
103 return (chan,contacts) 138 return (chan,contacts)
104 -- TODO: process information in contacts HashMap. 139 -- TODO: process information in contacts HashMap.
105 140
141 let nearNodes nid = do
142 bkts4 <- readTVar $ routing4 $ toxRouting tox
143 bkts6 <- readTVar $ routing6 $ toxRouting tox
144 let nss = map (R.kclosest (searchSpace (toxQSearch tox)) searchK nid)
145 [bkts4,bkts6]
146 return $ foldr interweave [] nss
147
148
149 forM_ (HashMap.toList contacts) $ \(them,Contact{contactPolicy}) -> do
150 wanted <- atomically $ (==Just TryingToConnect) <$> readTVar contactPolicy
151 when wanted $ do
152 let pub = toPublic $ userSecret acc
153 akey <- atomically $ packAnnounceKey announcer $ "dhtkey:" ++ show them
154 -- We send this packet every 30 seconds if there is more
155 -- than one peer (in the 8) that says they our friend is
156 -- announced on them. This packet can also be sent through
157 -- the DHT module as a DHT request packet (see DHT) if we
158 -- know the DHT public key of the friend and are looking
159 -- for them in the DHT but have not connected to them yet.
160 -- 30 second is a reasonable timeout to not flood the
161 -- network with too many packets while making sure the
162 -- other will eventually receive the packet. Since packets
163 -- are sent through every peer that knows the friend,
164 -- resending it right away without waiting has a high
165 -- likelihood of failure as the chances of packet loss
166 -- happening to all (up to to 8) packets sent is low.
167 --
168 schedule announcer
169 akey
170 (AnnounceMethod (toxQSearch tox)
171 (Left $ \theirkey rendezvous -> do
172 dkey <- Tox.getContactInfo tox
173 sendMessage
174 (Tox.toxToRoute tox)
175 (Tox.AnnouncedRendezvous theirkey rendezvous)
176 (pub,Tox.OnionDHTPublicKey dkey))
177 nearNodes
178 them
179 30) -- every 30 seconds
180 pub
181
182
183
106 -- Loop endlessly until clientRefs is null. 184 -- Loop endlessly until clientRefs is null.
107 fix $ \loop -> do 185 fix $ \loop -> do
108 mev <- atomically $ 186 mev <- atomically $
@@ -113,3 +191,9 @@ forkAccountWatcher acc tox st = forkIO $ do
113 return Nothing 191 return Nothing
114 forM_ mev $ \ev -> dispatch acc st ev >> loop 192 forM_ mev $ \ev -> dispatch acc st ev >> loop
115 193
194toxQSearch :: Tox.Tox -> Search Tox.NodeId (IP, PortNumber) Nonce32 Tox.NodeInfo Tox.Rendezvous
195toxQSearch tox = Tox.toxidSearch (Tox.onionTimeout tox) (Tox.toxCryptoKeys tox) (Tox.toxOnion tox)
196
197toxAnnounceInterval :: POSIXTime
198toxAnnounceInterval = 15
199