summaryrefslogtreecommitdiff
path: root/ToxTransport.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-08-31 16:02:05 -0400
committerjoe <joe@jerkface.net>2017-08-31 16:02:05 -0400
commit1f8782c9efbe5ebe384cfe892b29d7822d704283 (patch)
tree3edcae8d18c5fd67290df736dab1740d59975e58 /ToxTransport.hs
parenteba3cdcc646211cc152c16d0813cc7e9b1c3111b (diff)
Separated module CryptoTransport from ToxTransport.
Diffstat (limited to 'ToxTransport.hs')
-rw-r--r--ToxTransport.hs129
1 files changed, 2 insertions, 127 deletions
diff --git a/ToxTransport.hs b/ToxTransport.hs
index 62081df5..f77f863e 100644
--- a/ToxTransport.hs
+++ b/ToxTransport.hs
@@ -6,39 +6,14 @@
6{-# LANGUAGE ScopedTypeVariables #-} 6{-# LANGUAGE ScopedTypeVariables #-}
7{-# LANGUAGE TupleSections #-} 7{-# LANGUAGE TupleSections #-}
8{-# LANGUAGE TypeOperators #-} 8{-# LANGUAGE TypeOperators #-}
9module ToxTransport 9module ToxTransport (toxTransport) where
10 ( toxTransport
11
12 , Encrypted8(..)
13
14 -- CryptoTransport
15 , NetCrypto(..)
16 , CryptoData(..)
17 , CryptoMessage(..)
18 , CryptoPacket(..)
19 , HandshakeData(..)
20 , Handshake(..)
21
22 ) where
23 10
24import Network.QueryResponse 11import Network.QueryResponse
25import ToxCrypto 12import ToxCrypto
26import DHTTransport 13import DHTTransport
27import OnionTransport 14import OnionTransport
15import CryptoTransport
28 16
29import Control.Applicative
30import Control.Arrow
31import Control.Concurrent.STM
32import Control.Monad
33import Crypto.Hash
34import Crypto.Hash.Algorithms
35import qualified Data.ByteString as B
36 ;import Data.ByteString (ByteString)
37import Data.Serialize as S (Get, Put, Serialize, decode, get, put,
38 runGet)
39import Data.Typeable
40import Data.Word
41import GHC.TypeLits
42import Network.Socket 17import Network.Socket
43 18
44toxTransport :: 19toxTransport ::
@@ -61,106 +36,6 @@ toxTransport crypto closeLookup udp = do
61-- instance (Sized a, Sized b) => Sized (a,b) where size = _todo 36-- instance (Sized a, Sized b) => Sized (a,b) where size = _todo
62 37
63 38
64data NetCrypto
65 = NetHandshake (Handshake Encrypted)
66 | NetCrypto (CryptoPacket Encrypted)
67
68parseNetCrypto :: ByteString -> SockAddr -> Either String (NetCrypto, SockAddr)
69parseNetCrypto = _todo
70
71encodeNetCrypto :: NetCrypto -> SockAddr -> (ByteString, SockAddr)
72encodeNetCrypto = _todo
73
74data Handshake (f :: * -> *) = Handshake
75 { handshakeCookie :: Cookie
76 , handshakeNonce :: Nonce24
77 , hadshakeData :: f HandshakeData
78 }
79
80data HandshakeData = HandshakeData
81 { baseNonce :: Nonce24
82 , sessionKey :: PublicKey
83 , cookieHash :: Digest SHA512
84 , otherCookie :: Cookie
85 }
86
87data CryptoPacket (f :: * -> *) = CryptoPacket
88 { pktNonce :: Word16
89 , pktData :: f CryptoData
90 }
91
92data CryptoData = CryptoData
93 { -- | [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)]
94 bufferStart :: Word32
95 -- | [ uint32_t packet number if lossless
96 -- , sendbuffer buffer_end if lossy , (big endian)]
97 , bufferEnd :: Word32
98 -- | [data]
99 , bufferData :: CryptoMessage
100 }
101
102-- TODO: Flesh this out.
103data CryptoMessage -- First byte indicates data
104 = Padding -- ^ 0 padding (skipped until we hit a non zero (data id) byte)
105 | PacketRequest -- ^ 1 packet request packet (lossy packet)
106 | KillPacket -- ^ 2 connection kill packet (lossy packet)
107 | UnspecifiedPacket -- ^ 3+ unspecified
108 | MessengerLossless -- ^ 16+ reserved for Messenger usage (lossless packets)
109 | MessengerLossy -- ^ 192+ reserved for Messenger usage (lossy packets)
110 | Messenger255 -- ^ 255 reserved for Messenger usage (lossless packet)
111
112
113
114-- --> CookieRequest WithoutCookie
115-- <-- CookieResponse CookieAddress
116-- --> Handshake CookieAddress
117-- <-- Handshake CookieAddress
118
119-- Handshake packet:
120-- [uint8_t 26] (0x1a)
121-- [Cookie]
122-- [nonce (24 bytes)]
123-- [Encrypted message containing:
124-- [24 bytes base nonce]
125-- [session public key of the peer (32 bytes)]
126-- [sha512 hash of the entire Cookie sitting outside the encrypted part]
127-- [Other Cookie (used by the other to respond to the handshake packet)]
128-- ]
129
130-- cookie response packet (161 bytes):
131--
132-- [uint8_t 25]
133-- [Random nonce (24 bytes)]
134-- [Encrypted message containing:
135-- [Cookie]
136-- [uint64_t echo id (that was sent in the request)]
137-- ]
138--
139-- Encrypted message is encrypted with the exact same symmetric key as the
140-- cookie request packet it responds to but with a different nonce.
141-- (Encrypted message is encrypted with reqesters's DHT private key,
142-- responders's DHT public key and the nonce.)
143--
144-- Since we don't receive the public key, we will need to lookup the key by
145-- the SockAddr... I don't understand why the CookieResponse message is
146-- special this way. TODO: implement a multimap (SockAddr -> SharedSecret)
147-- and wrap cookie queries with store/delete. TODO: Should the entire
148-- SharedScret cache be keyed on only SockAddr ? Perhaps the secret cache
149-- should be (NodeId -> Secret) and the cookie-request map should be
150-- (SockAddr -> NodeId)
151
152-- Encrypted packets:
153--
154-- Length Contents
155-- :---------:--------------------------------------------------------------
156-- `1` `uint8_t` (0x1b)
157-- `2` `uint16_t` The last 2 bytes of the nonce used to encrypt this
158-- variable  Payload
159--
160-- The payload is encrypted with the session key and 'base nonce' set by the
161-- receiver in their handshake + packet number (starting at 0, big endian math).
162
163
164-- Byte value Packet Kind Return address 39-- Byte value Packet Kind Return address
165-- :----------- :-------------------- 40-- :----------- :--------------------
166-- `0x00` Ping Request DHTNode 41-- `0x00` Ping Request DHTNode