diff options
Diffstat (limited to 'src/Network')
-rw-r--r-- | src/Network/Kademlia/Bootstrap.hs | 11 | ||||
-rw-r--r-- | src/Network/Tox.hs | 5 | ||||
-rw-r--r-- | src/Network/Tox/TCP.hs | 44 |
3 files changed, 47 insertions, 13 deletions
diff --git a/src/Network/Kademlia/Bootstrap.hs b/src/Network/Kademlia/Bootstrap.hs index 0f5d4e4d..1324ae77 100644 --- a/src/Network/Kademlia/Bootstrap.hs +++ b/src/Network/Kademlia/Bootstrap.hs | |||
@@ -424,3 +424,14 @@ touchBucket r@BucketRefresher{ refreshSearch | |||
424 | modifyTVar' refreshQueue $ Int.insert num (now + interval) | 424 | modifyTVar' refreshQueue $ Int.insert num (now + interval) |
425 | writeTVar refreshLastTouch now | 425 | writeTVar refreshLastTouch now |
426 | return action | 426 | return action |
427 | |||
428 | refreshKademlia :: SensibleNodeId nid ni => BucketRefresher nid ni -> Kademlia nid ni | ||
429 | refreshKademlia r@BucketRefresher { refreshSearch = sch | ||
430 | , refreshPing = ping | ||
431 | , refreshBuckets = bkts | ||
432 | } | ||
433 | = Kademlia quietInsertions (searchSpace sch) (vanillaIO bkts ping) | ||
434 | { tblTransition = \tr -> do | ||
435 | io <- touchBucket r tr | ||
436 | return io | ||
437 | } | ||
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 1e82c0c4..ea9bbe56 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -59,6 +59,7 @@ import Network.Tox.NodeId | |||
59 | import qualified Network.Tox.Onion.Handlers as Onion | 59 | import qualified Network.Tox.Onion.Handlers as Onion |
60 | import qualified Network.Tox.Onion.Transport as Onion | 60 | import qualified Network.Tox.Onion.Transport as Onion |
61 | import Network.Tox.Transport | 61 | import Network.Tox.Transport |
62 | import Network.Tox.TCP (tcpClient) | ||
62 | import OnionRouter | 63 | import OnionRouter |
63 | import Network.Tox.ContactInfo | 64 | import Network.Tox.ContactInfo |
64 | import Text.XXD | 65 | import Text.XXD |
@@ -372,6 +373,8 @@ forkTox tox with_avahi = do | |||
372 | quitOnion <- forkListener "toxOnion" (clientNet $ toxOnion tox) | 373 | quitOnion <- forkListener "toxOnion" (clientNet $ toxOnion tox) |
373 | quitDHT <- forkListener "toxDHT" (clientNet $ toxDHT tox) | 374 | quitDHT <- forkListener "toxDHT" (clientNet $ toxDHT tox) |
374 | quitNC <- forkListener "toxCrypto" (toxCrypto tox) | 375 | quitNC <- forkListener "toxCrypto" (toxCrypto tox) |
376 | quitTCP <- forkListener "relay-client" (clientNet $ tcpClient $ tcpKademliaClient $ toxOnionRoutes tox) | ||
377 | tcpKademlia <- forkPollForRefresh (tcpBucketRefresher $ toxOnionRoutes tox) | ||
375 | quitAvahi <- if with_avahi then do | 378 | quitAvahi <- if with_avahi then do |
376 | forkPollForRefresh (DHT.refresher4 $ toxRouting tox) | 379 | forkPollForRefresh (DHT.refresher4 $ toxRouting tox) |
377 | forkPollForRefresh (DHT.refresher6 $ toxRouting tox) | 380 | forkPollForRefresh (DHT.refresher6 $ toxRouting tox) |
@@ -387,6 +390,8 @@ forkTox tox with_avahi = do | |||
387 | quitNC | 390 | quitNC |
388 | quitDHT | 391 | quitDHT |
389 | quitOnion | 392 | quitOnion |
393 | quitTCP | ||
394 | killThread tcpKademlia | ||
390 | quitToRoute | 395 | quitToRoute |
391 | quitHs | 396 | quitHs |
392 | , bootstrap (DHT.refresher4 $ toxRouting tox) | 397 | , bootstrap (DHT.refresher4 $ toxRouting tox) |
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs index 5c6456f6..353b5ea3 100644 --- a/src/Network/Tox/TCP.hs +++ b/src/Network/Tox/TCP.hs | |||
@@ -22,6 +22,7 @@ import Data.Word | |||
22 | import qualified Data.Vector as Vector | 22 | import qualified Data.Vector as Vector |
23 | import Network.Socket (SockAddr(..)) | 23 | import Network.Socket (SockAddr(..)) |
24 | import qualified Text.ParserCombinators.ReadP as RP | 24 | import qualified Text.ParserCombinators.ReadP as RP |
25 | import System.IO.Error | ||
25 | 26 | ||
26 | import Crypto.Tox | 27 | import Crypto.Tox |
27 | import Data.ByteString (hPut,hGet,ByteString,length) | 28 | import Data.ByteString (hPut,hGet,ByteString,length) |
@@ -95,7 +96,7 @@ nodeAddr ni = setPort (tcpPort ni) $ UDP.nodeAddr $ udpNodeInfo ni | |||
95 | nodeIP :: NodeInfo -> IP | 96 | nodeIP :: NodeInfo -> IP |
96 | nodeIP ni = UDP.nodeIP $ udpNodeInfo ni | 97 | nodeIP ni = UDP.nodeIP $ udpNodeInfo ni |
97 | 98 | ||
98 | tcpStream :: (Serialize y, Sized y, Serialize x, Sized x) => | 99 | tcpStream :: (Show y, Show x, Serialize y, Sized y, Serialize x, Sized x) => |
99 | TransportCrypto -> StreamHandshake NodeInfo x y | 100 | TransportCrypto -> StreamHandshake NodeInfo x y |
100 | tcpStream crypto = StreamHandshake | 101 | tcpStream crypto = StreamHandshake |
101 | { streamHello = \addr h -> do | 102 | { streamHello = \addr h -> do |
@@ -112,28 +113,45 @@ tcpStream crypto = StreamHandshake | |||
112 | } | 113 | } |
113 | } | 114 | } |
114 | noncef <- lookupNonceFunction crypto (transportSecret crypto) (UDP.id2key $ nodeId addr) | 115 | noncef <- lookupNonceFunction crypto (transportSecret crypto) (UDP.id2key $ nodeId addr) |
116 | dput XTCP $ "TCP:" ++ show addr ++ " <-- " ++ show hello | ||
115 | hPut h $ encode $ encryptPayload (noncef $ helloNonce hello) hello | 117 | hPut h $ encode $ encryptPayload (noncef $ helloNonce hello) hello |
116 | welcomeE <- withSize $ fmap decode . hGet h . constSize | 118 | welcomeE <- withSize $ fmap decode . hGet h . constSize |
117 | let Right welcome = welcomeE >>= \w -> decryptPayload (noncef $ welcomeNonce w) w | 119 | let Right welcome = welcomeE >>= \w -> decryptPayload (noncef $ welcomeNonce w) w |
120 | dput XTCP $ "TCP:" ++ show addr ++ " --> " ++ show welcome | ||
118 | noncef' <- lookupNonceFunction crypto skey (sessionPublicKey $ runIdentity $ welcomeData welcome) | 121 | noncef' <- lookupNonceFunction crypto skey (sessionPublicKey $ runIdentity $ welcomeData welcome) |
119 | nsend <- newMVar (sessionBaseNonce $ runIdentity $ helloData hello) | 122 | nsend <- newMVar (sessionBaseNonce $ runIdentity $ helloData hello) |
120 | nread <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome) | 123 | nread <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome) |
121 | let them = sessionPublicKey $ runIdentity $ welcomeData welcome | 124 | let them = sessionPublicKey $ runIdentity $ welcomeData welcome |
122 | return SessionProtocol | 125 | return SessionProtocol |
123 | { streamGoodbye = return () -- No goodbye packet? Seems rude. | 126 | { streamGoodbye = do |
124 | , streamDecode = do | 127 | dput XTCP $ "Closing " ++ show addr |
125 | decode <$> hGet h 2 >>= \case | 128 | return () -- No goodbye packet? Seems rude. |
126 | Left _ -> return Nothing | 129 | , streamDecode = |
127 | Right len -> do | 130 | let go = decode <$> hGet h 2 >>= \case |
128 | decode <$> hGet h (fromIntegral (len :: Word16)) >>= \case | 131 | Left e -> do |
129 | Left _ -> return Nothing | 132 | dput XTCP $ "TCP: Failed to get length: " ++ e |
130 | Right x -> do | 133 | return Nothing |
131 | n24 <- takeMVar nread | 134 | Right len -> do |
132 | let r = decrypt (noncef' n24) x >>= decodePlain | 135 | decode <$> hGet h (fromIntegral (len :: Word16)) >>= \case |
133 | putMVar nread (incrementNonce24 n24) | 136 | Left e -> do |
134 | return $ either (const Nothing) Just r | 137 | dput XTCP $ "TCP: Failed to decode packet." |
138 | return Nothing | ||
139 | Right x -> do | ||
140 | n24 <- takeMVar nread | ||
141 | let r = decrypt (noncef' n24) x >>= decodePlain | ||
142 | putMVar nread (incrementNonce24 n24) | ||
143 | either (dput XTCP) | ||
144 | (\x' -> do | ||
145 | dput XTCP $ "TCP:" ++ show addr ++ " --> " ++ show x' | ||
146 | return ()) | ||
147 | r | ||
148 | return $ either (const Nothing) Just r | ||
149 | in go `catchIOError` \e -> do | ||
150 | dput XTCP $ "TCP exception: " ++ show e | ||
151 | return Nothing | ||
135 | , streamEncode = \y -> do | 152 | , streamEncode = \y -> do |
136 | n24 <- takeMVar nsend | 153 | n24 <- takeMVar nsend |
154 | dput XTCP $ "TCP:" ++ show addr ++ " <-- " ++ show y | ||
137 | let bs = encode $ encrypt (noncef' n24) $ encodePlain y | 155 | let bs = encode $ encrypt (noncef' n24) $ encodePlain y |
138 | hPut h $ encode (fromIntegral $ Data.ByteString.length bs :: Word16) | 156 | hPut h $ encode (fromIntegral $ Data.ByteString.length bs :: Word16) |
139 | <> bs | 157 | <> bs |