diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Data/Tox/Relay.hs | 12 | ||||
-rw-r--r-- | src/Network/Tox.hs | 18 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 2 | ||||
-rw-r--r-- | src/Network/Tox/TCP.hs | 80 |
4 files changed, 97 insertions, 15 deletions
diff --git a/src/Data/Tox/Relay.hs b/src/Data/Tox/Relay.hs index 72a05660..1437c9cd 100644 --- a/src/Data/Tox/Relay.hs +++ b/src/Data/Tox/Relay.hs | |||
@@ -41,8 +41,8 @@ data RelayPacket | |||
41 | | RoutingResponse ConId PublicKey -- 0 for refusal, 16-255 for success. | 41 | | RoutingResponse ConId PublicKey -- 0 for refusal, 16-255 for success. |
42 | | ConnectNotification ConId | 42 | | ConnectNotification ConId |
43 | | DisconnectNotification ConId | 43 | | DisconnectNotification ConId |
44 | | RelayPing Word64 | 44 | | RelayPing Nonce8 |
45 | | RelayPong Word64 | 45 | | RelayPong Nonce8 |
46 | | OOBSend PublicKey ByteString | 46 | | OOBSend PublicKey ByteString |
47 | | OOBRecv PublicKey ByteString | 47 | | OOBRecv PublicKey ByteString |
48 | | OnionPacket (OnionRequest N0) | 48 | | OnionPacket (OnionRequest N0) |
@@ -82,8 +82,8 @@ instance Serialize RelayPacket where | |||
82 | 1 -> RoutingResponse <$> get <*> getPublicKey | 82 | 1 -> RoutingResponse <$> get <*> getPublicKey |
83 | 2 -> ConnectNotification <$> get | 83 | 2 -> ConnectNotification <$> get |
84 | 3 -> DisconnectNotification <$> get | 84 | 3 -> DisconnectNotification <$> get |
85 | 4 -> RelayPing <$> getWord64be | 85 | 4 -> RelayPing <$> get |
86 | 5 -> RelayPong <$> getWord64be | 86 | 5 -> RelayPong <$> get |
87 | 6 -> OOBSend <$> getPublicKey <*> (remaining >>= getBytes) | 87 | 6 -> OOBSend <$> getPublicKey <*> (remaining >>= getBytes) |
88 | 7 -> OOBRecv <$> getPublicKey <*> (remaining >>= getBytes) | 88 | 7 -> OOBRecv <$> getPublicKey <*> (remaining >>= getBytes) |
89 | 8 -> OnionPacket <$> get | 89 | 8 -> OnionPacket <$> get |
@@ -97,8 +97,8 @@ instance Serialize RelayPacket where | |||
97 | RoutingResponse rpid k -> put rpid >> putPublicKey k | 97 | RoutingResponse rpid k -> put rpid >> putPublicKey k |
98 | ConnectNotification conid -> put conid | 98 | ConnectNotification conid -> put conid |
99 | DisconnectNotification conid -> put conid | 99 | DisconnectNotification conid -> put conid |
100 | RelayPing pingid -> putWord64be pingid | 100 | RelayPing pingid -> put pingid |
101 | RelayPong pingid -> putWord64be pingid | 101 | RelayPong pingid -> put pingid |
102 | OOBSend k bs -> putPublicKey k >> putByteString bs | 102 | OOBSend k bs -> putPublicKey k >> putByteString bs |
103 | OOBRecv k bs -> putPublicKey k >> putByteString bs | 103 | OOBRecv k bs -> putPublicKey k >> putByteString bs |
104 | OnionPacket query -> put query | 104 | OnionPacket query -> put query |
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 37762eb8..83a17037 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -116,11 +116,17 @@ myAddr routing4 routing6 maddr = atomically $ do | |||
116 | 116 | ||
117 | newClient :: (DRG g, Show addr, Show meth) => | 117 | newClient :: (DRG g, Show addr, Show meth) => |
118 | g -> Transport String addr x | 118 | g -> Transport String addr x |
119 | -> (Client String meth DHT.TransactionId addr x -> x -> MessageClass String meth DHT.TransactionId addr x) | 119 | -> (Client String meth DHT.TransactionId addr x |
120 | -> x | ||
121 | -> MessageClass String meth DHT.TransactionId addr x) | ||
120 | -> (Maybe addr -> IO addr) | 122 | -> (Maybe addr -> IO addr) |
121 | -> (Client String meth DHT.TransactionId addr x -> meth -> Maybe (MethodHandler String DHT.TransactionId addr x)) | 123 | -> (Client String meth DHT.TransactionId addr x |
122 | -> (forall d. TransactionMethods d DHT.TransactionId addr x -> TransactionMethods d DHT.TransactionId addr x) | 124 | -> meth |
123 | -> (Client String meth DHT.TransactionId addr x -> Transport String addr x -> Transport String addr x) | 125 | -> Maybe (MethodHandler String DHT.TransactionId addr x)) |
126 | -> (forall d. TransactionMethods d DHT.TransactionId addr x | ||
127 | -> TransactionMethods d DHT.TransactionId addr x) | ||
128 | -> (Client String meth DHT.TransactionId addr x | ||
129 | -> Transport String addr x -> Transport String addr x) | ||
124 | -> IO (Client String meth DHT.TransactionId addr x) | 130 | -> IO (Client String meth DHT.TransactionId addr x) |
125 | newClient drg net classify selfAddr handlers modifytbl modifynet = do | 131 | newClient drg net classify selfAddr handlers modifytbl modifynet = do |
126 | -- If we have 8-byte keys for IntMap, then use it for transaction lookups. | 132 | -- If we have 8-byte keys for IntMap, then use it for transaction lookups. |
@@ -139,8 +145,8 @@ newClient drg net classify selfAddr handlers modifytbl modifynet = do | |||
139 | return $ Left (word64mapT,map_var) | 145 | return $ Left (word64mapT,map_var) |
140 | let dispatch tbl var handlers client = DispatchMethods | 146 | let dispatch tbl var handlers client = DispatchMethods |
141 | { classifyInbound = classify client | 147 | { classifyInbound = classify client |
142 | , lookupHandler = handlers -- var | 148 | , lookupHandler = handlers -- var |
143 | , tableMethods = modifytbl tbl | 149 | , tableMethods = modifytbl tbl |
144 | } | 150 | } |
145 | eprinter = logErrors -- printErrors stderr | 151 | eprinter = logErrors -- printErrors stderr |
146 | mkclient (tbl,var) handlers = | 152 | mkclient (tbl,var) handlers = |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 3d8a9e93..0cb03718 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -105,7 +105,7 @@ putOnionAsymm typ p a = put typ >> p >> putAliasedAsymm a | |||
105 | 105 | ||
106 | data OnionMessage (f :: * -> *) | 106 | data OnionMessage (f :: * -> *) |
107 | = OnionAnnounce (Asymm (f (AnnounceRequest,Nonce8))) | 107 | = OnionAnnounce (Asymm (f (AnnounceRequest,Nonce8))) |
108 | | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse) | 108 | | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse) -- XXX: Why is Nonce8 transmitted in the clear? |
109 | | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm | 109 | | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm |
110 | | OnionToRouteResponse (Asymm (Encrypted DataToRoute)) | 110 | | OnionToRouteResponse (Asymm (Encrypted DataToRoute)) |
111 | 111 | ||
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs index 28bcd244..608becc3 100644 --- a/src/Network/Tox/TCP.hs +++ b/src/Network/Tox/TCP.hs | |||
@@ -4,17 +4,29 @@ | |||
4 | {-# LANGUAGE FlexibleContexts #-} | 4 | {-# LANGUAGE FlexibleContexts #-} |
5 | module Network.Tox.TCP where | 5 | module Network.Tox.TCP where |
6 | 6 | ||
7 | import Control.Arrow | ||
7 | import Control.Concurrent | 8 | import Control.Concurrent |
8 | import Control.Concurrent.STM | 9 | import Control.Concurrent.STM |
10 | import Crypto.Random | ||
11 | import Data.Functor.Contravariant | ||
9 | import Data.Functor.Identity | 12 | import Data.Functor.Identity |
13 | import Data.IP | ||
10 | import Data.Serialize | 14 | import Data.Serialize |
15 | import Network.Socket (SockAddr(..)) | ||
11 | 16 | ||
12 | import Crypto.Tox | 17 | import Crypto.Tox |
13 | import Data.ByteString (hPut,hGet) | 18 | import Data.ByteString (hPut,hGet,ByteString) |
14 | import Data.Tox.Relay | 19 | import Data.Tox.Relay |
15 | import Network.Address (setPort,PortNumber,SockAddr) | 20 | import qualified Data.Word64Map |
21 | import DebugTag | ||
22 | import DPut | ||
23 | import Network.Address (setPort,PortNumber) | ||
24 | import Network.Kademlia.Routing | ||
25 | import Network.Kademlia.Search | ||
16 | import Network.QueryResponse | 26 | import Network.QueryResponse |
17 | import Network.QueryResponse.TCP | 27 | import Network.QueryResponse.TCP |
28 | import Network.Tox.DHT.Handlers (toxSpace) | ||
29 | import Network.Tox.Onion.Transport (OnionMessage(..),OnionResponse(..),N1) | ||
18 | import qualified Network.Tox.NodeId as UDP | 30 | import qualified Network.Tox.NodeId as UDP |
19 | 31 | ||
20 | 32 | ||
@@ -28,12 +40,18 @@ data NodeInfo = NodeInfo | |||
28 | 40 | ||
29 | type NodeId = UDP.NodeId | 41 | type NodeId = UDP.NodeId |
30 | 42 | ||
43 | instance Show NodeInfo where | ||
44 | show (NodeInfo udp port) = show udp ++ "{tcp:"++show port++"}" | ||
45 | |||
31 | nodeId :: NodeInfo -> NodeId | 46 | nodeId :: NodeInfo -> NodeId |
32 | nodeId ni = UDP.nodeId $ udpNodeInfo ni | 47 | nodeId ni = UDP.nodeId $ udpNodeInfo ni |
33 | 48 | ||
34 | nodeAddr :: NodeInfo -> SockAddr | 49 | nodeAddr :: NodeInfo -> SockAddr |
35 | nodeAddr ni = setPort (tcpPort ni) $ UDP.nodeAddr $ udpNodeInfo ni | 50 | nodeAddr ni = setPort (tcpPort ni) $ UDP.nodeAddr $ udpNodeInfo ni |
36 | 51 | ||
52 | nodeIP :: NodeInfo -> IP | ||
53 | nodeIP ni = UDP.nodeIP $ udpNodeInfo ni | ||
54 | |||
37 | tcpStream :: (Serialize y, Sized y, Serialize x, Sized x) => | 55 | tcpStream :: (Serialize y, Sized y, Serialize x, Sized x) => |
38 | TransportCrypto -> StreamHandshake NodeInfo x y | 56 | TransportCrypto -> StreamHandshake NodeInfo x y |
39 | tcpStream crypto = StreamHandshake | 57 | tcpStream crypto = StreamHandshake |
@@ -81,3 +99,61 @@ tcpStream crypto = StreamHandshake | |||
81 | 99 | ||
82 | toxTCP :: TransportCrypto -> IO (Transport err NodeInfo RelayPacket) | 100 | toxTCP :: TransportCrypto -> IO (Transport err NodeInfo RelayPacket) |
83 | toxTCP crypto = tcpTransport 30 (tcpStream crypto) | 101 | toxTCP crypto = tcpTransport 30 (tcpStream crypto) |
102 | |||
103 | tcpSpace :: KademliaSpace NodeId NodeInfo | ||
104 | tcpSpace = contramap udpNodeInfo toxSpace | ||
105 | |||
106 | nodeSearch :: Client err meth tid NodeInfo RelayPacket -> Search NodeId (IP, PortNumber) () NodeInfo NodeInfo | ||
107 | nodeSearch client = Search | ||
108 | { searchSpace = tcpSpace | ||
109 | , searchNodeAddress = nodeIP &&& tcpPort | ||
110 | , searchQuery = getNodes client | ||
111 | } | ||
112 | |||
113 | getNodes :: Client err meth tid NodeInfo RelayPacket -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo], [NodeInfo], Maybe ())) | ||
114 | getNodes client seeking dst = do | ||
115 | return Nothing -- TODO | ||
116 | |||
117 | handleOOB :: PublicKey -> ByteString -> NodeInfo -> NodeInfo -> IO (Maybe (RelayPacket -> RelayPacket)) | ||
118 | handleOOB k bs src dst = do | ||
119 | dput XMisc $ "TODO: handleOOB " ++ show src | ||
120 | return Nothing | ||
121 | |||
122 | handle2route :: OnionResponse N1 -> NodeInfo -> NodeInfo -> IO (Maybe (RelayPacket -> RelayPacket)) | ||
123 | handle2route o src dst = do | ||
124 | dput XMisc $ "TODO: handle2route " ++ show src | ||
125 | return Nothing | ||
126 | |||
127 | |||
128 | tcpClient :: TransportCrypto -> IO (Client String () Nonce8 NodeInfo RelayPacket) | ||
129 | tcpClient crypto = do | ||
130 | net <- toxTCP crypto | ||
131 | drg <- drgNew | ||
132 | map_var <- atomically $ newTVar (drg, Data.Word64Map.empty) | ||
133 | return Client | ||
134 | { clientNet = net | ||
135 | , clientDispatcher = DispatchMethods | ||
136 | { classifyInbound = \case | ||
137 | RelayPing n -> IsQuery () n | ||
138 | RelayPong n -> IsResponse n | ||
139 | OnionPacketResponse (OnionResponse _ (OnionAnnounceResponse n8 n24 ciphered)) -> IsResponse n8 | ||
140 | OnionPacketResponse o@(OnionResponse _ (OnionToRouteResponse _)) -> IsUnsolicited $ handle2route o | ||
141 | OOBRecv k bs -> IsUnsolicited $ handleOOB k bs | ||
142 | , lookupHandler = \() -> Just MethodHandler | ||
143 | { methodParse = \(RelayPing n8) -> Right () | ||
144 | , methodSerialize = \n8 src dst () -> RelayPong n8 | ||
145 | , methodAction = \src () -> return () | ||
146 | } | ||
147 | , tableMethods = transactionMethods (contramap (\(Nonce8 w64) -> w64) w64MapMethods) | ||
148 | $ first (either error Nonce8 . decode) . randomBytesGenerate 8 | ||
149 | } | ||
150 | , clientErrorReporter = logErrors | ||
151 | , clientPending = map_var | ||
152 | , clientAddress = \_ -> return $ NodeInfo | ||
153 | { udpNodeInfo = either error id $ UDP.nodeInfo (UDP.key2id $ transportPublic crypto) (SockAddrInet 0 0) | ||
154 | , tcpPort = 0 | ||
155 | } | ||
156 | , clientResponseId = return | ||
157 | , clientEnterQuery = \_ -> return () | ||
158 | , clientLeaveQuery = \_ _ -> return () | ||
159 | } | ||