diff options
Diffstat (limited to 'src/Network/Tox/Onion/Transport.hs')
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 93 |
1 files changed, 75 insertions, 18 deletions
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 | ||
55 | import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort) | 56 | import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort) |
@@ -87,6 +88,8 @@ import qualified Text.ParserCombinators.ReadP as RP | |||
87 | import Data.Hashable | 88 | import Data.Hashable |
88 | import DPut | 89 | import DPut |
89 | import DebugTag | 90 | import DebugTag |
91 | import Data.Word64Map (fitsInInt) | ||
92 | import Data.Bits (shiftR,shiftL) | ||
90 | 93 | ||
91 | type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a | 94 | type 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 | ||
273 | forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport | 276 | forwardOnions :: TransportCrypto -> UDPTransport -> (Int -> OnionResponse N1 -> IO ()) {- ^ TCP relay send -} -> UDPTransport |
274 | forwardOnions crypto udp = udp { awaitMessage = forwardAwait crypto udp } | 277 | forwardOnions crypto udp sendTCP = udp { awaitMessage = forwardAwait crypto udp sendTCP } |
275 | 278 | ||
276 | forwardAwait :: TransportCrypto -> UDPTransport -> HandleLo a -> IO a | 279 | forwardAwait :: TransportCrypto -> UDPTransport -> (Int -> OnionResponse N1 -> IO ()) {- ^ TCP relay send -} -> HandleLo a -> IO a |
277 | forwardAwait crypto udp kont = do | 280 | forwardAwait 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 | ||
394 | data Addressed a = Addressed { sockAddr :: SockAddr, unaddressed :: a } | 397 | data Addressed a = Addressed { sockAddr :: SockAddr, unaddressed :: a } |
398 | | TCPIndex { tcpIndex :: Int, unaddressed :: a } | ||
395 | deriving (Eq,Show) | 399 | deriving (Eq,Show) |
396 | 400 | ||
397 | instance Sized a => Sized (Addressed a) where | 401 | instance 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 | ||
426 | addrToIndex :: SockAddr -> Int | ||
427 | addrToIndex (SockAddrInet6 _ _ (lo, hi, _, _) _) = | ||
428 | if fitsInInt (Proxy :: Proxy Word64) | ||
429 | then fromIntegral lo + (fromIntegral hi `shiftL` 32) | ||
430 | else fromIntegral lo | ||
431 | addrToIndex _ = 0 | ||
432 | |||
433 | indexToAddr :: Int -> SockAddr | ||
434 | indexToAddr x = SockAddrInet6 0 0 (fromIntegral x, fromIntegral (x `shiftR` 32),0,0) 0 | ||
435 | |||
422 | instance Serialize a => Serialize (Addressed a) where | 436 | instance 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 | ||
426 | data N0 | 445 | data N0 |
427 | data S n | 446 | data 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 | ||
551 | rewrap :: (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)) | ||
559 | rewrap 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 | |||
532 | handleOnionRequest :: forall a proxy n. | 568 | handleOnionRequest :: 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 |
538 | handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do | 574 | handleOnionRequest 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 | ||
554 | wrapSymmetric :: Serialize (ReturnPath n) => | 597 | wrapSymmetric :: 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) |
556 | wrapSymmetric sym n saddr rpath = ReturnPath n $ encryptSymmetric sym n (encodePlain $ Addressed saddr rpath) | 599 | wrapSymmetric sym n saddr rpath = ReturnPath n $ encryptSymmetric sym n (encodePlain $ saddr rpath) |
557 | 600 | ||
558 | peelSymmetric :: Serialize (Addressed (ReturnPath n)) | 601 | peelSymmetric :: 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)) | |||
568 | peelOnion crypto nonce (Forwarding k fwd) = do | 611 | peelOnion 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 | ||
571 | handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a | 614 | handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n), Typeable n) => |
572 | handleOnionResponse 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 | ||
623 | handleOnionResponse 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 | ||
585 | data AnnounceRequest = AnnounceRequest | 642 | data AnnounceRequest = AnnounceRequest |