diff options
author | Joe Crayne <joe@jerkface.net> | 2018-12-06 21:32:55 -0500 |
---|---|---|
committer | Joe Crayne <joe@jerkface.net> | 2018-12-16 14:08:26 -0500 |
commit | df6292eef942c11b9ac58b337f29641dae404116 (patch) | |
tree | 4e034469484f79f06bb95d72a666e2f3f326f2b2 /src | |
parent | 3bb64acc07833b81b6e6cdb8fff3768a142d5be6 (diff) |
Intances for TCP.NodeInfo.
Diffstat (limited to 'src')
-rw-r--r-- | src/Network/Tox/NodeId.hs | 2 | ||||
-rw-r--r-- | src/Network/Tox/TCP.hs | 40 |
2 files changed, 42 insertions, 0 deletions
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs index 56ddf03c..98be1e3a 100644 --- a/src/Network/Tox/NodeId.hs +++ b/src/Network/Tox/NodeId.hs | |||
@@ -335,6 +335,8 @@ instance Read NodeInfo where | |||
335 | return $ NodeInfo nid ip port | 335 | return $ NodeInfo nid ip port |
336 | 336 | ||
337 | -- The Hashable instance depends only on the IP address and port number. | 337 | -- The Hashable instance depends only on the IP address and port number. |
338 | -- | ||
339 | -- TODO: Why is the node id excluded? | ||
338 | instance Hashable NodeInfo where | 340 | instance Hashable NodeInfo where |
339 | hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni) | 341 | hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni) |
340 | {-# INLINE hashWithSalt #-} | 342 | {-# INLINE hashWithSalt #-} |
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs index 5b5b4f4e..eede869f 100644 --- a/src/Network/Tox/TCP.hs +++ b/src/Network/Tox/TCP.hs | |||
@@ -9,11 +9,18 @@ import Control.Concurrent | |||
9 | import Control.Concurrent.STM | 9 | import Control.Concurrent.STM |
10 | import Control.Monad | 10 | import Control.Monad |
11 | import Crypto.Random | 11 | import Crypto.Random |
12 | import Data.Aeson (ToJSON(..),FromJSON(..)) | ||
13 | import qualified Data.Aeson as JSON | ||
12 | import Data.Functor.Contravariant | 14 | import Data.Functor.Contravariant |
13 | import Data.Functor.Identity | 15 | import Data.Functor.Identity |
16 | import Data.Hashable | ||
17 | import qualified Data.HashMap.Strict as HashMap | ||
14 | import Data.IP | 18 | import Data.IP |
15 | import Data.Serialize | 19 | import Data.Serialize |
20 | import Data.Word | ||
21 | import qualified Data.Vector as Vector | ||
16 | import Network.Socket (SockAddr(..)) | 22 | import Network.Socket (SockAddr(..)) |
23 | import qualified Text.ParserCombinators.ReadP as RP | ||
17 | 24 | ||
18 | import Crypto.Tox | 25 | import Crypto.Tox |
19 | import Data.ByteString (hPut,hGet,ByteString) | 26 | import Data.ByteString (hPut,hGet,ByteString) |
@@ -39,12 +46,45 @@ data NodeInfo = NodeInfo | |||
39 | { udpNodeInfo :: UDP.NodeInfo | 46 | { udpNodeInfo :: UDP.NodeInfo |
40 | , tcpPort :: PortNumber | 47 | , tcpPort :: PortNumber |
41 | } | 48 | } |
49 | deriving (Eq,Ord) | ||
42 | 50 | ||
43 | type NodeId = UDP.NodeId | 51 | type NodeId = UDP.NodeId |
44 | 52 | ||
53 | -- example: | ||
54 | -- KEyW2Bm.S-DpIGp72380BAfgintUWX1KX.6ZU.4m5Ex@80.99.99.99:33400{tcp:443} | ||
45 | instance Show NodeInfo where | 55 | instance Show NodeInfo where |
46 | show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" | 56 | show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" |
47 | 57 | ||
58 | instance Read NodeInfo where | ||
59 | readsPrec _ = RP.readP_to_S $ do | ||
60 | udp <- RP.readS_to_P reads | ||
61 | port <- RP.between (RP.char '{') (RP.char '}') $ do | ||
62 | mapM_ RP.char ("tcp:" :: String) | ||
63 | w16 <- RP.readS_to_P reads | ||
64 | return $ fromIntegral (w16 :: Word16) | ||
65 | return $ NodeInfo udp port | ||
66 | |||
67 | instance ToJSON NodeInfo where | ||
68 | toJSON (NodeInfo udp port) = case (toJSON udp) of | ||
69 | JSON.Object tbl -> JSON.Object $ HashMap.insert "tcp_ports" | ||
70 | (JSON.Array $ Vector.fromList | ||
71 | [JSON.Number (fromIntegral port)]) | ||
72 | tbl | ||
73 | x -> x -- Shouldn't happen. | ||
74 | |||
75 | instance FromJSON NodeInfo where | ||
76 | parseJSON json = do | ||
77 | udp <- parseJSON json | ||
78 | port <- case json of | ||
79 | JSON.Object v -> do | ||
80 | portnum:_ <- v JSON..: "tcp_ports" | ||
81 | return (fromIntegral (portnum :: Word16)) | ||
82 | _ -> fail "TCP.NodeInfo: Expected JSON object." | ||
83 | return $ NodeInfo udp port | ||
84 | |||
85 | instance Hashable NodeInfo where | ||
86 | hashWithSalt s n = hashWithSalt s (udpNodeInfo n) | ||
87 | |||
48 | nodeId :: NodeInfo -> NodeId | 88 | nodeId :: NodeInfo -> NodeId |
49 | nodeId ni = UDP.nodeId $ udpNodeInfo ni | 89 | nodeId ni = UDP.nodeId $ udpNodeInfo ni |
50 | 90 | ||