summaryrefslogtreecommitdiff
path: root/src/Network/Tox/TCP.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/Tox/TCP.hs')
-rw-r--r--src/Network/Tox/TCP.hs57
1 files changed, 17 insertions, 40 deletions
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs
index e3f5012b..1111d3b8 100644
--- a/src/Network/Tox/TCP.hs
+++ b/src/Network/Tox/TCP.hs
@@ -2,7 +2,10 @@
2{-# LANGUAGE PartialTypeSignatures #-} 2{-# LANGUAGE PartialTypeSignatures #-}
3{-# LANGUAGE LambdaCase #-} 3{-# LANGUAGE LambdaCase #-}
4{-# LANGUAGE FlexibleContexts #-} 4{-# LANGUAGE FlexibleContexts #-}
5module Network.Tox.TCP where 5module Network.Tox.TCP
6 ( module Network.Tox.TCP
7 , NodeInfo(..)
8 ) where
6 9
7import Control.Arrow 10import Control.Arrow
8import Control.Concurrent 11import Control.Concurrent
@@ -46,11 +49,6 @@ import qualified Network.Tox.NodeId as UDP
46withSize :: Sized x => (Size x -> m (p x)) -> m (p x) 49withSize :: Sized x => (Size x -> m (p x)) -> m (p x)
47withSize f = case size of len -> f len 50withSize f = case size of len -> f len
48 51
49data NodeInfo = NodeInfo
50 { udpNodeInfo :: UDP.NodeInfo
51 , tcpPort :: PortNumber
52 }
53 deriving (Eq,Ord)
54 52
55type NodeId = UDP.NodeId 53type NodeId = UDP.NodeId
56 54
@@ -59,36 +57,6 @@ type NodeId = UDP.NodeId
59instance Show NodeInfo where 57instance Show NodeInfo where
60 show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" 58 show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}"
61 59
62instance Read NodeInfo where
63 readsPrec _ = RP.readP_to_S $ do
64 udp <- RP.readS_to_P reads
65 port <- RP.between (RP.char '{') (RP.char '}') $ do
66 mapM_ RP.char ("tcp:" :: String)
67 w16 <- RP.readS_to_P reads
68 return $ fromIntegral (w16 :: Word16)
69 return $ NodeInfo udp port
70
71instance ToJSON NodeInfo where
72 toJSON (NodeInfo udp port) = case (toJSON udp) of
73 JSON.Object tbl -> JSON.Object $ HashMap.insert "tcp_ports"
74 (JSON.Array $ Vector.fromList
75 [JSON.Number (fromIntegral port)])
76 tbl
77 x -> x -- Shouldn't happen.
78
79instance FromJSON NodeInfo where
80 parseJSON json = do
81 udp <- parseJSON json
82 port <- case json of
83 JSON.Object v -> do
84 portnum:_ <- v JSON..: "tcp_ports"
85 return (fromIntegral (portnum :: Word16))
86 _ -> fail "TCP.NodeInfo: Expected JSON object."
87 return $ NodeInfo udp port
88
89instance Hashable NodeInfo where
90 hashWithSalt s n = hashWithSalt s (udpNodeInfo n)
91
92nodeId :: NodeInfo -> NodeId 60nodeId :: NodeInfo -> NodeId
93nodeId ni = UDP.nodeId $ udpNodeInfo ni 61nodeId ni = UDP.nodeId $ udpNodeInfo ni
94 62
@@ -275,12 +243,21 @@ tcpPing client dst = sendQuery client meth () dst
275 243
276type RelayClient = Client String () Nonce8 NodeInfo RelayPacket 244type RelayClient = Client String () Nonce8 NodeInfo RelayPacket
277 245
278newClient :: TransportCrypto -> IO RelayClient 246-- | Create a new TCP relay client. Because polymorphic existential record
279newClient crypto = do 247-- updates are currently hard with GHC, this function accepts parameters for
248-- generalizing the table-entry type for pending transactions. Safe trivial
249-- defaults are 'id' and 'tryPutMVar'. The resulting customized table state
250-- will be returned to the caller along with the new client.
251newClient :: TransportCrypto
252 -> (MVar RelayPacket -> a) -- ^ store mvar for query
253 -> (a -> RelayPacket -> IO void) -- ^ load mvar for query
254 -> IO ( TVar (ChaChaDRG, Data.Word64Map.Word64Map a)
255 , Client String () Nonce8 NodeInfo RelayPacket)
256newClient crypto store load = do
280 net <- toxTCP crypto 257 net <- toxTCP crypto
281 drg <- drgNew 258 drg <- drgNew
282 map_var <- atomically $ newTVar (drg, Data.Word64Map.empty) 259 map_var <- atomically $ newTVar (drg, Data.Word64Map.empty)
283 return Client 260 return $ (,) map_var Client
284 { clientNet = net 261 { clientNet = net
285 , clientDispatcher = DispatchMethods 262 , clientDispatcher = DispatchMethods
286 { classifyInbound = \case 263 { classifyInbound = \case
@@ -294,7 +271,7 @@ newClient crypto = do
294 , methodSerialize = \n8 src dst () -> RelayPong n8 271 , methodSerialize = \n8 src dst () -> RelayPong n8
295 , methodAction = \src () -> return () 272 , methodAction = \src () -> return ()
296 } 273 }
297 , tableMethods = transactionMethods (contramap (\(Nonce8 w64) -> w64) w64MapMethods) 274 , tableMethods = transactionMethods' store load (contramap (\(Nonce8 w64) -> w64) w64MapMethods)
298 $ first (either error Nonce8 . decode) . randomBytesGenerate 8 275 $ first (either error Nonce8 . decode) . randomBytesGenerate 8
299 } 276 }
300 , clientErrorReporter = logErrors 277 , clientErrorReporter = logErrors