diff options
Diffstat (limited to 'dht')
-rw-r--r-- | dht/dht-client.cabal | 1 | ||||
-rw-r--r-- | dht/src/Data/Tox/Onion.hs | 3 | ||||
-rw-r--r-- | dht/src/Data/Tox/Relay.hs | 29 | ||||
-rw-r--r-- | dht/src/Network/Tox.hs | 6 | ||||
-rw-r--r-- | dht/src/Network/Tox/DHT/Handlers.hs | 9 | ||||
-rw-r--r-- | dht/src/Network/Tox/DHT/Transport.hs | 3 | ||||
-rw-r--r-- | dht/src/Network/Tox/NodeId.hs | 4 | ||||
-rw-r--r-- | dht/src/Network/Tox/Onion/Handlers.hs | 3 | ||||
-rw-r--r-- | dht/src/Network/Tox/TCP.hs | 5 | ||||
-rw-r--r-- | dht/src/Network/Tox/TCP/NodeId.hs | 89 |
10 files changed, 115 insertions, 37 deletions
diff --git a/dht/dht-client.cabal b/dht/dht-client.cabal index 19f4f2b3..24739767 100644 --- a/dht/dht-client.cabal +++ b/dht/dht-client.cabal | |||
@@ -98,6 +98,7 @@ library | |||
98 | Network.Tox.DHT.Transport | 98 | Network.Tox.DHT.Transport |
99 | Network.Tox.Handshake | 99 | Network.Tox.Handshake |
100 | Network.Tox.NodeId | 100 | Network.Tox.NodeId |
101 | Network.Tox.TCP.NodeId | ||
101 | Network.Tox.Avahi | 102 | Network.Tox.Avahi |
102 | Network.Tox.RelayPinger | 103 | Network.Tox.RelayPinger |
103 | Network.UPNP | 104 | Network.UPNP |
diff --git a/dht/src/Data/Tox/Onion.hs b/dht/src/Data/Tox/Onion.hs index 258a9f73..d3c8086d 100644 --- a/dht/src/Data/Tox/Onion.hs +++ b/dht/src/Data/Tox/Onion.hs | |||
@@ -25,6 +25,7 @@ import Crypto.Tox hiding (encrypt,decrypt) | |||
25 | import Network.Tox.NodeId | 25 | import Network.Tox.NodeId |
26 | import qualified Crypto.Tox as ToxCrypto | 26 | import qualified Crypto.Tox as ToxCrypto |
27 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes(..),nodeInfo,DHTPublicKey(..),FriendRequest,asymNodeInfo) | 27 | import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes(..),nodeInfo,DHTPublicKey(..),FriendRequest,asymNodeInfo) |
28 | import Network.Tox.TCP.NodeId (fromUDPNode) | ||
28 | 29 | ||
29 | import Control.Applicative | 30 | import Control.Applicative |
30 | import Control.Arrow | 31 | import Control.Arrow |
@@ -717,7 +718,7 @@ getNodeList = do | |||
717 | (:) n <$> (getNodeList <|> pure []) | 718 | (:) n <$> (getNodeList <|> pure []) |
718 | 719 | ||
719 | instance S.Serialize AnnounceResponse where | 720 | instance S.Serialize AnnounceResponse where |
720 | get = AnnounceResponse <$> S.get <*> (SendNodes <$> getNodeList) | 721 | get = AnnounceResponse <$> S.get <*> (SendNodes . map fromUDPNode <$> getNodeList) |
721 | put (AnnounceResponse st (SendNodes ns)) = S.put st >> mapM_ S.put ns | 722 | put (AnnounceResponse st (SendNodes ns)) = S.put st >> mapM_ S.put ns |
722 | 723 | ||
723 | data DataToRoute = DataToRoute | 724 | data DataToRoute = DataToRoute |
diff --git a/dht/src/Data/Tox/Relay.hs b/dht/src/Data/Tox/Relay.hs index f28a1685..64c90806 100644 --- a/dht/src/Data/Tox/Relay.hs +++ b/dht/src/Data/Tox/Relay.hs | |||
@@ -7,7 +7,10 @@ | |||
7 | {-# LANGUAGE PatternSynonyms #-} | 7 | {-# LANGUAGE PatternSynonyms #-} |
8 | {-# LANGUAGE StandaloneDeriving #-} | 8 | {-# LANGUAGE StandaloneDeriving #-} |
9 | {-# LANGUAGE UndecidableInstances #-} | 9 | {-# LANGUAGE UndecidableInstances #-} |
10 | module Data.Tox.Relay where | 10 | module Data.Tox.Relay |
11 | ( module Network.Tox.TCP.NodeId | ||
12 | , module Data.Tox.Relay | ||
13 | ) where | ||
11 | 14 | ||
12 | import Data.Aeson (ToJSON(..),FromJSON(..)) | 15 | import Data.Aeson (ToJSON(..),FromJSON(..)) |
13 | import qualified Data.Aeson as JSON | 16 | import qualified Data.Aeson as JSON |
@@ -27,8 +30,10 @@ import qualified Rank2 | |||
27 | import qualified Text.ParserCombinators.ReadP as RP | 30 | import qualified Text.ParserCombinators.ReadP as RP |
28 | 31 | ||
29 | import Crypto.Tox | 32 | import Crypto.Tox |
33 | import Network.Tox.TCP.NodeId | ||
30 | import Data.Tox.Onion | 34 | import Data.Tox.Onion |
31 | import qualified Network.Tox.NodeId as UDP | 35 | import qualified Network.Tox.NodeId as UDP |
36 | import Network.Tox.TCP.NodeId as TCP | ||
32 | 37 | ||
33 | newtype ConId = ConId Word8 | 38 | newtype ConId = ConId Word8 |
34 | deriving (Eq,Show,Ord,Data,Serialize) | 39 | deriving (Eq,Show,Ord,Data,Serialize) |
@@ -196,28 +201,6 @@ instance Serialize (Welcome Encrypted) where | |||
196 | get = Welcome <$> get <*> get | 201 | get = Welcome <$> get <*> get |
197 | put (Welcome n dta) = put n >> put dta | 202 | put (Welcome n dta) = put n >> put dta |
198 | 203 | ||
199 | data NodeInfo = NodeInfo | ||
200 | { udpNodeInfo :: UDP.NodeInfo | ||
201 | , tcpPort :: PortNumber | ||
202 | } | ||
203 | deriving (Eq,Ord) | ||
204 | |||
205 | instance Read NodeInfo where | ||
206 | readsPrec _ = RP.readP_to_S $ do | ||
207 | udp <- RP.readS_to_P reads | ||
208 | port <- RP.between (RP.char '{') (RP.char '}') $ do | ||
209 | mapM_ RP.char ("tcp:" :: String) | ||
210 | w16 <- RP.readS_to_P reads | ||
211 | return $ fromIntegral (w16 :: Word16) | ||
212 | return $ NodeInfo udp port | ||
213 | |||
214 | instance ToJSON NodeInfo where | ||
215 | toJSON (NodeInfo udp port) = case (toJSON udp) of | ||
216 | JSON.Object tbl -> JSON.Object $ HashMap.insert "tcp_ports" | ||
217 | (JSON.Array $ Vector.fromList | ||
218 | [JSON.Number (fromIntegral port)]) | ||
219 | tbl | ||
220 | x -> x -- Shouldn't happen. | ||
221 | 204 | ||
222 | tcpPortScore :: Word16 -> Word16 | 205 | tcpPortScore :: Word16 -> Word16 |
223 | tcpPortScore 443 = 0 | 206 | tcpPortScore 443 = 0 |
diff --git a/dht/src/Network/Tox.hs b/dht/src/Network/Tox.hs index c233492d..61a1d117 100644 --- a/dht/src/Network/Tox.hs +++ b/dht/src/Network/Tox.hs | |||
@@ -47,6 +47,7 @@ import System.IO.Error | |||
47 | 47 | ||
48 | import Data.TableMethods | 48 | import Data.TableMethods |
49 | import Data.Tox.Onion (substituteLoopback) | 49 | import Data.Tox.Onion (substituteLoopback) |
50 | import Network.Tox.RelayPinger | ||
50 | import qualified Data.Word64Map | 51 | import qualified Data.Word64Map |
51 | import Network.BitTorrent.DHT.Token as Token | 52 | import Network.BitTorrent.DHT.Token as Token |
52 | import qualified Data.Wrapper.PSQ as PSQ | 53 | import qualified Data.Wrapper.PSQ as PSQ |
@@ -194,7 +195,8 @@ data Tox extra = Tox | |||
194 | 195 | ||
195 | -- | Create a DHTPublicKey packet to send to a remote contact. | 196 | -- | Create a DHTPublicKey packet to send to a remote contact. |
196 | getContactInfo :: Tox extra -> IO DHT.DHTPublicKey | 197 | getContactInfo :: Tox extra -> IO DHT.DHTPublicKey |
197 | getContactInfo Tox{toxCryptoKeys,toxRouting} = join $ atomically $ do | 198 | getContactInfo Tox{toxCryptoKeys,toxRouting,toxOnionRoutes} = join $ atomically $ do |
199 | (rcnt,relays) <- currentRelays (tcpRelayPinger toxOnionRoutes) | ||
198 | r4 <- readTVar $ DHT.routing4 toxRouting | 200 | r4 <- readTVar $ DHT.routing4 toxRouting |
199 | r6 <- readTVar $ DHT.routing6 toxRouting | 201 | r6 <- readTVar $ DHT.routing6 toxRouting |
200 | nonce <- transportNewNonce toxCryptoKeys | 202 | nonce <- transportNewNonce toxCryptoKeys |
@@ -210,7 +212,7 @@ getContactInfo Tox{toxCryptoKeys,toxRouting} = join $ atomically $ do | |||
210 | return DHT.DHTPublicKey | 212 | return DHT.DHTPublicKey |
211 | { dhtpkNonce = timestamp | 213 | { dhtpkNonce = timestamp |
212 | , dhtpk = id2key self | 214 | , dhtpk = id2key self |
213 | , dhtpkNodes = DHT.SendNodes $ take 4 ns | 215 | , dhtpkNodes = DHT.SendNodes $ take 4 $ relays ++ map TCP.fromUDPNode ns |
214 | } | 216 | } |
215 | 217 | ||
216 | isLocalHost :: SockAddr -> Bool | 218 | isLocalHost :: SockAddr -> Bool |
diff --git a/dht/src/Network/Tox/DHT/Handlers.hs b/dht/src/Network/Tox/DHT/Handlers.hs index e93f565b..323d5f5e 100644 --- a/dht/src/Network/Tox/DHT/Handlers.hs +++ b/dht/src/Network/Tox/DHT/Handlers.hs | |||
@@ -7,6 +7,7 @@ module Network.Tox.DHT.Handlers where | |||
7 | 7 | ||
8 | import Debug.Trace | 8 | import Debug.Trace |
9 | import Network.Tox.DHT.Transport as DHTTransport | 9 | import Network.Tox.DHT.Transport as DHTTransport |
10 | import Network.Tox.TCP.NodeId as TCP (fromUDPNode, udpNodeInfo) | ||
10 | import Network.QueryResponse as QR hiding (Client) | 11 | import Network.QueryResponse as QR hiding (Client) |
11 | import qualified Network.QueryResponse as QR (Client) | 12 | import qualified Network.QueryResponse as QR (Client) |
12 | import Crypto.Tox | 13 | import Crypto.Tox |
@@ -257,6 +258,7 @@ getNodesH routing addr (GetNodes nid) = do | |||
257 | Want_IP4 -> (ks,ks6) | 258 | Want_IP4 -> (ks,ks6) |
258 | Want_Both -> error $ "BUG:unreachable at " ++ __FILE__ ++ ":" ++ show __LINE__ | 259 | Want_Both -> error $ "BUG:unreachable at " ++ __FILE__ ++ ":" ++ show __LINE__ |
259 | return $ SendNodes | 260 | return $ SendNodes |
261 | $ map fromUDPNode | ||
260 | $ if null ns2 then ns1 | 262 | $ if null ns2 then ns1 |
261 | else take 4 (take 3 ns1 ++ ns2) | 263 | else take 4 (take 3 ns1 ++ ns2) |
262 | where | 264 | where |
@@ -397,8 +399,9 @@ unsendNodes :: Message -> Maybe (Asymm (Nonce8,SendNodes)) | |||
397 | unsendNodes (DHTSendNodes asymm) = Just asymm | 399 | unsendNodes (DHTSendNodes asymm) = Just asymm |
398 | unsendNodes _ = Nothing | 400 | unsendNodes _ = Nothing |
399 | 401 | ||
402 | -- XXX: map udpNodeInfo is probably not right | ||
400 | unwrapNodes :: SendNodes -> ( [NodeInfo], [NodeInfo], Maybe () ) | 403 | unwrapNodes :: SendNodes -> ( [NodeInfo], [NodeInfo], Maybe () ) |
401 | unwrapNodes (SendNodes ns) = (ns,ns,Just ()) | 404 | unwrapNodes (SendNodes ns) = (map udpNodeInfo ns,map udpNodeInfo ns,Just ()) |
402 | 405 | ||
403 | getNodes :: Client -> TVar (HashMap NodeId [NodeInfoCallback]) -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo],[NodeInfo],Maybe ())) | 406 | getNodes :: Client -> TVar (HashMap NodeId [NodeInfoCallback]) -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo],[NodeInfo],Maybe ())) |
404 | getNodes client cbvar nid addr = do | 407 | getNodes client cbvar nid addr = do |
@@ -409,10 +412,10 @@ getNodes client cbvar nid addr = do | |||
409 | forM_ ns $ \n -> do | 412 | forM_ ns $ \n -> do |
410 | now <- getPOSIXTime | 413 | now <- getPOSIXTime |
411 | atomically $ do | 414 | atomically $ do |
412 | mcbs <- HashMap.lookup (nodeId n) <$> readTVar cbvar | 415 | mcbs <- HashMap.lookup (nodeId . udpNodeInfo $ n) <$> readTVar cbvar |
413 | forM_ mcbs $ \cbs -> do | 416 | forM_ mcbs $ \cbs -> do |
414 | forM_ cbs $ \cb -> do | 417 | forM_ cbs $ \cb -> do |
415 | rumoredAddress cb now (nodeAddr addr) n | 418 | rumoredAddress cb now (nodeAddr addr) (udpNodeInfo n) |
416 | return $ fmap unwrapNodes $ join reply | 419 | return $ fmap unwrapNodes $ join reply |
417 | 420 | ||
418 | updateRouting :: Client -> Routing | 421 | updateRouting :: Client -> Routing |
diff --git a/dht/src/Network/Tox/DHT/Transport.hs b/dht/src/Network/Tox/DHT/Transport.hs index b9b63165..7475b3b1 100644 --- a/dht/src/Network/Tox/DHT/Transport.hs +++ b/dht/src/Network/Tox/DHT/Transport.hs | |||
@@ -36,6 +36,7 @@ module Network.Tox.DHT.Transport | |||
36 | ) where | 36 | ) where |
37 | 37 | ||
38 | import Network.Tox.NodeId | 38 | import Network.Tox.NodeId |
39 | import qualified Network.Tox.TCP.NodeId as TCP | ||
39 | import Crypto.Tox hiding (encrypt,decrypt) | 40 | import Crypto.Tox hiding (encrypt,decrypt) |
40 | import qualified Crypto.Tox as ToxCrypto | 41 | import qualified Crypto.Tox as ToxCrypto |
41 | import Network.QueryResponse | 42 | import Network.QueryResponse |
@@ -315,7 +316,7 @@ newtype GetNodes = GetNodes NodeId | |||
315 | instance Sized GetNodes where | 316 | instance Sized GetNodes where |
316 | size = ConstSize 32 -- TODO This right? | 317 | size = ConstSize 32 -- TODO This right? |
317 | 318 | ||
318 | newtype SendNodes = SendNodes [NodeInfo] | 319 | newtype SendNodes = SendNodes [TCP.NodeInfo] |
319 | deriving (Eq,Ord,Show,Read) | 320 | deriving (Eq,Ord,Show,Read) |
320 | 321 | ||
321 | instance Sized SendNodes where | 322 | instance Sized SendNodes where |
diff --git a/dht/src/Network/Tox/NodeId.hs b/dht/src/Network/Tox/NodeId.hs index 6c82ce09..8567e77d 100644 --- a/dht/src/Network/Tox/NodeId.hs +++ b/dht/src/Network/Tox/NodeId.hs | |||
@@ -252,8 +252,8 @@ nodeInfoFromJSON prefer4 (JSON.Object v) = do | |||
252 | getIP :: Word8 -> S.Get IP | 252 | getIP :: Word8 -> S.Get IP |
253 | getIP 0x02 = IPv4 <$> S.get | 253 | getIP 0x02 = IPv4 <$> S.get |
254 | getIP 0x0a = IPv6 <$> S.get | 254 | getIP 0x0a = IPv6 <$> S.get |
255 | getIP 0x82 = IPv4 <$> S.get -- TODO: TCP | 255 | getIP 0x82 = IPv4 <$> S.get -- TODO: TCP TOX_TCP_INET |
256 | getIP 0x8a = IPv6 <$> S.get -- TODO: TCP | 256 | getIP 0x8a = IPv6 <$> S.get -- TODO: TCP TOX_TCP_INET6 |
257 | getIP x = fail ("unsupported address family ("++show x++")") | 257 | getIP x = fail ("unsupported address family ("++show x++")") |
258 | 258 | ||
259 | instance Sized NodeInfo where | 259 | instance Sized NodeInfo where |
diff --git a/dht/src/Network/Tox/Onion/Handlers.hs b/dht/src/Network/Tox/Onion/Handlers.hs index b35631a3..52dcf536 100644 --- a/dht/src/Network/Tox/Onion/Handlers.hs +++ b/dht/src/Network/Tox/Onion/Handlers.hs | |||
@@ -4,6 +4,7 @@ | |||
4 | module Network.Tox.Onion.Handlers where | 4 | module Network.Tox.Onion.Handlers where |
5 | 5 | ||
6 | import Network.Kademlia.Search | 6 | import Network.Kademlia.Search |
7 | import Network.Tox.TCP.NodeId (udpNodeInfo) | ||
7 | import Network.Tox.DHT.Transport | 8 | import Network.Tox.DHT.Transport |
8 | import Network.Tox.DHT.Handlers hiding (Message,Client) | 9 | import Network.Tox.DHT.Handlers hiding (Message,Client) |
9 | import Network.Tox.Onion.Transport | 10 | import Network.Tox.Onion.Transport |
@@ -251,7 +252,7 @@ announceSerializer getTimeout = MethodSerializer | |||
251 | } | 252 | } |
252 | 253 | ||
253 | unwrapAnnounceResponse :: Maybe NodeId -> NodeInfo -> AnnounceResponse -> ([NodeInfo], [Rendezvous], Maybe Nonce32) | 254 | unwrapAnnounceResponse :: Maybe NodeId -> NodeInfo -> AnnounceResponse -> ([NodeInfo], [Rendezvous], Maybe Nonce32) |
254 | unwrapAnnounceResponse alias ni (AnnounceResponse is_stored (SendNodes ns)) | 255 | unwrapAnnounceResponse alias ni (AnnounceResponse is_stored (SendNodes ns0)) | let ns = map udpNodeInfo ns0 |
255 | = case is_stored of | 256 | = case is_stored of |
256 | NotStored n32 -> ( ns , [] , Just n32) | 257 | NotStored n32 -> ( ns , [] , Just n32) |
257 | SendBackKey k -> ( ns , [Rendezvous k ni] , Nothing ) | 258 | SendBackKey k -> ( ns , [Rendezvous k ni] , Nothing ) |
diff --git a/dht/src/Network/Tox/TCP.hs b/dht/src/Network/Tox/TCP.hs index e80a22d1..1531dfb4 100644 --- a/dht/src/Network/Tox/TCP.hs +++ b/dht/src/Network/Tox/TCP.hs | |||
@@ -44,6 +44,7 @@ import Network.Kademlia.Routing | |||
44 | import Network.Kademlia.Search hiding (sendQuery) | 44 | import Network.Kademlia.Search hiding (sendQuery) |
45 | import Network.QueryResponse | 45 | import Network.QueryResponse |
46 | import Network.QueryResponse.TCP | 46 | import Network.QueryResponse.TCP |
47 | import Network.Tox.TCP.NodeId () | ||
47 | import Network.Tox.DHT.Handlers (toxSpace) | 48 | import Network.Tox.DHT.Handlers (toxSpace) |
48 | import Network.Tox.Onion.Transport hiding (encrypt,decrypt) | 49 | import Network.Tox.Onion.Transport hiding (encrypt,decrypt) |
49 | import Network.Tox.Onion.Handlers (unwrapAnnounceResponse) | 50 | import Network.Tox.Onion.Handlers (unwrapAnnounceResponse) |
@@ -57,10 +58,6 @@ withSize f = case size of len -> f len | |||
57 | 58 | ||
58 | type NodeId = UDP.NodeId | 59 | type NodeId = UDP.NodeId |
59 | 60 | ||
60 | -- example: | ||
61 | -- KEyW2Bm.S-DpIGp72380BAfgintUWX1KX.6ZU.4m5Ex@80.99.99.99:33400{tcp:443} | ||
62 | instance Show NodeInfo where | ||
63 | show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" | ||
64 | 61 | ||
65 | nodeId :: NodeInfo -> NodeId | 62 | nodeId :: NodeInfo -> NodeId |
66 | nodeId ni = UDP.nodeId $ udpNodeInfo ni | 63 | nodeId ni = UDP.nodeId $ udpNodeInfo ni |
diff --git a/dht/src/Network/Tox/TCP/NodeId.hs b/dht/src/Network/Tox/TCP/NodeId.hs new file mode 100644 index 00000000..c218c88f --- /dev/null +++ b/dht/src/Network/Tox/TCP/NodeId.hs | |||
@@ -0,0 +1,89 @@ | |||
1 | {-# LANGUAGE CPP #-} | ||
2 | module Network.Tox.TCP.NodeId where | ||
3 | |||
4 | import Crypto.Tox | ||
5 | import qualified Network.Tox.NodeId as UDP | ||
6 | |||
7 | import qualified Data.Aeson as JSON | ||
8 | ;import Data.Aeson (FromJSON (..), ToJSON (..)) | ||
9 | import Data.Functor.Contravariant | ||
10 | import Data.Hashable | ||
11 | import qualified Data.HashMap.Strict as HashMap | ||
12 | import qualified Data.Vector as Vector | ||
13 | import Data.Word | ||
14 | import Network.Socket | ||
15 | import qualified Text.ParserCombinators.ReadP as RP | ||
16 | import Data.Serialize as S | ||
17 | |||
18 | #if MIN_VERSION_iproute(1,7,4) | ||
19 | import Data.IP hiding (fromSockAddr) | ||
20 | #else | ||
21 | import Data.IP | ||
22 | #endif | ||
23 | |||
24 | data NodeInfo = NodeInfo | ||
25 | { udpNodeInfo :: UDP.NodeInfo | ||
26 | , tcpPort :: PortNumber | ||
27 | } | ||
28 | deriving (Eq,Ord) | ||
29 | |||
30 | instance Read NodeInfo where | ||
31 | readsPrec _ = RP.readP_to_S $ do | ||
32 | udp <- RP.readS_to_P reads | ||
33 | port <- RP.between (RP.char '{') (RP.char '}') $ do | ||
34 | mapM_ RP.char ("tcp:" :: String) | ||
35 | w16 <- RP.readS_to_P reads | ||
36 | return $ fromIntegral (w16 :: Word16) | ||
37 | return $ NodeInfo udp port | ||
38 | |||
39 | instance ToJSON NodeInfo where | ||
40 | toJSON (NodeInfo udp port) = case (toJSON udp) of | ||
41 | JSON.Object tbl -> JSON.Object $ HashMap.insert "tcp_ports" | ||
42 | (JSON.Array $ Vector.fromList | ||
43 | [JSON.Number (fromIntegral port)]) | ||
44 | tbl | ||
45 | x -> x -- Shouldn't happen. | ||
46 | |||
47 | -- example: | ||
48 | -- KEyW2Bm.S-DpIGp72380BAfgintUWX1KX.6ZU.4m5Ex@80.99.99.99:33400{tcp:443} | ||
49 | instance Show NodeInfo where | ||
50 | show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" | ||
51 | |||
52 | instance Sized NodeInfo where | ||
53 | size = contramap udpNodeInfo size | ||
54 | |||
55 | |||
56 | getIP :: Word8 -> S.Get (Bool, IP) | ||
57 | getIP 0x02 = (,) False . IPv4 <$> S.get -- UDP 4 | ||
58 | getIP 0x0a = (,) False . IPv6 <$> S.get -- UDP 6 | ||
59 | getIP 0x82 = (,) True . IPv4 <$> S.get -- TCP 4 | ||
60 | getIP 0x8a = (,) True . IPv6 <$> S.get -- TCP 6 | ||
61 | getIP x = fail ("unsupported address family ("++show x++")") | ||
62 | |||
63 | instance S.Serialize NodeInfo where | ||
64 | get = do | ||
65 | addrfam <- S.get :: S.Get Word8 | ||
66 | (istcp, ip) <- getIP addrfam | ||
67 | port <- S.get :: S.Get PortNumber | ||
68 | nid <- S.get | ||
69 | let (udpport, tcpport) = if istcp | ||
70 | then (0, port) | ||
71 | else (port, 0) | ||
72 | return $ NodeInfo (UDP.NodeInfo nid ip udpport) tcpport | ||
73 | |||
74 | put (NodeInfo (UDP.NodeInfo nid ip udpport) tcpport) = do | ||
75 | if tcpport==0 | ||
76 | then do | ||
77 | case ip of | ||
78 | IPv4 ip4 -> S.put (2 :: Word8) >> S.put ip4 | ||
79 | IPv6 ip6 -> S.put (10 :: Word8) >> S.put ip6 | ||
80 | S.put udpport | ||
81 | else do | ||
82 | case ip of | ||
83 | IPv4 ip4 -> S.put (0x82 :: Word8) >> S.put ip4 | ||
84 | IPv6 ip6 -> S.put (0x8a :: Word8) >> S.put ip6 | ||
85 | S.put tcpport | ||
86 | S.put nid | ||
87 | |||
88 | fromUDPNode :: UDP.NodeInfo -> NodeInfo | ||
89 | fromUDPNode ni = NodeInfo ni 0 | ||