summaryrefslogtreecommitdiff
path: root/ToxToXMPP.hs
diff options
context:
space:
mode:
authorAndrew Cady <d@jerkface.net>2018-06-21 22:29:04 -0400
committerAndrew Cady <d@jerkface.net>2018-06-21 22:40:41 -0400
commit5622c6cdce0b8572434e8ab24fbae7f57ffadf3e (patch)
treebccfc1a212b7b2a1919fabc03bf190adf59554ee /ToxToXMPP.hs
parent4fa78c094f7bd1afa9a7dd72c1f32eb1dd867ac8 (diff)
start to implement plan in conn-notes.txt
Diffstat (limited to 'ToxToXMPP.hs')
-rw-r--r--ToxToXMPP.hs75
1 files changed, 70 insertions, 5 deletions
diff --git a/ToxToXMPP.hs b/ToxToXMPP.hs
index 26e22361..2683d404 100644
--- a/ToxToXMPP.hs
+++ b/ToxToXMPP.hs
@@ -1,6 +1,7 @@
1{-# LANGUAGE CPP #-} 1{-# LANGUAGE CPP #-}
2{-# LANGUAGE LambdaCase #-} 2{-# LANGUAGE LambdaCase #-}
3{-# LANGUAGE NamedFieldPuns #-} 3{-# LANGUAGE NamedFieldPuns #-}
4{-# LANGUAGE NondecreasingIndentation #-}
4module ToxToXMPP 5module ToxToXMPP
5 ( forkAccountWatcher 6 ( forkAccountWatcher
6 , JabberClients 7 , JabberClients
@@ -22,6 +23,7 @@ import Network.Tox.Crypto.Transport as Tox
22import Util (unsplitJID) 23import Util (unsplitJID)
23import XMPPServer as XMPP 24import XMPPServer as XMPP
24 25
26import Network.Tox.DHT.Handlers (nodeSearch, nodesOfInterest)
25import Announcer 27import Announcer
26import Announcer.Tox 28import Announcer.Tox
27import Connection 29import Connection
@@ -58,7 +60,7 @@ import Network.Tox
58import Network.Tox.ContactInfo 60import Network.Tox.ContactInfo
59import Network.Tox.DHT.Handlers 61import Network.Tox.DHT.Handlers
60import qualified Network.Tox.DHT.Transport as Tox 62import qualified Network.Tox.DHT.Transport as Tox
61 ;import Network.Tox.DHT.Transport (FriendRequest (..)) 63 ;import Network.Tox.DHT.Transport (dhtpk, FriendRequest (..))
62import Network.Tox.NodeId 64import Network.Tox.NodeId
63import qualified Network.Tox.Onion.Handlers as Tox 65import qualified Network.Tox.Onion.Handlers as Tox
64import qualified Network.Tox.Onion.Transport as Tox 66import qualified Network.Tox.Onion.Transport as Tox
@@ -144,13 +146,65 @@ data ToxToXMPP = ToxToXMPP
144default_nospam :: Word32 146default_nospam :: Word32
145default_nospam = 0x6a7a27fc -- big-endian base64: anon/A== 147default_nospam = 0x6a7a27fc -- big-endian base64: anon/A==
146 148
149nodeinfoStaleTime :: POSIXTime
150nodeinfoStaleTime = 600
151
152nodeinfoSearchInterval :: POSIXTime
153nodeinfoSearchInterval = 15
154
155gotDhtPubkey :: Tox.DHTPublicKey -> ToxToXMPP -> PublicKey -> IO ()
156gotDhtPubkey pubkey tx theirKey = do
157 contact <- atomically $ getContact theirKey (txAccount tx) >>= mapM (readTVar . contactLastSeenAddr)
158 forM_ contact $ \lastSeen -> do
159 case lastSeen of
160 Nothing -> doSearch
161 Just (tm, _) -> do
162 now <- getPOSIXTime
163 when (now - tm > nodeinfoStaleTime) doSearch
164 where
165 doSearch = do
166 let pub = toPublic $ userSecret (txAccount tx)
167 me = key2id pub
168 akey <- akeyConnect (txAnnouncer tx) me theirKey
169 atomically $ registerNodeCallback (toxRouting tox) (nic akey)
170 scheduleSearch (txAnnouncer tx) akey meth pubkey
171 tox :: Tox JabberClients
172 tox = txTox tx
173 target = key2id $ dhtpk pubkey
174 meth :: SearchMethod Tox.DHTPublicKey
175 meth =
176 SearchMethod
177 { sSearch = nodeSearch (toxDHT tox) (nodesOfInterest $ toxRouting tox)
178 , sNearestNodes = nearNodes tox
179 , sTarget = target
180 , sInterval = nodeinfoSearchInterval
181 , sWithResult = \r sr -> return ()
182 }
183 nic akey =
184 NodeInfoCallback
185 { interestingNodeId = target
186 , listenerId = 2
187 , observedAddress = observe akey
188 , rumoredAddress = assume akey
189 }
190
191 assume :: AnnounceKey -> POSIXTime -> SockAddr -> NodeInfo -> STM ()
192 assume akey time addr ni =
193 tput XNodeinfoSearch $ show ("rumor", akey, time, addr, ni)
194
195 observe :: AnnounceKey -> POSIXTime -> NodeInfo -> STM ()
196 observe akey time ni = do
197 tput XNodeinfoSearch $ show ("observation", akey, time, ni)
198 unschedule (txAnnouncer tx) akey -- todo: schedule the handshake here
199 setContactAddr time theirKey (nodeAddr ni) (txAccount tx)
200
147dispatch :: ToxToXMPP -> ContactEvent -> IO () 201dispatch :: ToxToXMPP -> ContactEvent -> IO ()
148dispatch tx (SessionEstablished theirKey) = stopConnecting tx theirKey 202dispatch tx (SessionEstablished theirKey) = stopConnecting tx theirKey
149dispatch tx (SessionTerminated theirKey) = startConnecting tx theirKey 203dispatch tx (SessionTerminated theirKey) = startConnecting tx theirKey
150dispatch tx (AddrChange theirkey saddr) = return () -- todo 204dispatch tx (AddrChange theirkey saddr) = return () -- todo
151dispatch tx (PolicyChange theirkey TryingToConnect ) = startConnecting tx theirkey 205dispatch tx (PolicyChange theirkey TryingToConnect ) = startConnecting tx theirkey
152dispatch tx (PolicyChange theirkey policy ) = stopConnecting tx theirkey 206dispatch tx (PolicyChange theirkey policy ) = stopConnecting tx theirkey
153dispatch tx (OnionRouted theirkey (OnionDHTPublicKey pkey)) = return () -- todo 207dispatch tx (OnionRouted theirKey (OnionDHTPublicKey pkey)) = gotDhtPubkey pkey tx theirKey
154dispatch tx (OnionRouted theirkey (OnionFriendRequest fr) ) = do 208dispatch tx (OnionRouted theirkey (OnionFriendRequest fr) ) = do
155 let ToxToXMPP { txAnnouncer = acr 209 let ToxToXMPP { txAnnouncer = acr
156 , txAccount = acnt 210 , txAccount = acnt
@@ -189,6 +243,7 @@ akeyConnect :: Announcer -> NodeId -> PublicKey -> IO AnnounceKey
189akeyConnect announcer me them = atomically $ do 243akeyConnect announcer me them = atomically $ do
190 packAnnounceKey announcer $ "connect:" ++ (take 8 $ show me) ++ ":" ++ show (key2id them) 244 packAnnounceKey announcer $ "connect:" ++ (take 8 $ show me) ++ ":" ++ show (key2id them)
191 245
246
192-- | Returns a list of nospam values to use for friend requests to send to a 247-- | Returns a list of nospam values to use for friend requests to send to a
193-- remote peer. This list is non-empty only when it is desirable to send 248-- remote peer. This list is non-empty only when it is desirable to send
194-- friend requests. 249-- friend requests.
@@ -208,6 +263,16 @@ checkSoliciting presence me them contact = do
208 _ -> maybeToList $ readMaybe $ T.unpack $ key2jid default_nospam them 263 _ -> maybeToList $ readMaybe $ T.unpack $ key2jid default_nospam them
209 return nospam 264 return nospam
210 265
266nearNodes :: Tox extra -> NodeId -> STM [NodeInfo]
267nearNodes tox nid = do
268 bkts4 <- readTVar $ routing4 $ toxRouting tox
269 bkts6 <- readTVar $ routing6 $ toxRouting tox
270 let nss =
271 map
272 (R.kclosest (searchSpace (toxQSearch tox)) searchK nid)
273 [bkts4, bkts6]
274 return $ foldr interweave [] nss
275
211startConnecting0 :: ToxToXMPP -> PublicKey -> Contact -> IO () 276startConnecting0 :: ToxToXMPP -> PublicKey -> Contact -> IO ()
212startConnecting0 tx them contact = do 277startConnecting0 tx them contact = do
213 dput XMan $ "START CONNECTING " ++ show (key2id them) 278 dput XMan $ "START CONNECTING " ++ show (key2id them)