summaryrefslogtreecommitdiff
path: root/ToxTransport.hs
blob: 62081df52200e5eb0481bdd683b55d908d965645 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE LambdaCase                 #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TupleSections              #-}
{-# LANGUAGE TypeOperators              #-}
module ToxTransport
    ( toxTransport

    , Encrypted8(..)

    -- CryptoTransport
    , NetCrypto(..)
    , CryptoData(..)
    , CryptoMessage(..)
    , CryptoPacket(..)
    , HandshakeData(..)
    , Handshake(..)

    ) where

import Network.QueryResponse
import ToxCrypto
import DHTTransport
import OnionTransport

import Control.Applicative
import Control.Arrow
import Control.Concurrent.STM
import Control.Monad
import Crypto.Hash
import Crypto.Hash.Algorithms
import qualified Data.ByteString as B
         ;import Data.ByteString (ByteString)
import Data.Serialize            as S (Get, Put, Serialize, decode, get, put,
                                       runGet)
import Data.Typeable
import Data.Word
import GHC.TypeLits
import Network.Socket

toxTransport ::
      TransportCrypto
          -> (PublicKey -> IO (Maybe NodeInfo))
          -> UDPTransport
          -> IO ( Transport String NodeInfo (DHTMessage Encrypted8)
                , Transport String OnionToOwner (OnionMessage Encrypted)
                , Transport String SockAddr NetCrypto )
toxTransport crypto closeLookup udp = do
    (dht,udp1) <- partitionTransport parseDHTAddr encodeDHTAddr id $ forwardOnions crypto udp
    (onion,udp2) <- partitionTransport parseOnionAddr encodeOnionAddr id udp1
    let netcrypto = layerTransport parseNetCrypto encodeNetCrypto udp2
    return ( forwardDHTRequests crypto closeLookup dht
           , onion
           , netcrypto
           )


-- instance (Sized a, Sized b) => Sized (a,b) where size = _todo


data NetCrypto
    = NetHandshake (Handshake Encrypted)
    | NetCrypto (CryptoPacket Encrypted)

parseNetCrypto :: ByteString -> SockAddr -> Either String (NetCrypto, SockAddr)
parseNetCrypto = _todo

encodeNetCrypto :: NetCrypto -> SockAddr -> (ByteString, SockAddr)
encodeNetCrypto = _todo

data Handshake (f :: * -> *) = Handshake
    { handshakeCookie :: Cookie
    , handshakeNonce :: Nonce24
    , hadshakeData :: f HandshakeData
    }

data HandshakeData = HandshakeData
    { baseNonce :: Nonce24
    , sessionKey :: PublicKey
    , cookieHash :: Digest SHA512
    , otherCookie :: Cookie
    }

data CryptoPacket (f :: * -> *) = CryptoPacket
    { pktNonce :: Word16
    , pktData :: f CryptoData
    }

data CryptoData = CryptoData
    { -- | [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)]
      bufferStart :: Word32
      -- | [  uint32_t packet number if lossless
      --   , sendbuffer buffer_end  if lossy   , (big endian)]
    , bufferEnd :: Word32
      -- | [data]
    , bufferData :: CryptoMessage
    }

-- TODO: Flesh this out.
data CryptoMessage      -- First byte indicates data
    = Padding           -- ^ 0 padding (skipped until we hit a non zero (data id) byte)
    | PacketRequest     -- ^ 1 packet request packet (lossy packet)
    | KillPacket        -- ^ 2 connection kill packet (lossy packet)
    | UnspecifiedPacket -- ^ 3+ unspecified
    | MessengerLossless -- ^ 16+  reserved for Messenger usage (lossless packets)
    | MessengerLossy    -- ^ 192+ reserved for Messenger usage (lossy packets)
    | Messenger255      -- ^ 255 reserved for Messenger usage (lossless packet)



-- --> CookieRequest WithoutCookie
-- <-- CookieResponse CookieAddress
-- --> Handshake CookieAddress
-- <-- Handshake CookieAddress

-- Handshake packet:
--    [uint8_t 26] (0x1a)
--    [Cookie]
--    [nonce (24 bytes)]
--    [Encrypted message containing:
--        [24 bytes base nonce]
--        [session public key of the peer (32 bytes)]
--        [sha512 hash of the entire Cookie sitting outside the encrypted part]
--        [Other Cookie (used by the other to respond to the handshake packet)]
--    ]

-- cookie response packet (161 bytes):
--
--     [uint8_t 25]
--     [Random nonce (24 bytes)]
--     [Encrypted message containing:
--         [Cookie]
--         [uint64_t echo id (that was sent in the request)]
--     ]
--
--     Encrypted message is encrypted with the exact same symmetric key as the
--     cookie request packet it responds to but with a different nonce.
--     (Encrypted message is encrypted with reqesters's DHT private key,
--     responders's DHT public key and the nonce.)
--
--     Since we don't receive the public key, we will need to lookup the key by
--     the SockAddr... I don't understand why the CookieResponse message is
--     special this way.  TODO: implement a multimap (SockAddr -> SharedSecret)
--     and wrap cookie queries with store/delete.  TODO: Should the entire
--     SharedScret cache be keyed on only SockAddr ?  Perhaps the secret cache
--     should be (NodeId -> Secret) and the cookie-request map should be
--     (SockAddr -> NodeId)

-- Encrypted packets:
--
--  Length    Contents
-- :---------:--------------------------------------------------------------
--  `1`       `uint8_t` (0x1b)
--  `2`       `uint16_t` The last 2 bytes of the nonce used to encrypt this
--  variable   Payload
--
-- The payload is encrypted with the session key and 'base nonce' set by the
-- receiver in their handshake + packet number (starting at 0, big endian math).


--   Byte value   Packet Kind           Return address
-- :----------- :--------------------
--   `0x00`       Ping Request          DHTNode
--   `0x01`       Ping Response         -
--   `0x02`       Nodes Request         DHTNode
--   `0x04`       Nodes Response        -
--   `0x18`       Cookie Request        DHTNode, but without sending pubkey in response
--   `0x19`       Cookie Response       - (no pubkey)
--
--   `0x21`       LAN Discovery         DHTNode (No reply, port 33445, trigger Nodes Request/Response)
--
--   `0x20`       DHT Request           DHTNode/-forward
--
--   `0x1a`       Crypto Handshake      CookieAddress
--
--   `0x1b`       Crypto Data           SessionAddress
--
--   `0x83`       Announce Request      OnionToOwner
--   `0x84`       Announce Response     -
--   `0x85`       Onion Data Request    OnionToOwner
--   `0x86`       Onion Data Response   -
--
--   `0xf0`       Bootstrap Info        SockAddr?
--
--   `0x80`       Onion Request 0       -forward
--   `0x81`       Onion Request 1       -forward
--   `0x82`       Onion Request 2       -forward
--   `0x8c`       Onion Response 3      -return
--   `0x8d`       Onion Response 2      -return
--   `0x8e`       Onion Response 1      -return