diff options
Diffstat (limited to 'ToxTransport.hs')
-rw-r--r-- | ToxTransport.hs | 116 |
1 files changed, 98 insertions, 18 deletions
diff --git a/ToxTransport.hs b/ToxTransport.hs index a927e55a..855b0c7e 100644 --- a/ToxTransport.hs +++ b/ToxTransport.hs | |||
@@ -1,27 +1,40 @@ | |||
1 | {-# LANGUAGE ScopedTypeVariables #-} | 1 | {-# LANGUAGE DataKinds #-} |
2 | {-# LANGUAGE DataKinds,KindSignatures #-} | 2 | {-# LANGUAGE GADTs #-} |
3 | {-# LANGUAGE GADTs #-} | ||
4 | {-# LANGUAGE TypeOperators #-} | ||
5 | {-# LANGUAGE LambdaCase #-} | ||
6 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 3 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
7 | {-# LANGUAGE TupleSections #-} | 4 | {-# LANGUAGE KindSignatures #-} |
8 | module ToxTransport where | 5 | {-# LANGUAGE LambdaCase #-} |
6 | {-# LANGUAGE ScopedTypeVariables #-} | ||
7 | {-# LANGUAGE TupleSections #-} | ||
8 | {-# LANGUAGE TypeOperators #-} | ||
9 | module ToxTransport | ||
10 | ( toxTransport | ||
11 | , TransportCrypto | ||
12 | , UDPTransport | ||
13 | , DirectMessage | ||
14 | , Encrypted8 | ||
15 | , OnionToOwner | ||
16 | , OnionMessage | ||
17 | , NetCrypto | ||
18 | ) where | ||
9 | 19 | ||
10 | import Network.QueryResponse | 20 | import Network.QueryResponse |
21 | import ToxAddress as Tox hiding (OnionToOwner, ReturnPath) | ||
11 | import ToxCrypto | 22 | import ToxCrypto |
12 | import ToxAddress as Tox hiding (ReturnPath,OnionToOwner) | ||
13 | import ToxPacket | 23 | import ToxPacket |
14 | 24 | ||
25 | import Control.Applicative | ||
26 | import Control.Arrow | ||
15 | import Control.Concurrent.STM | 27 | import Control.Concurrent.STM |
28 | import Crypto.Hash | ||
29 | import Crypto.Hash.Algorithms | ||
16 | import qualified Data.ByteString as B | 30 | import qualified Data.ByteString as B |
17 | ;import Data.ByteString (ByteString) | 31 | ;import Data.ByteString (ByteString) |
32 | import Data.Serialize as S (Get, Put, Serialize, decode, get, put, | ||
33 | runGet) | ||
34 | import Data.Typeable | ||
18 | import Data.Word | 35 | import Data.Word |
19 | import Network.Socket | ||
20 | import Data.Serialize as S (decode, Serialize, get, put, Get, Put, runGet) | ||
21 | import GHC.TypeLits | 36 | import GHC.TypeLits |
22 | import Data.Typeable | 37 | import Network.Socket |
23 | import Control.Applicative | ||
24 | import Control.Arrow | ||
25 | 38 | ||
26 | newtype SymmetricKey = SymmetricKey ByteString | 39 | newtype SymmetricKey = SymmetricKey ByteString |
27 | 40 | ||
@@ -65,11 +78,12 @@ toxTransport :: | |||
65 | -> UDPTransport | 78 | -> UDPTransport |
66 | -> IO ( Transport String NodeInfo (DirectMessage Encrypted8) | 79 | -> IO ( Transport String NodeInfo (DirectMessage Encrypted8) |
67 | , Transport String OnionToOwner (OnionMessage Encrypted) | 80 | , Transport String OnionToOwner (OnionMessage Encrypted) |
68 | , Transport String SockAddr ByteString ) | 81 | , Transport String SockAddr NetCrypto ) |
69 | toxTransport crypto udp = do | 82 | toxTransport crypto udp = do |
70 | (dht,udp1) <- partitionTransport parseDHTAddr encodeDHTAddr id $ handleOnion crypto udp | 83 | (dht,udp1) <- partitionTransport parseDHTAddr encodeDHTAddr id $ handleOnion crypto udp |
71 | (onion,udp2) <- partitionTransport parseOnionAddr encodeOnionAddr id udp1 | 84 | (onion,udp2) <- partitionTransport parseOnionAddr encodeOnionAddr id udp1 |
72 | return (dht,onion,udp2) | 85 | let netcrypto = layerTransport parseNetCrypto encodeNetCrypto udp2 |
86 | return (dht,onion,netcrypto) | ||
73 | 87 | ||
74 | 88 | ||
75 | type HandleHi a = Maybe (Either String (Message, Tox.Address)) -> IO a | 89 | type HandleHi a = Maybe (Either String (Message, Tox.Address)) -> IO a |
@@ -180,8 +194,62 @@ encodeOnionAddr :: (OnionMessage Encrypted,OnionToOwner) -> (ByteString, SockAdd | |||
180 | encodeOnionAddr = _todo | 194 | encodeOnionAddr = _todo |
181 | 195 | ||
182 | 196 | ||
183 | data CookieAddress = WithoutCookie NodeInfo | 197 | -- data CookieAddress = WithoutCookie NodeInfo | CookieAddress Cookie SockAddr |
184 | | CookieAddress Cookie SockAddr | 198 | |
199 | data NetCrypto | ||
200 | = NetHandshake (Handshake Encrypted) | ||
201 | | NetCrypto (CryptoPacket Encrypted) | ||
202 | |||
203 | parseNetCrypto :: ByteString -> SockAddr -> Either String (NetCrypto, SockAddr) | ||
204 | parseNetCrypto = _todo | ||
205 | |||
206 | encodeNetCrypto :: NetCrypto -> SockAddr -> (ByteString, SockAddr) | ||
207 | encodeNetCrypto = _todo | ||
208 | |||
209 | data Handshake (f :: * -> *) = Handshake | ||
210 | { handshakeCookie :: Cookie | ||
211 | , handshakeNonce :: Nonce24 | ||
212 | , hadshakeData :: f HandshakeData | ||
213 | } | ||
214 | |||
215 | data HandshakeData = HandshakeData | ||
216 | { baseNonce :: Nonce24 | ||
217 | , sessionKey :: PublicKey | ||
218 | , cookieHash :: Digest SHA512 | ||
219 | , otherCookie :: Cookie | ||
220 | } | ||
221 | |||
222 | data CryptoPacket (f :: * -> *) = CryptoPacket | ||
223 | { pktNonce :: Word16 | ||
224 | , pktData :: f CryptoData | ||
225 | } | ||
226 | |||
227 | data CryptoData = CryptoData | ||
228 | { -- | [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)] | ||
229 | bufferStart :: Word32 | ||
230 | -- | [ uint32_t packet number if lossless | ||
231 | -- , sendbuffer buffer_end if lossy , (big endian)] | ||
232 | , bufferEnd :: Word32 | ||
233 | -- | [data] | ||
234 | , bufferData :: CryptoMessage | ||
235 | } | ||
236 | |||
237 | -- TODO: Flesh this out. | ||
238 | data CryptoMessage -- First byte indicates data | ||
239 | = Padding -- ^ 0 padding (skipped until we hit a non zero (data id) byte) | ||
240 | | PacketRequest -- ^ 1 packet request packet (lossy packet) | ||
241 | | KillPacket -- ^ 2 connection kill packet (lossy packet) | ||
242 | | UnspecifiedPacket -- ^ 3+ unspecified | ||
243 | | MessengerLossless -- ^ 16+ reserved for Messenger usage (lossless packets) | ||
244 | | MessengerLossy -- ^ 192+ reserved for Messenger usage (lossy packets) | ||
245 | | Messenger255 -- ^ 255 reserved for Messenger usage (lossless packet) | ||
246 | |||
247 | |||
248 | |||
249 | -- --> CookieRequest WithoutCookie | ||
250 | -- <-- CookieResponse CookieAddress | ||
251 | -- --> Handshake CookieAddress | ||
252 | -- <-- Handshake CookieAddress | ||
185 | 253 | ||
186 | -- Handshake packet: | 254 | -- Handshake packet: |
187 | -- [uint8_t 26] (0x1a) | 255 | -- [uint8_t 26] (0x1a) |
@@ -216,8 +284,20 @@ data CookieAddress = WithoutCookie NodeInfo | |||
216 | -- should be (NodeId -> Secret) and the cookie-request map should be | 284 | -- should be (NodeId -> Secret) and the cookie-request map should be |
217 | -- (SockAddr -> NodeId) | 285 | -- (SockAddr -> NodeId) |
218 | 286 | ||
287 | -- Encrypted packets: | ||
288 | -- | ||
289 | -- Length Contents | ||
290 | -- :---------:-------------------------------------------------------------- | ||
291 | -- `1` `uint8_t` (0x1b) | ||
292 | -- `2` `uint16_t` The last 2 bytes of the nonce used to encrypt this | ||
293 | -- variable Payload | ||
294 | -- | ||
295 | -- The payload is encrypted with the session key and 'base nonce' set by the | ||
296 | -- receiver in their handshake + packet number (starting at 0, big endian math). | ||
297 | |||
298 | |||
219 | -- Byte value Packet Kind Return address | 299 | -- Byte value Packet Kind Return address |
220 | -- :----------- :-------------------- | 300 | -- :----------- :-------------------- |
221 | -- `0x00` Ping Request DHTNode | 301 | -- `0x00` Ping Request DHTNode |
222 | -- `0x01` Ping Response - | 302 | -- `0x01` Ping Response - |
223 | -- `0x02` Nodes Request DHTNode | 303 | -- `0x02` Nodes Request DHTNode |