summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Data/Tox/Relay.hs10
-rw-r--r--src/Network/Tox.hs10
-rw-r--r--src/Network/Tox/Onion/Transport.hs93
-rw-r--r--src/Network/Tox/Transport.hs5
4 files changed, 89 insertions, 29 deletions
diff --git a/src/Data/Tox/Relay.hs b/src/Data/Tox/Relay.hs
index f801d1cd..82fef126 100644
--- a/src/Data/Tox/Relay.hs
+++ b/src/Data/Tox/Relay.hs
@@ -48,11 +48,11 @@ data RelayPacket
48 | OnionPacket (OnionRequest N0) 48 | OnionPacket (OnionRequest N0)
49 | OnionPacketResponse (OnionResponse N1) 49 | OnionPacketResponse (OnionResponse N1)
50 -- 0x0A through 0x0F reserved for future use. 50 -- 0x0A through 0x0F reserved for future use.
51 | RelayData ConId ByteString -- Word8 is a connection id. Encoded as number 16 to 255. 51 | RelayData ByteString ConId -- Word8 is a connection id. Encoded as number 16 to 255.
52 deriving (Eq,Ord,Show,Data) 52 deriving (Eq,Ord,Show,Data)
53 53
54packetNumber :: RelayPacket -> Word8 54packetNumber :: RelayPacket -> Word8
55packetNumber (RelayData (ConId conid) _) = conid -- 0 to 15 not allowed. 55packetNumber (RelayData _ (ConId conid)) = conid -- 0 to 15 not allowed.
56packetNumber rp = fromIntegral $ pred $ constrIndex $ toConstr rp 56packetNumber rp = fromIntegral $ pred $ constrIndex $ toConstr rp
57 57
58instance Sized RelayPacket where 58instance Sized RelayPacket where
@@ -71,7 +71,7 @@ instance Sized RelayPacket where
71 OnionPacketResponse answer -> case contramap (`asTypeOf` answer) size of 71 OnionPacketResponse answer -> case contramap (`asTypeOf` answer) size of
72 ConstSize n -> n 72 ConstSize n -> n
73 VarSize f -> f answer 73 VarSize f -> f answer
74 RelayData _ bs -> B.length bs 74 RelayData bs _ -> B.length bs
75 75
76instance Serialize RelayPacket where 76instance Serialize RelayPacket where
77 77
@@ -88,7 +88,7 @@ instance Serialize RelayPacket where
88 7 -> OOBRecv <$> getPublicKey <*> (remaining >>= getBytes) 88 7 -> OOBRecv <$> getPublicKey <*> (remaining >>= getBytes)
89 8 -> OnionPacket <$> get 89 8 -> OnionPacket <$> get
90 9 -> OnionPacketResponse <$> get 90 9 -> OnionPacketResponse <$> get
91 conid -> RelayData (ConId conid) <$> (remaining >>= getBytes) 91 conid -> (`RelayData` ConId conid) <$> (remaining >>= getBytes)
92 92
93 put rp = do 93 put rp = do
94 putWord8 $ packetNumber rp 94 putWord8 $ packetNumber rp
@@ -103,7 +103,7 @@ instance Serialize RelayPacket where
103 OOBRecv k bs -> putPublicKey k >> putByteString bs 103 OOBRecv k bs -> putPublicKey k >> putByteString bs
104 OnionPacket query -> put query 104 OnionPacket query -> put query
105 OnionPacketResponse answer -> put answer 105 OnionPacketResponse answer -> put answer
106 RelayData _ bs -> putByteString bs 106 RelayData bs _ -> putByteString bs
107 107
108-- | Initial client-to-server handshake message. 108-- | Initial client-to-server handshake message.
109newtype Hello (f :: * -> *) = Hello (Asymm (f HelloData)) 109newtype Hello (f :: * -> *) = Hello (Asymm (f HelloData))
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs
index ddb22d50..b22cfdf3 100644
--- a/src/Network/Tox.hs
+++ b/src/Network/Tox.hs
@@ -271,10 +271,11 @@ newTox :: TVar Onion.AnnouncedKeys -- ^ Store of announced keys we are a rende
271 -> SockAddr -- ^ Bind-address to listen on. 271 -> SockAddr -- ^ Bind-address to listen on.
272 -> ( ContactInfo extra -> SockAddr -> Session -> IO () ) 272 -> ( ContactInfo extra -> SockAddr -> Session -> IO () )
273 -> Maybe SecretKey -- ^ Optional DHT secret key to use. 273 -> Maybe SecretKey -- ^ Optional DHT secret key to use.
274 -> ( Int -> Onion.OnionResponse Onion.N1 -> IO () ) -- ^ TCP-bound onion responses.
274 -> IO (Tox extra) 275 -> IO (Tox extra)
275newTox keydb addr onsess suppliedDHTKey = do 276newTox keydb addr onsess suppliedDHTKey tcp = do
276 (udp,sock) <- {- addVerbosity <$> -} udpTransport' addr 277 (udp,sock) <- {- addVerbosity <$> -} udpTransport' addr
277 tox <- newToxOverTransport keydb addr onsess suppliedDHTKey udp 278 tox <- newToxOverTransport keydb addr onsess suppliedDHTKey udp tcp
278 return tox { toxAnnounceToLan = announceToLan sock (key2id $ transportPublic $ toxCryptoKeys tox) } 279 return tox { toxAnnounceToLan = announceToLan sock (key2id $ transportPublic $ toxCryptoKeys tox) }
279 280
280-- | This version of 'newTox' is useful for automated tests using 'testPairTransport'. 281-- | This version of 'newTox' is useful for automated tests using 'testPairTransport'.
@@ -283,8 +284,9 @@ newToxOverTransport :: TVar Onion.AnnouncedKeys
283 -> ( ContactInfo extra -> SockAddr -> Session -> IO () ) 284 -> ( ContactInfo extra -> SockAddr -> Session -> IO () )
284 -> Maybe SecretKey 285 -> Maybe SecretKey
285 -> Onion.UDPTransport 286 -> Onion.UDPTransport
287 -> ( Int -> Onion.OnionResponse Onion.N1 -> IO () ) -- ^ TCP-bound onion responses.
286 -> IO (Tox extra) 288 -> IO (Tox extra)
287newToxOverTransport keydb addr onNewSession suppliedDHTKey udp = do 289newToxOverTransport keydb addr onNewSession suppliedDHTKey udp tcp = do
288 roster <- newContactInfo 290 roster <- newContactInfo
289 crypto0 <- newCrypto 291 crypto0 <- newCrypto
290 let -- patch in supplied DHT key 292 let -- patch in supplied DHT key
@@ -306,7 +308,7 @@ newToxOverTransport keydb addr onNewSession suppliedDHTKey udp = do
306 308
307 mkrouting <- DHT.newRouting addr crypto updateIP updateIP 309 mkrouting <- DHT.newRouting addr crypto updateIP updateIP
308 orouter <- newOnionRouter $ dput XRoutes 310 orouter <- newOnionRouter $ dput XRoutes
309 (cryptonet,dhtcrypt,onioncrypt,dtacrypt,handshakes) <- toxTransport crypto orouter lookupClose udp 311 (cryptonet,dhtcrypt,onioncrypt,dtacrypt,handshakes) <- toxTransport crypto orouter lookupClose udp tcp
310 sessions <- initSessions (sendMessage cryptonet) 312 sessions <- initSessions (sendMessage cryptonet)
311 313
312 let dhtnet0 = layerTransportM (DHT.decrypt crypto) (DHT.encrypt crypto) dhtcrypt 314 let dhtnet0 = layerTransportM (DHT.decrypt crypto) (DHT.encrypt crypto) dhtcrypt
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs
index 160b99f7..f6d9ca31 100644
--- a/src/Network/Tox/Onion/Transport.hs
+++ b/src/Network/Tox/Onion/Transport.hs
@@ -50,6 +50,7 @@ module Network.Tox.Onion.Transport
50 , selectAlias 50 , selectAlias
51 , RouteId(..) 51 , RouteId(..)
52 , routeId 52 , routeId
53 , rewrap
53 ) where 54 ) where
54 55
55import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort) 56import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort)
@@ -87,6 +88,8 @@ import qualified Text.ParserCombinators.ReadP as RP
87import Data.Hashable 88import Data.Hashable
88import DPut 89import DPut
89import DebugTag 90import DebugTag
91import Data.Word64Map (fitsInInt)
92import Data.Bits (shiftR,shiftL)
90 93
91type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a 94type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a
92 95
@@ -270,20 +273,20 @@ encodeOnionAddr crypto getRoute (msg,OnionDestination _ ni (Just rid)) = do
270 return x 273 return x
271 274
272 275
273forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport 276forwardOnions :: TransportCrypto -> UDPTransport -> (Int -> OnionResponse N1 -> IO ()) {- ^ TCP relay send -} -> UDPTransport
274forwardOnions crypto udp = udp { awaitMessage = forwardAwait crypto udp } 277forwardOnions crypto udp sendTCP = udp { awaitMessage = forwardAwait crypto udp sendTCP }
275 278
276forwardAwait :: TransportCrypto -> UDPTransport -> HandleLo a -> IO a 279forwardAwait :: TransportCrypto -> UDPTransport -> (Int -> OnionResponse N1 -> IO ()) {- ^ TCP relay send -} -> HandleLo a -> IO a
277forwardAwait crypto udp kont = do 280forwardAwait crypto udp sendTCP kont = do
278 fix $ \another -> do 281 fix $ \another -> do
279 awaitMessage udp $ \case 282 awaitMessage udp $ \case
280 m@(Just (Right (bs,saddr))) -> case B.head bs of 283 m@(Just (Right (bs,saddr))) -> case B.head bs of
281 0x80 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N0) crypto saddr udp another 284 0x80 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N0) crypto (Addressed saddr) udp another
282 0x81 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N1) crypto saddr udp another 285 0x81 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N1) crypto (Addressed saddr) udp another
283 0x82 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N2) crypto saddr udp another 286 0x82 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N2) crypto (Addressed saddr) udp another
284 0x8c -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N3) crypto saddr udp another 287 0x8c -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N3) crypto saddr udp sendTCP another
285 0x8d -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N2) crypto saddr udp another 288 0x8d -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N2) crypto saddr udp sendTCP another
286 0x8e -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N1) crypto saddr udp another 289 0x8e -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N1) crypto saddr udp sendTCP another
287 _ -> kont m 290 _ -> kont m
288 m -> kont m 291 m -> kont m
289 292
@@ -392,6 +395,7 @@ instance (Sized (ReturnPath n)) => Sized (OnionResponse (S n)) where
392 size = contramap pathToOwner size <> contramap msgToOwner size 395 size = contramap pathToOwner size <> contramap msgToOwner size
393 396
394data Addressed a = Addressed { sockAddr :: SockAddr, unaddressed :: a } 397data Addressed a = Addressed { sockAddr :: SockAddr, unaddressed :: a }
398 | TCPIndex { tcpIndex :: Int, unaddressed :: a }
395 deriving (Eq,Show) 399 deriving (Eq,Show)
396 400
397instance Sized a => Sized (Addressed a) where 401instance Sized a => Sized (Addressed a) where
@@ -419,9 +423,24 @@ putForwardAddr saddr = fromMaybe (return $ error "unsupported SockAddr family")
419 IPv6 ip6 -> S.put (0x0a :: Word8) >> S.put ip6 423 IPv6 ip6 -> S.put (0x0a :: Word8) >> S.put ip6
420 S.put port 424 S.put port
421 425
426addrToIndex :: SockAddr -> Int
427addrToIndex (SockAddrInet6 _ _ (lo, hi, _, _) _) =
428 if fitsInInt (Proxy :: Proxy Word64)
429 then fromIntegral lo + (fromIntegral hi `shiftL` 32)
430 else fromIntegral lo
431addrToIndex _ = 0
432
433indexToAddr :: Int -> SockAddr
434indexToAddr x = SockAddrInet6 0 0 (fromIntegral x, fromIntegral (x `shiftR` 32),0,0) 0
435
422instance Serialize a => Serialize (Addressed a) where 436instance Serialize a => Serialize (Addressed a) where
423 get = Addressed <$> getForwardAddr <*> get 437 get = do saddr <- getForwardAddr
438 a <- get
439 case sockAddrPort saddr of
440 Just 0 -> return $ TCPIndex (addrToIndex saddr) a
441 _ -> return $ Addressed saddr a
424 put (Addressed addr x) = putForwardAddr addr >> put x 442 put (Addressed addr x) = putForwardAddr addr >> put x
443 put (TCPIndex idx x) = putForwardAddr (indexToAddr idx) >> put x
425 444
426data N0 445data N0
427data S n 446data S n
@@ -529,31 +548,55 @@ instance (Serialize (Encrypted (Addressed (Forwarding n msg)))) => Serialize (Fo
529 get = Forwarding <$> getPublicKey <*> get 548 get = Forwarding <$> getPublicKey <*> get
530 put (Forwarding k x) = putPublicKey k >> put x 549 put (Forwarding k x) = putPublicKey k >> put x
531 550
551rewrap :: (ThreeMinus n ~ S (ThreeMinus (S n)),
552 Serialize (ReturnPath n),
553 Serialize
554 (Forwarding (ThreeMinus (S n)) (OnionMessage Encrypted))) =>
555 TransportCrypto
556 -> (forall x. x -> Addressed x)
557 -> OnionRequest n
558 -> IO (Either String (OnionRequest (S n), SockAddr))
559rewrap crypto saddr (OnionRequest nonce msg rpath) = do
560 (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto
561 <*> transportNewNonce crypto )
562 peeled <- peelOnion crypto nonce msg
563 return $ peeled >>= \case
564 Addressed dst msg'
565 -> Right (OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath, dst)
566 _ -> Left "Onion forward to TCP client?"
567
532handleOnionRequest :: forall a proxy n. 568handleOnionRequest :: forall a proxy n.
533 ( LessThanThree n 569 ( LessThanThree n
534 , KnownPeanoNat n 570 , KnownPeanoNat n
535 , Sized (ReturnPath n) 571 , Sized (ReturnPath n)
536 , Typeable n 572 , Typeable n
537 ) => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a 573 ) => proxy n -> TransportCrypto -> (forall x. x -> Addressed x) -> UDPTransport -> IO a -> OnionRequest n -> IO a
538handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do 574handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do
539 let n = peanoVal rpath 575 let n = peanoVal rpath
540 dput XOnion $ "handleOnionRequest " ++ show n 576 dput XOnion $ "handleOnionRequest " ++ show n
541 (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto 577 (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto
542 <*> transportNewNonce crypto ) 578 <*> transportNewNonce crypto )
543 peeled <- peelOnion crypto nonce msg 579 peeled <- peelOnion crypto nonce msg
580 let showDestination = case saddr () of
581 Addressed a _ -> either show show $ either4or6 a
582 TCPIndex i _ -> "TCP" ++ show [i]
583
544 case peeled of 584 case peeled of
545 Left e -> do 585 Left e -> do
546 -- todo report encryption error 586 -- todo report encryption error
547 dput XOnion $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), e] 587 dput XOnion $ unwords [ "peelOnion:", show n, showDestination, e]
548 kont 588 kont
549 Right (Addressed dst msg') -> do 589 Right (Addressed dst msg') -> do
550 dput XOnion $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), "-->", either show show (either4or6 dst), "SUCCESS"] 590 dput XOnion $ unwords [ "peelOnion:", show n, showDestination, "-->", either show show (either4or6 dst), "SUCCESS"]
551 sendMessage udp dst (runPut $ putRequest $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath) 591 sendMessage udp dst (runPut $ putRequest $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath)
552 kont 592 kont
593 Right (TCPIndex {}) -> do
594 dput XUnexpected "handleOnionRequest: Onion forward to TCP client?"
595 kont
553 596
554wrapSymmetric :: Serialize (ReturnPath n) => 597wrapSymmetric :: Serialize (ReturnPath n) =>
555 SymmetricKey -> Nonce24 -> SockAddr -> ReturnPath n -> ReturnPath (S n) 598 SymmetricKey -> Nonce24 -> (forall x. x -> Addressed x) -> ReturnPath n -> ReturnPath (S n)
556wrapSymmetric sym n saddr rpath = ReturnPath n $ encryptSymmetric sym n (encodePlain $ Addressed saddr rpath) 599wrapSymmetric sym n saddr rpath = ReturnPath n $ encryptSymmetric sym n (encodePlain $ saddr rpath)
557 600
558peelSymmetric :: Serialize (Addressed (ReturnPath n)) 601peelSymmetric :: Serialize (Addressed (ReturnPath n))
559 => SymmetricKey -> ReturnPath (S n) -> Either String (Addressed (ReturnPath n)) 602 => SymmetricKey -> ReturnPath (S n) -> Either String (Addressed (ReturnPath n))
@@ -568,8 +611,16 @@ peelOnion :: Serialize (Addressed (Forwarding n t))
568peelOnion crypto nonce (Forwarding k fwd) = do 611peelOnion crypto nonce (Forwarding k fwd) = do
569 fmap runIdentity . uncomposed <$> decryptMessage crypto (dhtKey crypto) nonce (Right $ Asymm k nonce fwd) 612 fmap runIdentity . uncomposed <$> decryptMessage crypto (dhtKey crypto) nonce (Right $ Asymm k nonce fwd)
570 613
571handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a 614handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n), Typeable n) =>
572handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do 615 proxy (S n)
616 -> TransportCrypto
617 -> SockAddr
618 -> UDPTransport
619 -> (Int -> OnionResponse N1 -> IO ()) -- ^ TCP-relay onion send.
620 -> IO a
621 -> OnionResponse (S n)
622 -> IO a
623handleOnionResponse proxy crypto saddr udp sendTCP kont (OnionResponse path msg) = do
573 sym <- atomically $ transportSymmetric crypto 624 sym <- atomically $ transportSymmetric crypto
574 case peelSymmetric sym path of 625 case peelSymmetric sym path of
575 Left e -> do 626 Left e -> do
@@ -580,6 +631,12 @@ handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do
580 Right (Addressed dst path') -> do 631 Right (Addressed dst path') -> do
581 sendMessage udp dst (runPut $ putResponse $ OnionResponse path' msg) 632 sendMessage udp dst (runPut $ putResponse $ OnionResponse path' msg)
582 kont 633 kont
634 Right (TCPIndex dst path') -> do
635 -- This should only occur for OnionResponse N1
636 case gcast (OnionResponse path' msg) of
637 Just supported -> sendTCP dst supported
638 Nothing -> dput XUnexpected "handleOnionResponse: TCP-bound message not supported."
639 kont
583 640
584 641
585data AnnounceRequest = AnnounceRequest 642data AnnounceRequest = AnnounceRequest
diff --git a/src/Network/Tox/Transport.hs b/src/Network/Tox/Transport.hs
index 0b03ed19..0b34e8f8 100644
--- a/src/Network/Tox/Transport.hs
+++ b/src/Network/Tox/Transport.hs
@@ -22,14 +22,15 @@ toxTransport ::
22 -> OnionRouter 22 -> OnionRouter
23 -> (PublicKey -> IO (Maybe NodeInfo)) 23 -> (PublicKey -> IO (Maybe NodeInfo))
24 -> UDPTransport 24 -> UDPTransport
25 -> (Int -> OnionResponse N1 -> IO ()) -- ^ TCP-bound callback.
25 -> IO ( Transport String SockAddr (CryptoPacket Encrypted) 26 -> IO ( Transport String SockAddr (CryptoPacket Encrypted)
26 , Transport String NodeInfo (DHTMessage Encrypted8) 27 , Transport String NodeInfo (DHTMessage Encrypted8)
27 , Transport String (OnionDestination RouteId) (OnionMessage Encrypted) 28 , Transport String (OnionDestination RouteId) (OnionMessage Encrypted)
28 , Transport String AnnouncedRendezvous (PublicKey,OnionData) 29 , Transport String AnnouncedRendezvous (PublicKey,OnionData)
29 , Transport String SockAddr (Handshake Encrypted)) 30 , Transport String SockAddr (Handshake Encrypted))
30toxTransport crypto orouter closeLookup udp = do 31toxTransport crypto orouter closeLookup udp tcp = do
31 (netcrypto, udp0) <- partitionTransport parseCrypto encodeCrypto udp 32 (netcrypto, udp0) <- partitionTransport parseCrypto encodeCrypto udp
32 (dht,udp1) <- partitionTransportM (parseDHTAddr crypto) (fmap Just . encodeDHTAddr) $ forwardOnions crypto udp0 33 (dht,udp1) <- partitionTransportM (parseDHTAddr crypto) (fmap Just . encodeDHTAddr) $ forwardOnions crypto udp0 tcp
33 (onion1,udp2) <- partitionTransportM (parseOnionAddr $ lookupSender orouter) 34 (onion1,udp2) <- partitionTransportM (parseOnionAddr $ lookupSender orouter)
34 (encodeOnionAddr crypto $ lookupRoute orouter) 35 (encodeOnionAddr crypto $ lookupRoute orouter)
35 udp1 36 udp1