diff options
-rw-r--r-- | dht/HandshakeCache.hs | 6 | ||||
-rw-r--r-- | dht/ToxManager.hs | 69 |
2 files changed, 53 insertions, 22 deletions
diff --git a/dht/HandshakeCache.hs b/dht/HandshakeCache.hs index 61735e8a..91f5faaf 100644 --- a/dht/HandshakeCache.hs +++ b/dht/HandshakeCache.hs | |||
@@ -113,13 +113,13 @@ cacheHandshake hscache me them their_node ecookie = do | |||
113 | dput XNetCrypto $ "cacheHandshake " ++ show (key2id them,ecookie) | 113 | dput XNetCrypto $ "cacheHandshake " ++ show (key2id them,ecookie) |
114 | atomically $ snd <$> cacheHandshakeSTM hscache me them their_node ecookie timestamp | 114 | atomically $ snd <$> cacheHandshakeSTM hscache me them their_node ecookie timestamp |
115 | 115 | ||
116 | haveCachedCookie :: HandshakeCache | 116 | getPendingCookieFlag :: HandshakeCache |
117 | -> PublicKey | 117 | -> PublicKey |
118 | -> PublicKey | 118 | -> PublicKey |
119 | -> STM Bool | 119 | -> STM Bool |
120 | haveCachedCookie hscache me them = do | 120 | getPendingCookieFlag hscache me them = do |
121 | m <- Map.lookup (me,them) <$> readTVar (hscPendingCookies hscache) | 121 | m <- Map.lookup (me,them) <$> readTVar (hscPendingCookies hscache) |
122 | return $ maybe True (const False) m | 122 | return $ maybe False (const True) m |
123 | 123 | ||
124 | 124 | ||
125 | setPendingCookie :: HandshakeCache | 125 | setPendingCookie :: HandshakeCache |
diff --git a/dht/ToxManager.hs b/dht/ToxManager.hs index 96bd9bc3..ab73b327 100644 --- a/dht/ToxManager.hs +++ b/dht/ToxManager.hs | |||
@@ -49,6 +49,8 @@ import Network.Tox.NodeId | |||
49 | import qualified Network.Tox.Onion.Handlers as Tox | 49 | import qualified Network.Tox.Onion.Handlers as Tox |
50 | import qualified Network.Tox.Onion.Transport as Tox | 50 | import qualified Network.Tox.Onion.Transport as Tox |
51 | ;import Network.Tox.Onion.Transport (OnionData (..)) | 51 | ;import Network.Tox.Onion.Transport (OnionData (..)) |
52 | import Network.Tox.Onion.Routes (tcpKademliaClient) | ||
53 | import qualified Network.Tox.TCP as TCP | ||
52 | import Presence | 54 | import Presence |
53 | import Text.Read | 55 | import Text.Read |
54 | import Util (unsplitJID) | 56 | import Util (unsplitJID) |
@@ -134,7 +136,12 @@ toxman ssvar announcer toxbkts tox presence = ToxManager | |||
134 | toxAnnounceInterval) | 136 | toxAnnounceInterval) |
135 | pub | 137 | pub |
136 | 138 | ||
137 | forkAccountWatcher ssvar acnt tox presence announcer | 139 | forkAccountWatcher ssvar |
140 | (TCP.tcpClient $ tcpKademliaClient $ toxOnionRoutes tox) | ||
141 | acnt | ||
142 | tox | ||
143 | presence | ||
144 | announcer | ||
138 | return () | 145 | return () |
139 | 146 | ||
140 | , deactivateAccount = \k pubname -> do | 147 | , deactivateAccount = \k pubname -> do |
@@ -256,6 +263,7 @@ data ToxToXMPP = ToxToXMPP | |||
256 | , txPresence :: PresenceState Pending | 263 | , txPresence :: PresenceState Pending |
257 | , txTox :: Tox JabberClients | 264 | , txTox :: Tox JabberClients |
258 | , txSessions :: TVar (Map.Map Uniq24 AggregateSession) | 265 | , txSessions :: TVar (Map.Map Uniq24 AggregateSession) |
266 | , txTCP :: TCP.RelayClient | ||
259 | } | 267 | } |
260 | 268 | ||
261 | default_nospam :: Word32 | 269 | default_nospam :: Word32 |
@@ -267,6 +275,26 @@ nodeinfoStaleTime = 600 -- consider DHT node address stale after 10 minutes | |||
267 | nodeinfoSearchInterval :: POSIXTime | 275 | nodeinfoSearchInterval :: POSIXTime |
268 | nodeinfoSearchInterval = 15 -- when no address, search DHT node every 15 seconds | 276 | nodeinfoSearchInterval = 15 -- when no address, search DHT node every 15 seconds |
269 | 277 | ||
278 | connectViaRelay :: ToxToXMPP -> PublicKey -> Tox.DHTPublicKey | ||
279 | -> Announcer -> AnnounceKey -> POSIXTime -> STM (IO ()) | ||
280 | connectViaRelay tx theirKey theirDhtKey ann tkey now = do | ||
281 | mcontact <- getContact theirKey (txAccount tx) | ||
282 | case mcontact of | ||
283 | Nothing -> return $ return () | ||
284 | Just contact -> do | ||
285 | established <- activeSesh tx theirKey | ||
286 | return $ when (not established) go | ||
287 | where | ||
288 | go = do | ||
289 | let Tox.SendNodes ns = Tox.dhtpkNodes theirDhtKey | ||
290 | mcon <- foldr (\action next -> action >>= maybe next (return . Just)) | ||
291 | (return Nothing) | ||
292 | $ map (\ni -> fmap ((,) ni) <$> TCP.tcpConnectionRequest (txTCP tx) theirKey ni) ns | ||
293 | forM_ mcon $ \(con,ni) -> do | ||
294 | return () | ||
295 | -- TODO: try connect tcp relays | ||
296 | -- TODO: cookie;handshake | ||
297 | |||
270 | gotDhtPubkey :: Tox.DHTPublicKey -> ToxToXMPP -> PublicKey -> IO () | 298 | gotDhtPubkey :: Tox.DHTPublicKey -> ToxToXMPP -> PublicKey -> IO () |
271 | gotDhtPubkey theirDhtKey tx theirKey = do | 299 | gotDhtPubkey theirDhtKey tx theirKey = do |
272 | contact <- atomically $ getContact theirKey (txAccount tx) >>= mapM (readTVar . contactLastSeenAddr) | 300 | contact <- atomically $ getContact theirKey (txAccount tx) >>= mapM (readTVar . contactLastSeenAddr) |
@@ -284,10 +312,11 @@ gotDhtPubkey theirDhtKey tx theirKey = do | |||
284 | me = key2id myPublicKey | 312 | me = key2id myPublicKey |
285 | 313 | ||
286 | doSearch = do | 314 | doSearch = do |
287 | -- TODO: attempt to connect via TCP relays. | ||
288 | let akey = akeyConnect (txAnnouncer tx) me theirKey | 315 | let akey = akeyConnect (txAnnouncer tx) me theirKey |
316 | tkey = akeyConnectTCP (txAnnouncer tx) me theirKey | ||
289 | atomically $ registerNodeCallback (toxRouting tox) (nic akey) | 317 | atomically $ registerNodeCallback (toxRouting tox) (nic akey) |
290 | scheduleSearch (txAnnouncer tx) akey meth theirDhtKey | 318 | scheduleSearch (txAnnouncer tx) akey meth theirDhtKey |
319 | -- TODO atomically $ scheduleImmediately (txAnnouncer tx) tkey $ ScheduledItem $ connectViaRelay tx theirKey theirDhtKey | ||
291 | 320 | ||
292 | target :: NodeId | 321 | target :: NodeId |
293 | target = key2id $ dhtpk theirDhtKey | 322 | target = key2id $ dhtpk theirDhtKey |
@@ -339,15 +368,14 @@ gotAddr' ni@(nodeAddr -> addr) tx theirKey theirDhtKey = atomically blee | |||
339 | 368 | ||
340 | blee = do | 369 | blee = do |
341 | scheduleImmediately (txAnnouncer tx) akey $ | 370 | scheduleImmediately (txAnnouncer tx) akey $ |
342 | ScheduledItem $ getCookie tx theirKey theirDhtKey ni (activeSesh addr) (getContact theirKey (txAccount tx)) | 371 | ScheduledItem $ |
343 | 372 | getCookie tx theirKey theirDhtKey ni | |
344 | tox :: Tox JabberClients | 373 | (activeSesh tx theirKey) |
345 | tox = txTox tx | 374 | (getContact theirKey $ txAccount tx) |
346 | 375 | ||
347 | crypto = toxCryptoKeys tox | 376 | activeSesh :: ToxToXMPP -> PublicKey -> STM Bool |
348 | 377 | activeSesh tx theirKey = do | |
349 | activeSesh :: SockAddr -> STM Bool | 378 | let myPublicKey = toPublic $ userSecret (txAccount tx) |
350 | activeSesh a = do | ||
351 | ss <- readTVar (txSessions tx) | 379 | ss <- readTVar (txSessions tx) |
352 | u <- xor24 <$> unsafeIOToSTM (hash24 myPublicKey) | 380 | u <- xor24 <$> unsafeIOToSTM (hash24 myPublicKey) |
353 | <*> unsafeIOToSTM (hash24 theirKey) | 381 | <*> unsafeIOToSTM (hash24 theirKey) |
@@ -364,9 +392,6 @@ gotAddr' ni@(nodeAddr -> addr) tx theirKey theirDhtKey = atomically blee | |||
364 | Just False -> return False | 392 | Just False -> return False |
365 | _ -> (== Established) <$> aggregateStatus c | 393 | _ -> (== Established) <$> aggregateStatus c |
366 | 394 | ||
367 | client :: Network.Tox.DHT.Handlers.Client | ||
368 | client = toxDHT tox | ||
369 | |||
370 | getCookie | 395 | getCookie |
371 | :: ToxToXMPP | 396 | :: ToxToXMPP |
372 | -> PublicKey | 397 | -> PublicKey |
@@ -503,6 +528,10 @@ akeyConnect :: Announcer -> NodeId -> PublicKey -> AnnounceKey | |||
503 | akeyConnect announcer me them = | 528 | akeyConnect announcer me them = |
504 | packAnnounceKey announcer $ "connect(" ++ (take 8 $ show me) ++ ")" ++ show (key2id them) | 529 | packAnnounceKey announcer $ "connect(" ++ (take 8 $ show me) ++ ")" ++ show (key2id them) |
505 | 530 | ||
531 | akeyConnectTCP :: Announcer -> NodeId -> PublicKey -> AnnounceKey | ||
532 | akeyConnectTCP announcer me them = | ||
533 | packAnnounceKey announcer $ "tcp-connect(" ++ (take 8 $ show me) ++ ")" ++ show (key2id them) | ||
534 | |||
506 | 535 | ||
507 | 536 | ||
508 | -- | Because Tox does not have a friend-request response, we consider an | 537 | -- | Because Tox does not have a friend-request response, we consider an |
@@ -645,8 +674,9 @@ closeSessions me them ssvar = do | |||
645 | closeAll ag | 674 | closeAll ag |
646 | 675 | ||
647 | forkAccountWatcher :: TVar (Map.Map Uniq24 AggregateSession) | 676 | forkAccountWatcher :: TVar (Map.Map Uniq24 AggregateSession) |
677 | -> TCP.RelayClient | ||
648 | -> Account JabberClients -> Tox JabberClients -> PresenceState Pending -> Announcer -> IO ThreadId | 678 | -> Account JabberClients -> Tox JabberClients -> PresenceState Pending -> Announcer -> IO ThreadId |
649 | forkAccountWatcher ssvar acc tox st announcer = forkIO $ do | 679 | forkAccountWatcher ssvar tcp acc tox st announcer = forkIO $ do |
650 | myThreadId >>= flip labelThread ("online:" | 680 | myThreadId >>= flip labelThread ("online:" |
651 | ++ show (key2id $ toPublic $ userSecret acc)) | 681 | ++ show (key2id $ toPublic $ userSecret acc)) |
652 | (chan,cs) <- atomically $ do | 682 | (chan,cs) <- atomically $ do |
@@ -658,6 +688,7 @@ forkAccountWatcher ssvar acc tox st announcer = forkIO $ do | |||
658 | , txPresence = st | 688 | , txPresence = st |
659 | , txTox = tox | 689 | , txTox = tox |
660 | , txSessions = ssvar | 690 | , txSessions = ssvar |
691 | , txTCP = tcp | ||
661 | } | 692 | } |
662 | forM_ (HashMap.toList cs) $ \(them,c) -> do | 693 | forM_ (HashMap.toList cs) $ \(them,c) -> do |
663 | startConnecting0 tx (id2key them) c "enabled account" | 694 | startConnecting0 tx (id2key them) c "enabled account" |
@@ -690,17 +721,17 @@ getStatus me them a c hs = do | |||
690 | policy <- fromMaybe RefusingToConnect <$> maybe (return Nothing) (readTVar . contactPolicy) c | 721 | policy <- fromMaybe RefusingToConnect <$> maybe (return Nothing) (readTVar . contactPolicy) c |
691 | mdht <- maybe (return Nothing) (readTVar . contactKeyPacket) c | 722 | mdht <- maybe (return Nothing) (readTVar . contactKeyPacket) c |
692 | maddr <- maybe (return Nothing) (readTVar . contactLastSeenAddr) c | 723 | maddr <- maybe (return Nothing) (readTVar . contactLastSeenAddr) c |
693 | haveCookie <- haveCachedCookie hs me them | 724 | cookieIsPending <- getPendingCookieFlag hs me them |
694 | return $ statusLogic astat policy mdht maddr haveCookie | 725 | return $ statusLogic astat policy mdht maddr cookieIsPending |
695 | 726 | ||
696 | statusLogic :: Status ToxProgress -> Policy -> Maybe dhtkey -> Maybe addr -> Bool -> Status ToxProgress | 727 | statusLogic :: Status ToxProgress -> Policy -> Maybe dhtkey -> Maybe addr -> Bool -> Status ToxProgress |
697 | statusLogic astat policy mdht maddr haveCookie = case () of | 728 | statusLogic astat policy mdht maddr cookieIsPending = case () of |
698 | () | Established <- astat -> Established | 729 | () | Established <- astat -> Established |
699 | | InProgress AwaitingSessionPacket <- astat -> InProgress AwaitingSessionPacket | 730 | | InProgress AwaitingSessionPacket <- astat -> InProgress AwaitingSessionPacket |
700 | | RefusingToConnect <- policy -> Dormant | 731 | | RefusingToConnect <- policy -> Dormant |
701 | | Nothing <- mdht -> InProgress AwaitingDHTKey | 732 | | Nothing <- mdht -> InProgress AwaitingDHTKey |
702 | | Nothing <- maddr -> InProgress AcquiringIPAddress | 733 | | Nothing <- maddr -> InProgress AcquiringIPAddress |
703 | | not haveCookie -> InProgress AcquiringCookie | 734 | | cookieIsPending -> InProgress AcquiringCookie |
704 | | otherwise -> InProgress AwaitingHandshake | 735 | | otherwise -> InProgress AwaitingHandshake |
705 | 736 | ||
706 | 737 | ||