summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Network/Tox/Crypto/Transport.hs121
1 files changed, 121 insertions, 0 deletions
diff --git a/src/Network/Tox/Crypto/Transport.hs b/src/Network/Tox/Crypto/Transport.hs
new file mode 100644
index 00000000..09f7fda8
--- /dev/null
+++ b/src/Network/Tox/Crypto/Transport.hs
@@ -0,0 +1,121 @@
1{-# LANGUAGE KindSignatures #-}
2module Network.Tox.Crypto.Transport
3 ( parseNetCrypto
4 , encodeNetCrypto
5 -- CryptoTransport
6 , NetCrypto(..)
7 , CryptoData(..)
8 , CryptoMessage(..)
9 , CryptoPacket(..)
10 , HandshakeData(..)
11 , Handshake(..)
12 ) where
13
14import Crypto.Tox
15import Network.Tox.DHT.Transport (Cookie)
16
17import Network.Socket
18import Data.ByteString
19import Data.Word
20import Crypto.Hash
21
22data NetCrypto
23 = NetHandshake (Handshake Encrypted)
24 | NetCrypto (CryptoPacket Encrypted)
25
26parseNetCrypto :: ByteString -> SockAddr -> Either String (NetCrypto, SockAddr)
27parseNetCrypto _ _ = Left "TODO: parseNetCrypto"
28
29encodeNetCrypto :: NetCrypto -> SockAddr -> (ByteString, SockAddr)
30encodeNetCrypto _ _ = _todo
31
32data Handshake (f :: * -> *) = Handshake
33 { handshakeCookie :: Cookie
34 , handshakeNonce :: Nonce24
35 , hadshakeData :: f HandshakeData
36 }
37
38data HandshakeData = HandshakeData
39 { baseNonce :: Nonce24
40 , sessionKey :: PublicKey
41 , cookieHash :: Digest SHA512
42 , otherCookie :: Cookie
43 }
44
45data CryptoPacket (f :: * -> *) = CryptoPacket
46 { pktNonce :: Word16
47 , pktData :: f CryptoData
48 }
49
50data CryptoData = CryptoData
51 { -- | [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)]
52 bufferStart :: Word32
53 -- | [ uint32_t packet number if lossless
54 -- , sendbuffer buffer_end if lossy , (big endian)]
55 , bufferEnd :: Word32
56 -- | [data]
57 , bufferData :: CryptoMessage
58 }
59
60-- TODO: Flesh this out.
61data CryptoMessage -- First byte indicates data
62 = Padding -- ^ 0 padding (skipped until we hit a non zero (data id) byte)
63 | PacketRequest -- ^ 1 packet request packet (lossy packet)
64 | KillPacket -- ^ 2 connection kill packet (lossy packet)
65 | UnspecifiedPacket -- ^ 3+ unspecified
66 | MessengerLossless -- ^ 16+ reserved for Messenger usage (lossless packets)
67 | MessengerLossy -- ^ 192+ reserved for Messenger usage (lossy packets)
68 | Messenger255 -- ^ 255 reserved for Messenger usage (lossless packet)
69
70
71
72-- --> CookieRequest WithoutCookie
73-- <-- CookieResponse CookieAddress
74-- --> Handshake CookieAddress
75-- <-- Handshake CookieAddress
76
77-- Handshake packet:
78-- [uint8_t 26] (0x1a)
79-- [Cookie]
80-- [nonce (24 bytes)]
81-- [Encrypted message containing:
82-- [24 bytes base nonce]
83-- [session public key of the peer (32 bytes)]
84-- [sha512 hash of the entire Cookie sitting outside the encrypted part]
85-- [Other Cookie (used by the other to respond to the handshake packet)]
86-- ]
87
88-- cookie response packet (161 bytes):
89--
90-- [uint8_t 25]
91-- [Random nonce (24 bytes)]
92-- [Encrypted message containing:
93-- [Cookie]
94-- [uint64_t echo id (that was sent in the request)]
95-- ]
96--
97-- Encrypted message is encrypted with the exact same symmetric key as the
98-- cookie request packet it responds to but with a different nonce.
99-- (Encrypted message is encrypted with reqesters's DHT private key,
100-- responders's DHT public key and the nonce.)
101--
102-- Since we don't receive the public key, we will need to lookup the key by
103-- the SockAddr... I don't understand why the CookieResponse message is
104-- special this way. TODO: implement a multimap (SockAddr -> SharedSecret)
105-- and wrap cookie queries with store/delete. TODO: Should the entire
106-- SharedScret cache be keyed on only SockAddr ? Perhaps the secret cache
107-- should be (NodeId -> Secret) and the cookie-request map should be
108-- (SockAddr -> NodeId)
109
110-- Encrypted packets:
111--
112-- Length Contents
113-- :---------:--------------------------------------------------------------
114-- `1` `uint8_t` (0x1b)
115-- `2` `uint16_t` The last 2 bytes of the nonce used to encrypt this
116-- variable  Payload
117--
118-- The payload is encrypted with the session key and 'base nonce' set by the
119-- receiver in their handshake + packet number (starting at 0, big endian math).
120
121