diff options
Diffstat (limited to 'src/Network/Tox')
-rw-r--r-- | src/Network/Tox/DHT/Transport.hs | 29 | ||||
-rw-r--r-- | src/Network/Tox/NodeId.hs | 6 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Handlers.hs | 30 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 72 | ||||
-rw-r--r-- | src/Network/Tox/Transport.hs | 5 |
5 files changed, 122 insertions, 20 deletions
diff --git a/src/Network/Tox/DHT/Transport.hs b/src/Network/Tox/DHT/Transport.hs index 187e23f2..16af0e3f 100644 --- a/src/Network/Tox/DHT/Transport.hs +++ b/src/Network/Tox/DHT/Transport.hs | |||
@@ -16,7 +16,8 @@ module Network.Tox.DHT.Transport | |||
16 | , Pong(..) | 16 | , Pong(..) |
17 | , GetNodes(..) | 17 | , GetNodes(..) |
18 | , SendNodes(..) | 18 | , SendNodes(..) |
19 | , DHTPublicKey | 19 | , DHTPublicKey(..) |
20 | , FriendRequest(..) | ||
20 | , CookieRequest | 21 | , CookieRequest |
21 | , Cookie | 22 | , Cookie |
22 | , DHTRequest | 23 | , DHTRequest |
@@ -35,10 +36,12 @@ import Network.QueryResponse | |||
35 | import Control.Arrow | 36 | import Control.Arrow |
36 | import Control.Monad | 37 | import Control.Monad |
37 | import Data.Bool | 38 | import Data.Bool |
38 | import qualified Data.ByteString as B | 39 | import qualified Data.ByteString as B |
39 | ;import Data.ByteString (ByteString) | 40 | ;import Data.ByteString (ByteString) |
41 | import Data.Functor.Contravariant | ||
42 | import Data.Monoid | ||
43 | import Data.Serialize as S | ||
40 | import Data.Tuple | 44 | import Data.Tuple |
41 | import Data.Serialize as S | ||
42 | import Data.Word | 45 | import Data.Word |
43 | import Network.Socket | 46 | import Network.Socket |
44 | 47 | ||
@@ -203,6 +206,13 @@ data DHTPublicKey = DHTPublicKey | |||
203 | , dhtpkNodes :: SendNodes -- other reachable nodes | 206 | , dhtpkNodes :: SendNodes -- other reachable nodes |
204 | } | 207 | } |
205 | 208 | ||
209 | -- int8_t (0x20 sent over onion, 0x12 for sent over net_crypto) | ||
210 | -- [uint32_t nospam][Message (UTF8) 1 to ONION_CLIENT_MAX_DATA_SIZE bytes] | ||
211 | data FriendRequest = FriendRequest | ||
212 | { friendNoSpam :: Word32 | ||
213 | , friendRequestText :: ByteString -- UTF8 | ||
214 | } | ||
215 | |||
206 | -- When sent as a DHT request packet (this is the data sent in the DHT request | 216 | -- When sent as a DHT request packet (this is the data sent in the DHT request |
207 | -- packet): | 217 | -- packet): |
208 | -- | 218 | -- |
@@ -231,6 +241,13 @@ instance Sized DHTPublicKey where | |||
231 | ConstSize nodes -> nodes | 241 | ConstSize nodes -> nodes |
232 | VarSize sznodes -> sznodes nodes | 242 | VarSize sznodes -> sznodes nodes |
233 | 243 | ||
244 | instance Sized Word32 where size = ConstSize 4 | ||
245 | |||
246 | -- FIXME: Inconsitently, this type does not include the 0x20 or 0x12 tag byte | ||
247 | -- where the DHTPublicKey type does include its tag. | ||
248 | instance Sized FriendRequest where | ||
249 | size = contramap friendNoSpam size <> contramap friendRequestText (VarSize B.length) | ||
250 | |||
234 | instance Serialize DHTPublicKey where | 251 | instance Serialize DHTPublicKey where |
235 | -- TODO: This should agree with Sized instance. | 252 | -- TODO: This should agree with Sized instance. |
236 | get = DHTPublicKey <$> get <*> getPublicKey <*> get | 253 | get = DHTPublicKey <$> get <*> getPublicKey <*> get |
@@ -239,6 +256,10 @@ instance Serialize DHTPublicKey where | |||
239 | putPublicKey key | 256 | putPublicKey key |
240 | put nodes | 257 | put nodes |
241 | 258 | ||
259 | instance Serialize FriendRequest where | ||
260 | get = FriendRequest <$> get <*> (remaining >>= getBytes) | ||
261 | put (FriendRequest nospam txt) = put nospam >> putByteString txt | ||
262 | |||
242 | newtype GetNodes = GetNodes NodeId | 263 | newtype GetNodes = GetNodes NodeId |
243 | deriving (Eq,Ord,Show,Read,S.Serialize) | 264 | deriving (Eq,Ord,Show,Read,S.Serialize) |
244 | 265 | ||
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs index bba56e27..20dc1854 100644 --- a/src/Network/Tox/NodeId.hs +++ b/src/Network/Tox/NodeId.hs | |||
@@ -213,8 +213,10 @@ instance FromJSON NodeInfo where | |||
213 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) | 213 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) |
214 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | 214 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) |
215 | let (bs,_) = Base16.decode (C8.pack nidstr) | 215 | let (bs,_) = Base16.decode (C8.pack nidstr) |
216 | guard (B.length bs == 32) | 216 | enid = Base64.decode (C8.pack $ 'A' : map (nmtoken64 False) nidstr) |
217 | return $ NodeInfo (bs2id bs) ip (fromIntegral (portnum :: Word16)) | 217 | idbs <- (guard (B.length bs == 32) >> return bs) |
218 | <|> either fail (return . B.drop 1) enid | ||
219 | return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16)) | ||
218 | 220 | ||
219 | getIP :: Word8 -> S.Get IP | 221 | getIP :: Word8 -> S.Get IP |
220 | getIP 0x02 = IPv4 <$> S.get | 222 | getIP 0x02 = IPv4 <$> S.get |
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs index 167df336..439de709 100644 --- a/src/Network/Tox/Onion/Handlers.hs +++ b/src/Network/Tox/Onion/Handlers.hs | |||
@@ -130,7 +130,7 @@ toOnionDestination :: AnnouncedRoute -> OnionDestination r | |||
130 | toOnionDestination (AnnouncedRoute ni rpath) = OnionToOwner ni rpath | 130 | toOnionDestination (AnnouncedRoute ni rpath) = OnionToOwner ni rpath |
131 | 131 | ||
132 | data AnnouncedKeys = AnnouncedKeys | 132 | data AnnouncedKeys = AnnouncedKeys |
133 | { keyByAge :: !(PSQ NodeId (Down POSIXTime)) -- timeout of 300 seconds | 133 | { keyByAge :: !(PSQ NodeId (Down POSIXTime)) -- TODO: timeout of 300 seconds |
134 | , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int,AnnouncedRoute)) | 134 | , keyAssoc :: !(MinMaxPSQ' NodeId NodeDistance (Int,AnnouncedRoute)) |
135 | } | 135 | } |
136 | 136 | ||
@@ -160,15 +160,6 @@ handlers net routing toks keydb AnnounceType | |||
160 | handlers net _ _ keydb _ = Just $ NoReply Right $ dataToRouteH keydb net | 160 | handlers net _ _ keydb _ = Just $ NoReply Right $ dataToRouteH keydb net |
161 | 161 | ||
162 | 162 | ||
163 | data Rendezvous = Rendezvous | ||
164 | { rendezvousKey :: PublicKey | ||
165 | , rendezvousNode :: NodeInfo | ||
166 | } | ||
167 | deriving Eq | ||
168 | |||
169 | instance Show Rendezvous where | ||
170 | show (Rendezvous k ni) = concat [show $ key2id k, ":", show ni] | ||
171 | |||
172 | toxidSearch :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int)) | 163 | toxidSearch :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int)) |
173 | -> Client r | 164 | -> Client r |
174 | -> Search NodeId (IP, PortNumber) (Maybe Nonce32) NodeInfo Rendezvous | 165 | -> Search NodeId (IP, PortNumber) (Maybe Nonce32) NodeInfo Rendezvous |
@@ -211,6 +202,25 @@ unwrapAnnounceResponse ni (AnnounceResponse is_stored (SendNodes ns)) | |||
211 | SendBackKey k -> (ns, [Rendezvous k ni], Nothing) | 202 | SendBackKey k -> (ns, [Rendezvous k ni], Nothing) |
212 | Acknowledged n32 -> (ns, [], Just n32) | 203 | Acknowledged n32 -> (ns, [], Just n32) |
213 | 204 | ||
205 | -- TODO Announce key to announce peers. | ||
206 | -- | ||
207 | -- Announce Peers are only put in the 8 closest peers array if they respond | ||
208 | -- to an announce request. If the peers fail to respond to 3 announce | ||
209 | -- requests they are deemed timed out and removed. | ||
210 | -- | ||
211 | -- ... | ||
212 | -- | ||
213 | -- For this reason, after the peer is announced successfully for 17 seconds, | ||
214 | -- announce packets are sent aggressively every 3 seconds to each known close | ||
215 | -- peer (in the list of 8 peers) to search aggressively for peers that know | ||
216 | -- the peer we are searching for. | ||
217 | |||
218 | -- TODO | ||
219 | -- If toxcore goes offline (no onion traffic for 20 seconds) toxcore will | ||
220 | -- aggressively reannounce itself and search for friends as if it was just | ||
221 | -- started. | ||
222 | |||
223 | |||
214 | announce :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int)) | 224 | announce :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int)) |
215 | -> Client r | 225 | -> Client r |
216 | -> NodeId | 226 | -> NodeId |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 989b06fd..3e3596a6 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -17,9 +17,12 @@ | |||
17 | module Network.Tox.Onion.Transport | 17 | module Network.Tox.Onion.Transport |
18 | ( parseOnionAddr | 18 | ( parseOnionAddr |
19 | , encodeOnionAddr | 19 | , encodeOnionAddr |
20 | , parseDataToRoute | ||
21 | , encodeDataToRoute | ||
20 | , forwardOnions | 22 | , forwardOnions |
21 | , OnionDestination(..) | 23 | , OnionDestination(..) |
22 | , OnionMessage(..) | 24 | , OnionMessage(..) |
25 | , Rendezvous(..) | ||
23 | , DataToRoute(..) | 26 | , DataToRoute(..) |
24 | , AnnounceResponse(..) | 27 | , AnnounceResponse(..) |
25 | , AnnounceRequest(..) | 28 | , AnnounceRequest(..) |
@@ -44,7 +47,7 @@ import Network.QueryResponse | |||
44 | import Crypto.Tox hiding (encrypt,decrypt) | 47 | import Crypto.Tox hiding (encrypt,decrypt) |
45 | import Network.Tox.NodeId | 48 | import Network.Tox.NodeId |
46 | import qualified Crypto.Tox as ToxCrypto | 49 | import qualified Crypto.Tox as ToxCrypto |
47 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes(..),nodeInfo,DHTPublicKey,asymNodeInfo) | 50 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes(..),nodeInfo,DHTPublicKey,FriendRequest,asymNodeInfo) |
48 | 51 | ||
49 | import Debug.Trace | 52 | import Debug.Trace |
50 | import Control.Arrow | 53 | import Control.Arrow |
@@ -561,13 +564,39 @@ instance Serialize DataToRoute where | |||
561 | get = DataToRoute <$> getPublicKey <*> get | 564 | get = DataToRoute <$> getPublicKey <*> get |
562 | put (DataToRoute k dta) = putPublicKey k >> put dta | 565 | put (DataToRoute k dta) = putPublicKey k >> put dta |
563 | 566 | ||
564 | data OnionData = OnionDHTPublicKey DHTPublicKey -- 0x9c | 567 | data OnionData |
568 | = -- | type 0x9c | ||
569 | -- | ||
570 | -- We send this packet every 30 seconds if there is more than one peer (in | ||
571 | -- the 8) that says they our friend is announced on them. This packet can | ||
572 | -- also be sent through the DHT module as a DHT request packet (see DHT) if | ||
573 | -- we know the DHT public key of the friend and are looking for them in the | ||
574 | -- DHT but have not connected to them yet. 30 second is a reasonable | ||
575 | -- timeout to not flood the network with too many packets while making sure | ||
576 | -- the other will eventually receive the packet. Since packets are sent | ||
577 | -- through every peer that knows the friend, resending it right away | ||
578 | -- without waiting has a high likelihood of failure as the chances of | ||
579 | -- packet loss happening to all (up to to 8) packets sent is low. | ||
580 | -- | ||
581 | -- If a friend is online and connected to us, the onion will stop all of | ||
582 | -- its actions for that friend. If the peer goes offline it will restart | ||
583 | -- searching for the friend as if toxcore was just started. | ||
584 | OnionDHTPublicKey DHTPublicKey | ||
585 | | -- | type 0x20 | ||
586 | -- | ||
587 | -- | ||
588 | OnionFriendRequest FriendRequest -- 0x20 | ||
565 | 589 | ||
566 | instance Sized OnionData where | 590 | instance Sized OnionData where |
567 | size = VarSize $ \(OnionDHTPublicKey dhtpk) -> case size of | 591 | size = VarSize $ \case |
592 | OnionDHTPublicKey dhtpk -> case size of | ||
568 | ConstSize n -> n -- Override because OnionData probably | 593 | ConstSize n -> n -- Override because OnionData probably |
569 | -- should be treated as variable sized. | 594 | -- should be treated as variable sized. |
570 | VarSize f -> f dhtpk | 595 | VarSize f -> f dhtpk |
596 | -- FIXME: inconsitantly, we have to add in the tag byte for this case. | ||
597 | OnionFriendRequest req -> 1 + case size of | ||
598 | ConstSize n -> n | ||
599 | VarSize f -> f req | ||
571 | 600 | ||
572 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> (OnionMessage Encrypted, OnionDestination r) | 601 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> (OnionMessage Encrypted, OnionDestination r) |
573 | encrypt crypto msg rpath = ( transcode ( (. (runIdentity . either id assymData)) | 602 | encrypt crypto msg rpath = ( transcode ( (. (runIdentity . either id assymData)) |
@@ -625,12 +654,14 @@ sequenceMessage (OnionAnnounce a) = fmap OnionAnnounce $ sequenceA $ fmap | |||
625 | sequenceMessage (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 <$> uncomposed dta | 654 | sequenceMessage (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 <$> uncomposed dta |
626 | sequenceMessage (OnionToRoute pub a) = pure $ OnionToRoute pub a | 655 | sequenceMessage (OnionToRoute pub a) = pure $ OnionToRoute pub a |
627 | sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a | 656 | sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a |
657 | -- sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a | ||
628 | 658 | ||
629 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> OnionMessage f -> OnionMessage g | 659 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> OnionMessage f -> OnionMessage g |
630 | transcode f (OnionAnnounce a) = OnionAnnounce $ a { assymData = f (assymNonce a) (Right a) } | 660 | transcode f (OnionAnnounce a) = OnionAnnounce $ a { assymData = f (assymNonce a) (Right a) } |
631 | transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta | 661 | transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta |
632 | transcode f (OnionToRoute pub a) = OnionToRoute pub a | 662 | transcode f (OnionToRoute pub a) = OnionToRoute pub a |
633 | transcode f (OnionToRouteResponse a) = OnionToRouteResponse a | 663 | transcode f (OnionToRouteResponse a) = OnionToRouteResponse a |
664 | -- transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { assymData = f (assymNonce a) (Right a) } | ||
634 | 665 | ||
635 | 666 | ||
636 | data OnionRoute = OnionRoute | 667 | data OnionRoute = OnionRoute |
@@ -673,3 +704,38 @@ wrapOnion :: Serialize (Forwarding n msg) => | |||
673 | -> Forwarding (S n) msg | 704 | -> Forwarding (S n) msg |
674 | wrapOnion skey nonce destkey saddr fwd = | 705 | wrapOnion skey nonce destkey saddr fwd = |
675 | Forwarding (toPublic skey) $ encryptMessage skey destkey nonce (Addressed saddr fwd) | 706 | Forwarding (toPublic skey) $ encryptMessage skey destkey nonce (Addressed saddr fwd) |
707 | |||
708 | |||
709 | -- TODO | ||
710 | -- Two types of packets may be sent to Rendezvous via OnionToRoute requests. | ||
711 | -- | ||
712 | -- (1) DHT public key packet (0x9c) | ||
713 | -- | ||
714 | -- (2) Friend request | ||
715 | data Rendezvous = Rendezvous | ||
716 | { rendezvousKey :: PublicKey | ||
717 | , rendezvousNode :: NodeInfo | ||
718 | } | ||
719 | deriving Eq | ||
720 | |||
721 | instance Show Rendezvous where | ||
722 | show (Rendezvous k ni) = concat [show $ key2id k, ":", show ni] | ||
723 | |||
724 | |||
725 | |||
726 | parseDataToRoute | ||
727 | :: TransportCrypto | ||
728 | -> (OnionMessage Encrypted,OnionDestination r) | ||
729 | -> Either (Assym (Encrypted DataToRoute),Rendezvous) (OnionMessage Encrypted, OnionDestination r) | ||
730 | parseDataToRoute crypto (OnionToRouteResponse dta, od) | ||
731 | = Left ( dta | ||
732 | , Rendezvous (onionAliasPublic crypto) $ onionNodeInfo od ) | ||
733 | parseDataToRoute _ msg = Right msg | ||
734 | |||
735 | encodeDataToRoute :: TransportCrypto | ||
736 | -> (Assym (Encrypted DataToRoute),Rendezvous) | ||
737 | -> Maybe (OnionMessage Encrypted,OnionDestination r) | ||
738 | encodeDataToRoute crypto (dta, Rendezvous pub ni) | ||
739 | = Just ( OnionToRoute pub -- Public key of destination node | ||
740 | dta | ||
741 | , OnionDestination ni Nothing ) | ||
diff --git a/src/Network/Tox/Transport.hs b/src/Network/Tox/Transport.hs index d4e1a754..d915561f 100644 --- a/src/Network/Tox/Transport.hs +++ b/src/Network/Tox/Transport.hs | |||
@@ -24,15 +24,18 @@ toxTransport :: | |||
24 | -> UDPTransport | 24 | -> UDPTransport |
25 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) | 25 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) |
26 | , Transport String (OnionDestination RouteId) (OnionMessage Encrypted) | 26 | , Transport String (OnionDestination RouteId) (OnionMessage Encrypted) |
27 | , Transport String Rendezvous (Assym (Encrypted DataToRoute)) | ||
27 | , Transport String SockAddr NetCrypto ) | 28 | , Transport String SockAddr NetCrypto ) |
28 | toxTransport crypto orouter closeLookup udp = do | 29 | toxTransport crypto orouter closeLookup udp = do |
29 | (dht,udp1) <- partitionTransport parseDHTAddr (Just . encodeDHTAddr) $ forwardOnions crypto udp | 30 | (dht,udp1) <- partitionTransport parseDHTAddr (Just . encodeDHTAddr) $ forwardOnions crypto udp |
30 | (onion,udp2) <- partitionTransportM (parseOnionAddr $ lookupSender orouter) | 31 | (onion1,udp2) <- partitionTransportM (parseOnionAddr $ lookupSender orouter) |
31 | (encodeOnionAddr $ lookupRoute orouter) | 32 | (encodeOnionAddr $ lookupRoute orouter) |
32 | udp1 | 33 | udp1 |
34 | (dta,onion) <- partitionTransport (parseDataToRoute crypto) (encodeDataToRoute crypto) onion1 | ||
33 | let netcrypto = layerTransport parseNetCrypto encodeNetCrypto udp2 | 35 | let netcrypto = layerTransport parseNetCrypto encodeNetCrypto udp2 |
34 | return ( forwardDHTRequests crypto closeLookup dht | 36 | return ( forwardDHTRequests crypto closeLookup dht |
35 | , onion | 37 | , onion |
38 | , dta | ||
36 | , netcrypto | 39 | , netcrypto |
37 | ) | 40 | ) |
38 | 41 | ||