diff options
author | joe <joe@jerkface.net> | 2017-09-20 20:47:10 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-09-20 20:47:10 -0400 |
commit | 6b822e47e4995e4aaf4cb1cc034c34314bd51da2 (patch) | |
tree | 5e83ab1f500ba850b25bcdd5f4d54bf03809dd22 /src | |
parent | 447e9e53661edd7c633f757eb3403298849e4c35 (diff) |
Added outbound initiation addresses to the Onion transport.
Diffstat (limited to 'src')
-rw-r--r-- | src/Network/Tox.hs | 3 | ||||
-rw-r--r-- | src/Network/Tox/Crypto/Transport.hs | 1 | ||||
-rw-r--r-- | src/Network/Tox/DHT/Transport.hs | 1 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Handlers.hs | 20 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 57 | ||||
-rw-r--r-- | src/Network/Tox/Transport.hs | 2 |
6 files changed, 47 insertions, 37 deletions
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 17585dfd..7893d84a 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -235,7 +235,8 @@ newTox keydb addr = do | |||
235 | atomically $ newTVar nil { maxInterval = 20 } -- 20 second timeout on announce ping-ids. | 235 | atomically $ newTVar nil { maxInterval = 20 } -- 20 second timeout on announce ping-ids. |
236 | oniondrg <- drgNew | 236 | oniondrg <- drgNew |
237 | let onionnet = layerTransport (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt | 237 | let onionnet = layerTransport (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt |
238 | onionclient <- newClient oniondrg onionnet Onion.classify (const $ return $ Onion.OnionToMe addr) | 238 | onionclient <- newClient oniondrg onionnet Onion.classify |
239 | (const $ return $ either (const $ error "bad sockaddr") Onion.OnionDestination $ nodeInfo zeroID addr) | ||
239 | (Onion.handlers onionnet routing toks keydb) | 240 | (Onion.handlers onionnet routing toks keydb) |
240 | (const id) | 241 | (const id) |
241 | return Tox | 242 | return Tox |
diff --git a/src/Network/Tox/Crypto/Transport.hs b/src/Network/Tox/Crypto/Transport.hs index 09f7fda8..851de5d9 100644 --- a/src/Network/Tox/Crypto/Transport.hs +++ b/src/Network/Tox/Crypto/Transport.hs | |||
@@ -19,6 +19,7 @@ import Data.ByteString | |||
19 | import Data.Word | 19 | import Data.Word |
20 | import Crypto.Hash | 20 | import Crypto.Hash |
21 | 21 | ||
22 | |||
22 | data NetCrypto | 23 | data NetCrypto |
23 | = NetHandshake (Handshake Encrypted) | 24 | = NetHandshake (Handshake Encrypted) |
24 | | NetCrypto (CryptoPacket Encrypted) | 25 | | NetCrypto (CryptoPacket Encrypted) |
diff --git a/src/Network/Tox/DHT/Transport.hs b/src/Network/Tox/DHT/Transport.hs index 5e20709b..187e23f2 100644 --- a/src/Network/Tox/DHT/Transport.hs +++ b/src/Network/Tox/DHT/Transport.hs | |||
@@ -24,6 +24,7 @@ module Network.Tox.DHT.Transport | |||
24 | , encrypt | 24 | , encrypt |
25 | , decrypt | 25 | , decrypt |
26 | , dhtMessageType | 26 | , dhtMessageType |
27 | , asymNodeInfo | ||
27 | ) where | 28 | ) where |
28 | 29 | ||
29 | import Network.Tox.NodeId | 30 | import Network.Tox.NodeId |
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs index 9dc6177c..72398735 100644 --- a/src/Network/Tox/Onion/Handlers.hs +++ b/src/Network/Tox/Onion/Handlers.hs | |||
@@ -35,7 +35,7 @@ import Data.Bits | |||
35 | import Data.Ord | 35 | import Data.Ord |
36 | import Data.Functor.Identity | 36 | import Data.Functor.Identity |
37 | 37 | ||
38 | type Client = QR.Client String PacketKind TransactionId OnionToOwner Message | 38 | type Client = QR.Client String PacketKind TransactionId OnionDestination Message |
39 | type Message = OnionMessage Identity | 39 | type Message = OnionMessage Identity |
40 | 40 | ||
41 | classify :: Message -> MessageClass String PacketKind TransactionId | 41 | classify :: Message -> MessageClass String PacketKind TransactionId |
@@ -59,7 +59,7 @@ classify msg = go msg | |||
59 | -- The reason for this 20 second timeout in toxcore is that it gives a reasonable | 59 | -- The reason for this 20 second timeout in toxcore is that it gives a reasonable |
60 | -- time (20 to 40 seconds) for a peer to announce himself while taking in count | 60 | -- time (20 to 40 seconds) for a peer to announce himself while taking in count |
61 | -- all the possible delays with some extra seconds. | 61 | -- all the possible delays with some extra seconds. |
62 | announceH :: Routing -> TVar SessionTokens -> TVar AnnouncedKeys -> OnionToOwner -> AnnounceRequest -> IO AnnounceResponse | 62 | announceH :: Routing -> TVar SessionTokens -> TVar AnnouncedKeys -> OnionDestination -> AnnounceRequest -> IO AnnounceResponse |
63 | announceH routing toks keydb (OnionToOwner naddr retpath) req = do | 63 | announceH routing toks keydb (OnionToOwner naddr retpath) req = do |
64 | case () of | 64 | case () of |
65 | _ | announcePingId req == zeros32 | 65 | _ | announcePingId req == zeros32 |
@@ -89,16 +89,16 @@ announceH routing toks keydb (OnionToOwner naddr retpath) req = do | |||
89 | then Nonce32 . toPaddedByteString 32 <$> grantToken toks naddr | 89 | then Nonce32 . toPaddedByteString 32 <$> grantToken toks naddr |
90 | else return $ zeros32 | 90 | else return $ zeros32 |
91 | let k = case record of | 91 | let k = case record of |
92 | Nothing -> NotStored newtok | 92 | Nothing -> NotStored newtok |
93 | Just (OnionToOwner {}) | storing -> Acknowledged newtok | 93 | Just (OnionDestination {}) | storing -> Acknowledged newtok |
94 | Just (OnionToOwner ni _) -> SendBackKey $ id2key (nodeId ni) | 94 | Just (OnionToOwner ni _) -> SendBackKey $ id2key (nodeId ni) |
95 | let response = AnnounceResponse k ns | 95 | let response = AnnounceResponse k ns |
96 | hPutStrLn stderr $ unwords ["Announce:", show req, "-reply->", show response] | 96 | hPutStrLn stderr $ unwords ["Announce:", show req, "-reply->", show response] |
97 | return response | 97 | return response |
98 | 98 | ||
99 | dataToRouteH :: | 99 | dataToRouteH :: |
100 | TVar AnnouncedKeys | 100 | TVar AnnouncedKeys |
101 | -> Transport err OnionToOwner (OnionMessage f) | 101 | -> Transport err OnionDestination (OnionMessage f) |
102 | -> addr | 102 | -> addr |
103 | -> OnionMessage f | 103 | -> OnionMessage f |
104 | -> IO () | 104 | -> IO () |
@@ -118,11 +118,11 @@ type NodeDistance = NodeId | |||
118 | 118 | ||
119 | data AnnouncedKeys = AnnouncedKeys | 119 | data AnnouncedKeys = AnnouncedKeys |
120 | { keyByAge :: !(PSQ NodeId (Down POSIXTime)) -- timeout of 300 seconds | 120 | { keyByAge :: !(PSQ NodeId (Down POSIXTime)) -- timeout of 300 seconds |
121 | , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int,OnionToOwner)) | 121 | , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int,OnionDestination)) |
122 | } | 122 | } |
123 | 123 | ||
124 | 124 | ||
125 | insertKey :: POSIXTime -> NodeId -> OnionToOwner -> NodeDistance -> AnnouncedKeys -> AnnouncedKeys | 125 | insertKey :: POSIXTime -> NodeId -> OnionDestination -> NodeDistance -> AnnouncedKeys -> AnnouncedKeys |
126 | insertKey tm pub toxpath d keydb = AnnouncedKeys | 126 | insertKey tm pub toxpath d keydb = AnnouncedKeys |
127 | { keyByAge = PSQ.insert pub (Down tm) (keyByAge keydb) | 127 | { keyByAge = PSQ.insert pub (Down tm) (keyByAge keydb) |
128 | , keyAssoc = case MinMaxPSQ.lookup' pub (keyAssoc keydb) of | 128 | , keyAssoc = case MinMaxPSQ.lookup' pub (keyAssoc keydb) of |
@@ -134,12 +134,12 @@ areq :: Message -> Either String AnnounceRequest | |||
134 | areq (OnionAnnounce assym) = Right $ fst $ runIdentity $ assymData assym | 134 | areq (OnionAnnounce assym) = Right $ fst $ runIdentity $ assymData assym |
135 | areq _ = Left "Unexpected non-announce OnionMessage" | 135 | areq _ = Left "Unexpected non-announce OnionMessage" |
136 | 136 | ||
137 | handlers :: Transport err OnionToOwner Message | 137 | handlers :: Transport err OnionDestination Message |
138 | -> Routing | 138 | -> Routing |
139 | -> TVar SessionTokens | 139 | -> TVar SessionTokens |
140 | -> TVar AnnouncedKeys | 140 | -> TVar AnnouncedKeys |
141 | -> PacketKind | 141 | -> PacketKind |
142 | -> Maybe (MethodHandler String TransactionId OnionToOwner Message) | 142 | -> Maybe (MethodHandler String TransactionId OnionDestination Message) |
143 | handlers net routing toks keydb AnnounceType | 143 | handlers net routing toks keydb AnnounceType |
144 | = Just | 144 | = Just |
145 | $ MethodHandler areq (\(TransactionId n8 n24) src dst -> OnionAnnounceResponse n8 n24 . Identity) | 145 | $ MethodHandler areq (\(TransactionId n8 n24) src dst -> OnionAnnounceResponse n8 n24 . Identity) |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 8c4df694..a521c39e 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -19,7 +19,7 @@ module Network.Tox.Onion.Transport | |||
19 | ( parseOnionAddr | 19 | ( parseOnionAddr |
20 | , encodeOnionAddr | 20 | , encodeOnionAddr |
21 | , forwardOnions | 21 | , forwardOnions |
22 | , OnionToOwner(..) | 22 | , OnionDestination(..) |
23 | , OnionMessage(..) | 23 | , OnionMessage(..) |
24 | , DataToRoute(..) | 24 | , DataToRoute(..) |
25 | , AnnounceResponse(..) | 25 | , AnnounceResponse(..) |
@@ -41,7 +41,7 @@ import Network.QueryResponse | |||
41 | import Crypto.Tox hiding (encrypt,decrypt) | 41 | import Crypto.Tox hiding (encrypt,decrypt) |
42 | import Network.Tox.NodeId | 42 | import Network.Tox.NodeId |
43 | import qualified Crypto.Tox as ToxCrypto | 43 | import qualified Crypto.Tox as ToxCrypto |
44 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey) | 44 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey,asymNodeInfo) |
45 | 45 | ||
46 | import Debug.Trace | 46 | import Debug.Trace |
47 | import Control.Arrow | 47 | import Control.Arrow |
@@ -87,11 +87,11 @@ deriving instance ( Show (f (AnnounceRequest, Nonce8)) | |||
87 | , Show (f DataToRoute) | 87 | , Show (f DataToRoute) |
88 | ) => Show (OnionMessage f) | 88 | ) => Show (OnionMessage f) |
89 | 89 | ||
90 | data OnionToOwner = OnionToOwner NodeInfo (ReturnPath N3) | 90 | data OnionDestination = OnionToOwner NodeInfo (ReturnPath N3) -- ^ Somebody else's path to us. |
91 | | OnionToMe SockAddr -- SockAddr is immediate peer in route | 91 | | OnionDestination NodeInfo -- ^ Our own onion-path. |
92 | deriving Show | 92 | deriving Show |
93 | 93 | ||
94 | onionKey :: OnionToOwner -> Maybe PublicKey | 94 | onionKey :: OnionDestination -> Maybe PublicKey |
95 | onionKey (OnionToOwner ni _) = Just $ id2key (nodeId ni) | 95 | onionKey (OnionToOwner ni _) = Just $ id2key (nodeId ni) |
96 | onionKey _ = Nothing | 96 | onionKey _ = Nothing |
97 | 97 | ||
@@ -120,7 +120,7 @@ instance Serialize (OnionMessage Encrypted) where | |||
120 | put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x | 120 | put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x |
121 | put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAssym a | 121 | put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAssym a |
122 | 122 | ||
123 | onionToOwner :: Assym a -> ReturnPath N3 -> SockAddr -> Either String OnionToOwner | 123 | onionToOwner :: Assym a -> ReturnPath N3 -> SockAddr -> Either String OnionDestination |
124 | onionToOwner assym ret3 saddr = do | 124 | onionToOwner assym ret3 saddr = do |
125 | ni <- nodeInfo (key2id $ senderKey assym) saddr | 125 | ni <- nodeInfo (key2id $ senderKey assym) saddr |
126 | return $ OnionToOwner ni ret3 | 126 | return $ OnionToOwner ni ret3 |
@@ -131,18 +131,18 @@ onion :: Sized msg => | |||
131 | ByteString | 131 | ByteString |
132 | -> SockAddr | 132 | -> SockAddr |
133 | -> Get (Assym (Encrypted msg) -> t) | 133 | -> Get (Assym (Encrypted msg) -> t) |
134 | -> Either String (t, OnionToOwner) | 134 | -> Either String (t, OnionDestination) |
135 | onion bs saddr getf = do (f,(assym,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs | 135 | onion bs saddr getf = do (f,(assym,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs |
136 | oaddr <- onionToOwner assym ret3 saddr | 136 | oaddr <- onionToOwner assym ret3 saddr |
137 | return (f assym, oaddr) | 137 | return (f assym, oaddr) |
138 | 138 | ||
139 | 139 | ||
140 | parseOnionAddr :: (ByteString, SockAddr) -> Either (OnionMessage Encrypted,OnionToOwner) (ByteString,SockAddr) | 140 | parseOnionAddr :: (ByteString, SockAddr) -> Either (OnionMessage Encrypted,OnionDestination) (ByteString,SockAddr) |
141 | parseOnionAddr (msg,saddr) | 141 | parseOnionAddr (msg,saddr) |
142 | | Just (typ,bs) <- B.uncons msg | 142 | | Just (typ,bs) <- B.uncons msg |
143 | , let right = Right (msg,saddr) | 143 | , let right = Right (msg,saddr) |
144 | query = either (const right) Left | 144 | query = either (const right) Left |
145 | response = either (const right) (Left . (, OnionToMe saddr)) | 145 | response = either (const right) (Left . \msg -> ( msg , replyAlias saddr msg )) |
146 | = case typ of | 146 | = case typ of |
147 | 0x83 -> query $ onion bs saddr (pure OnionAnnounce) -- Announce Request | 147 | 0x83 -> query $ onion bs saddr (pure OnionAnnounce) -- Announce Request |
148 | 0x85 -> query $ onion bs saddr (OnionToRoute <$> getPublicKey) -- Onion Data Request | 148 | 0x85 -> query $ onion bs saddr (OnionToRoute <$> getPublicKey) -- Onion Data Request |
@@ -154,22 +154,28 @@ getOnionReply :: Word8 -> Get (OnionMessage Encrypted) | |||
154 | getOnionReply 0x84 = OnionAnnounceResponse <$> get <*> get <*> get | 154 | getOnionReply 0x84 = OnionAnnounceResponse <$> get <*> get <*> get |
155 | getOnionReply 0x86 = OnionToRouteResponse <$> getOnionAssym | 155 | getOnionReply 0x86 = OnionToRouteResponse <$> getOnionAssym |
156 | 156 | ||
157 | replyAlias :: SockAddr -> OnionMessage Encrypted -> OnionDestination | ||
158 | replyAlias saddr (OnionAnnounceResponse _ _ _) | ||
159 | = OnionDestination | ||
160 | $ either (error "replyAlias: bad protocol") id | ||
161 | $ nodeInfo zeroID saddr -- TODO OnionAnnounceResponse has no sender key | ||
162 | replyAlias saddr (OnionToRouteResponse asym) | ||
163 | = OnionDestination $ asymNodeInfo saddr asym | ||
164 | |||
157 | putOnionMsg :: OnionMessage Encrypted -> Put | 165 | putOnionMsg :: OnionMessage Encrypted -> Put |
158 | putOnionMsg (OnionAnnounce a) = putOnionAssym 0x83 (return ()) a | 166 | putOnionMsg (OnionAnnounce a) = putOnionAssym 0x83 (return ()) a |
159 | putOnionMsg (OnionToRoute pubkey a) = putOnionAssym 0x85 (putPublicKey pubkey) a | 167 | putOnionMsg (OnionToRoute pubkey a) = putOnionAssym 0x85 (putPublicKey pubkey) a |
160 | putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x | 168 | putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x |
161 | putOnionMsg (OnionToRouteResponse a) = putOnionAssym 0x86 (return ()) a | 169 | putOnionMsg (OnionToRouteResponse a) = putOnionAssym 0x86 (return ()) a |
162 | 170 | ||
163 | encodeOnionAddr :: (OnionMessage Encrypted,OnionToOwner) -> (ByteString, SockAddr) | 171 | encodeOnionAddr :: (OnionMessage Encrypted,OnionDestination) -> (ByteString, SockAddr) |
164 | encodeOnionAddr (msg,OnionToOwner ni p) = ( runPut $ putResponse (OnionResponse p msg) | 172 | encodeOnionAddr (msg,OnionToOwner ni p) = ( runPut $ putResponse (OnionResponse p msg) |
165 | , nodeAddr ni ) | 173 | , nodeAddr ni ) |
166 | encodeOnionAddr (msg,OnionToMe a) = ( runPut (putOnionMsg msg), a) | 174 | encodeOnionAddr (msg,OnionDestination a) = ( runPut (putOnionMsg msg), nodeAddr a) -- TODO: Construct (OnionRequest N0)? |
167 | 175 | ||
168 | forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport -- HandleHi a -> IO a -> HandleLo a | 176 | forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport |
169 | forwardOnions crypto udp = udp { awaitMessage = forwardAwait crypto udp } | 177 | forwardOnions crypto udp = udp { awaitMessage = forwardAwait crypto udp } |
170 | 178 | ||
171 | -- forMe :: HandleHi | ||
172 | -- forThem :: handleLo | ||
173 | forwardAwait :: TransportCrypto -> UDPTransport -> HandleLo a -> IO a | 179 | forwardAwait :: TransportCrypto -> UDPTransport -> HandleLo a -> IO a |
174 | forwardAwait crypto udp kont = do | 180 | forwardAwait crypto udp kont = do |
175 | fix $ \another -> do | 181 | fix $ \another -> do |
@@ -520,26 +526,27 @@ instance Sized OnionData where | |||
520 | -- should be treated as variable sized. | 526 | -- should be treated as variable sized. |
521 | VarSize f -> f dhtpk | 527 | VarSize f -> f dhtpk |
522 | 528 | ||
523 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionToOwner -> (OnionMessage Encrypted, OnionToOwner) | 529 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination -> (OnionMessage Encrypted, OnionDestination) |
524 | encrypt crypto msg rpath = ( transcode (encryptMessage crypto okey) msg | 530 | encrypt crypto msg rpath = ( transcode ( (. (runIdentity . either id assymData)) |
531 | . encryptMessage skey okey) | ||
532 | msg | ||
525 | , rpath) | 533 | , rpath) |
526 | where | 534 | where |
535 | skey = transportSecret crypto | ||
536 | |||
527 | -- The OnionToMe case shouldn't happen, but we'll use our own public | 537 | -- The OnionToMe case shouldn't happen, but we'll use our own public |
528 | -- key in this situation. | 538 | -- key in this situation. |
529 | okey = fromMaybe (transportPublic crypto) $ onionKey rpath | 539 | okey = fromMaybe (transportPublic crypto) $ onionKey rpath |
530 | 540 | ||
541 | |||
531 | encryptMessage :: Serialize a => | 542 | encryptMessage :: Serialize a => |
532 | TransportCrypto -> PublicKey -> Nonce24 -> Either (Identity a) (Assym (Identity a)) -> Encrypted a | 543 | SecretKey -> PublicKey -> Nonce24 -> a -> Encrypted a |
533 | encryptMessage crypto destKey n (Right a) = ToxCrypto.encrypt secret plain | 544 | encryptMessage skey destKey n a = ToxCrypto.encrypt secret plain |
534 | where | ||
535 | secret = computeSharedSecret (transportSecret crypto) destKey n | ||
536 | plain = encodePlain $ runIdentity $ assymData a | ||
537 | encryptMessage crypto destKey n (Left x) = ToxCrypto.encrypt secret plain | ||
538 | where | 545 | where |
539 | secret = computeSharedSecret (transportSecret crypto) destKey n | 546 | secret = computeSharedSecret skey destKey n |
540 | plain = encodePlain $ runIdentity $ x | 547 | plain = encodePlain a |
541 | 548 | ||
542 | decrypt :: TransportCrypto -> OnionMessage Encrypted -> OnionToOwner -> Either String (OnionMessage Identity, OnionToOwner) | 549 | decrypt :: TransportCrypto -> OnionMessage Encrypted -> OnionDestination -> Either String (OnionMessage Identity, OnionDestination) |
543 | decrypt crypto msg addr = (, addr) <$> (sequenceMessage $ transcode (decryptMessage crypto) msg) | 550 | decrypt crypto msg addr = (, addr) <$> (sequenceMessage $ transcode (decryptMessage crypto) msg) |
544 | 551 | ||
545 | decryptMessage :: Serialize x => | 552 | decryptMessage :: Serialize x => |
diff --git a/src/Network/Tox/Transport.hs b/src/Network/Tox/Transport.hs index 24bd60b7..d99b6713 100644 --- a/src/Network/Tox/Transport.hs +++ b/src/Network/Tox/Transport.hs | |||
@@ -21,7 +21,7 @@ toxTransport :: | |||
21 | -> (PublicKey -> IO (Maybe NodeInfo)) | 21 | -> (PublicKey -> IO (Maybe NodeInfo)) |
22 | -> UDPTransport | 22 | -> UDPTransport |
23 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) | 23 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) |
24 | , Transport String OnionToOwner (OnionMessage Encrypted) | 24 | , Transport String OnionDestination (OnionMessage Encrypted) |
25 | , Transport String SockAddr NetCrypto ) | 25 | , Transport String SockAddr NetCrypto ) |
26 | toxTransport crypto closeLookup udp = do | 26 | toxTransport crypto closeLookup udp = do |
27 | (dht,udp1) <- partitionTransport parseDHTAddr encodeDHTAddr id $ forwardOnions crypto udp | 27 | (dht,udp1) <- partitionTransport parseDHTAddr encodeDHTAddr id $ forwardOnions crypto udp |