summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/Tox/NodeId.hs2
-rw-r--r--src/Network/Tox/TCP.hs40
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?
338instance Hashable NodeInfo where 340instance 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
9import Control.Concurrent.STM 9import Control.Concurrent.STM
10import Control.Monad 10import Control.Monad
11import Crypto.Random 11import Crypto.Random
12import Data.Aeson (ToJSON(..),FromJSON(..))
13import qualified Data.Aeson as JSON
12import Data.Functor.Contravariant 14import Data.Functor.Contravariant
13import Data.Functor.Identity 15import Data.Functor.Identity
16import Data.Hashable
17import qualified Data.HashMap.Strict as HashMap
14import Data.IP 18import Data.IP
15import Data.Serialize 19import Data.Serialize
20import Data.Word
21import qualified Data.Vector as Vector
16import Network.Socket (SockAddr(..)) 22import Network.Socket (SockAddr(..))
23import qualified Text.ParserCombinators.ReadP as RP
17 24
18import Crypto.Tox 25import Crypto.Tox
19import Data.ByteString (hPut,hGet,ByteString) 26import 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
43type NodeId = UDP.NodeId 51type NodeId = UDP.NodeId
44 52
53-- example:
54-- KEyW2Bm.S-DpIGp72380BAfgintUWX1KX.6ZU.4m5Ex@80.99.99.99:33400{tcp:443}
45instance Show NodeInfo where 55instance 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
58instance 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
67instance 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
75instance 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
85instance Hashable NodeInfo where
86 hashWithSalt s n = hashWithSalt s (udpNodeInfo n)
87
48nodeId :: NodeInfo -> NodeId 88nodeId :: NodeInfo -> NodeId
49nodeId ni = UDP.nodeId $ udpNodeInfo ni 89nodeId ni = UDP.nodeId $ udpNodeInfo ni
50 90