summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--DHTTransport.hs64
-rw-r--r--OnionTransport.hs59
-rw-r--r--ToxAddress.hs5
-rw-r--r--ToxCrypto.hs13
4 files changed, 137 insertions, 4 deletions
diff --git a/DHTTransport.hs b/DHTTransport.hs
index 97a8113c..690ee346 100644
--- a/DHTTransport.hs
+++ b/DHTTransport.hs
@@ -2,6 +2,8 @@
2{-# LANGUAGE KindSignatures #-} 2{-# LANGUAGE KindSignatures #-}
3{-# LANGUAGE LambdaCase #-} 3{-# LANGUAGE LambdaCase #-}
4{-# LANGUAGE RankNTypes #-} 4{-# LANGUAGE RankNTypes #-}
5{-# LANGUAGE TupleSections #-}
6{-# LANGUAGE TypeOperators #-}
5module DHTTransport 7module DHTTransport
6 ( parseDHTAddr 8 ( parseDHTAddr
7 , encodeDHTAddr 9 , encodeDHTAddr
@@ -16,15 +18,20 @@ module DHTTransport
16 , Cookie 18 , Cookie
17 , DHTRequest 19 , DHTRequest
18 , mapMessage 20 , mapMessage
21 , encrypt
22 , decrypt
19 ) where 23 ) where
20 24
21import ToxAddress 25import ToxAddress
22import ToxCrypto 26import ToxCrypto hiding (encrypt,decrypt)
27import qualified ToxCrypto
23import Network.QueryResponse 28import Network.QueryResponse
24 29
25import Control.Arrow 30import Control.Arrow
31import Control.Monad
26import qualified Data.ByteString as B 32import qualified Data.ByteString as B
27 ;import Data.ByteString (ByteString) 33 ;import Data.ByteString (ByteString)
34import Data.Tuple
28import Data.Serialize as S (Get, Serialize, get, put, runGet) 35import Data.Serialize as S (Get, Serialize, get, put, runGet)
29import Data.Word 36import Data.Word
30import Network.Socket 37import Network.Socket
@@ -124,6 +131,10 @@ data DHTRequest
124 | NATPong Nonce8 131 | NATPong Nonce8
125 | DHTPK DHTPublicKey 132 | DHTPK DHTPublicKey
126 133
134instance Serialize DHTRequest where
135 get = return _todo
136 put _ = return () -- todo
137
127-- | Length | Contents | 138-- | Length | Contents |
128-- |:------------|:------------------------------------| 139-- |:------------|:------------------------------------|
129-- | `1` | `uint8_t` (0x9c) | 140-- | `1` | `uint8_t` (0x9c) |
@@ -177,6 +188,10 @@ data Cookie = Cookie Nonce24 (Encrypted CookieData)
177 188
178instance Sized Cookie where size = ConstSize 112 -- 24 byte nonce + 88 byte cookie data 189instance Sized Cookie where size = ConstSize 112 -- 24 byte nonce + 88 byte cookie data
179 190
191instance Serialize Cookie where
192 get = return $ Cookie _todo _todo
193 put _ = return () -- todo
194
180data CookieData = CookieData -- 16 (mac) 195data CookieData = CookieData -- 16 (mac)
181 { cookieTime :: Word64 -- 8 196 { cookieTime :: Word64 -- 8
182 , longTermKey :: PublicKey -- 32 197 , longTermKey :: PublicKey -- 32
@@ -186,6 +201,10 @@ data CookieData = CookieData -- 16 (mac)
186instance Sized CookieRequest where 201instance Sized CookieRequest where
187 size = ConstSize 64 -- 32 byte key + 32 byte padding 202 size = ConstSize 64 -- 32 byte key + 32 byte padding
188 203
204instance Serialize CookieRequest where
205 get = CookieRequest <$> return _todo
206 put (CookieRequest _) = return () -- todo
207
189forwardDHTRequests :: TransportCrypto -> (PublicKey -> IO (Maybe NodeInfo)) -> DHTTransport -> DHTTransport 208forwardDHTRequests :: TransportCrypto -> (PublicKey -> IO (Maybe NodeInfo)) -> DHTTransport -> DHTTransport
190forwardDHTRequests crypto closeLookup dht = dht { awaitMessage = await' } 209forwardDHTRequests crypto closeLookup dht = dht { awaitMessage = await' }
191 where 210 where
@@ -198,3 +217,46 @@ forwardDHTRequests crypto closeLookup dht = dht { awaitMessage = await' }
198 await' pass 217 await' pass
199 m -> pass m 218 m -> pass m
200 219
220encrypt :: TransportCrypto -> DHTMessage ((,) Nonce8) -> NodeInfo -> (DHTMessage Encrypted8, NodeInfo)
221encrypt crypto msg ni = (transcode (encryptMessage crypto) msg, ni)
222
223encryptMessage :: Serialize a =>
224 TransportCrypto -> Nonce24 -> Either (Nonce8,a) (Assym (Nonce8,a)) -> Encrypted8 a
225encryptMessage crypto n (Right assym) = E8 $ ToxCrypto.encrypt secret plain
226 where
227 secret = computeSharedSecret (transportSecret crypto) (senderKey assym) n
228 plain = encodePlain $ swap $ assymData assym
229encryptMessage crypto n (Left plain) = _todo
230
231decrypt :: TransportCrypto -> DHTMessage Encrypted8 -> NodeInfo -> Either String (DHTMessage ((,) Nonce8), NodeInfo)
232decrypt crypto msg ni = (, ni) <$> (sequenceMessage $ transcode (decryptMessage crypto) msg)
233
234decryptMessage :: Serialize x =>
235 TransportCrypto
236 -> Nonce24
237 -> Either (Encrypted8 x) (Assym (Encrypted8 x))
238 -> (Either String ∘ ((,) Nonce8)) x
239decryptMessage crypto n (Right assymE) = plain8 $ ToxCrypto.decrypt secret e
240 where
241 secret = computeSharedSecret (transportSecret crypto) (senderKey assymE) n
242 E8 e = assymData assymE
243 plain8 = Composed . fmap swap . (>>= decodePlain)
244decryptMessage crypto n (Left (E8 e)) = _todo
245
246sequenceMessage :: Applicative m => DHTMessage (m ∘ f) -> m (DHTMessage f)
247sequenceMessage (DHTPing asym) = fmap DHTPing $ sequenceA $ fmap uncomposed asym
248sequenceMessage (DHTPong asym) = fmap DHTPong $ sequenceA $ fmap uncomposed asym
249sequenceMessage (DHTGetNodes asym) = fmap DHTGetNodes $ sequenceA $ fmap uncomposed asym
250sequenceMessage (DHTSendNodes asym) = fmap DHTSendNodes $ sequenceA $ fmap uncomposed asym
251sequenceMessage (DHTCookieRequest asym) = fmap DHTCookieRequest $ sequenceA $ fmap uncomposed asym
252sequenceMessage (DHTCookie n dta) = fmap (DHTCookie n) $ uncomposed dta
253sequenceMessage (DHTDHTRequest pubkey asym) = fmap (DHTDHTRequest pubkey) $ sequenceA $ fmap uncomposed asym
254
255transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> DHTMessage f -> DHTMessage g
256transcode f (DHTPing asym) = DHTPing $ asym { assymData = f (assymNonce asym) (Right asym) }
257transcode f (DHTPong asym) = DHTPong $ asym { assymData = f (assymNonce asym) (Right asym) }
258transcode f (DHTGetNodes asym) = DHTGetNodes $ asym { assymData = f (assymNonce asym) (Right asym) }
259transcode f (DHTSendNodes asym) = DHTSendNodes $ asym { assymData = f (assymNonce asym) (Right asym) }
260transcode f (DHTCookieRequest asym) = DHTCookieRequest $ asym { assymData = f (assymNonce asym) (Right asym) }
261transcode f (DHTCookie n dta) = DHTCookie n $ f n $ Left dta
262transcode f (DHTDHTRequest pubkey asym) = DHTDHTRequest pubkey $ asym { assymData = f (assymNonce asym) (Right asym) }
diff --git a/OnionTransport.hs b/OnionTransport.hs
index 804c444e..aa4bae1e 100644
--- a/OnionTransport.hs
+++ b/OnionTransport.hs
@@ -3,6 +3,7 @@
3{-# LANGUAGE GeneralizedNewtypeDeriving #-} 3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE KindSignatures #-} 4{-# LANGUAGE KindSignatures #-}
5{-# LANGUAGE LambdaCase #-} 5{-# LANGUAGE LambdaCase #-}
6{-# LANGUAGE RankNTypes #-}
6{-# LANGUAGE ScopedTypeVariables #-} 7{-# LANGUAGE ScopedTypeVariables #-}
7{-# LANGUAGE TupleSections #-} 8{-# LANGUAGE TupleSections #-}
8{-# LANGUAGE TypeOperators #-} 9{-# LANGUAGE TypeOperators #-}
@@ -21,15 +22,20 @@ module OnionTransport
21 , OnionResponse(..) 22 , OnionResponse(..)
22 , Addressed(..) 23 , Addressed(..)
23 , UDPTransport 24 , UDPTransport
25 , KeyRecord(..)
26 , encrypt
27 , decrypt
24 ) where 28 ) where
25 29
26import Network.QueryResponse 30import Network.QueryResponse
27import ToxCrypto 31import ToxCrypto hiding (encrypt,decrypt)
32import qualified ToxCrypto
28import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo) 33import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo)
29 34
30import Control.Arrow 35import Control.Arrow
31import qualified Data.ByteString as B 36import qualified Data.ByteString as B
32 ;import Data.ByteString (ByteString) 37 ;import Data.ByteString (ByteString)
38import Data.Functor.Identity
33import Data.Serialize as S (Get, Put, Serialize, get, put, runGet) 39import Data.Serialize as S (Get, Put, Serialize, get, put, runGet)
34import Data.Typeable 40import Data.Typeable
35import Data.Word 41import Data.Word
@@ -52,6 +58,7 @@ data OnionMessage (f :: * -> *)
52 58
53data OnionToOwner = OnionToOwner NodeInfo (ReturnPath 3) 59data OnionToOwner = OnionToOwner NodeInfo (ReturnPath 3)
54 | OnionToMe SockAddr -- SockAddr is immediate peer in route 60 | OnionToMe SockAddr -- SockAddr is immediate peer in route
61 deriving Show
55 62
56 63
57onionToOwner assym ret3 saddr = do 64onionToOwner assym ret3 saddr = do
@@ -127,6 +134,10 @@ data ReturnPath (n :: Nat) where
127 NoReturnPath :: ReturnPath 0 134 NoReturnPath :: ReturnPath 0
128 ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath n)) -> ReturnPath (n + 1) 135 ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath n)) -> ReturnPath (n + 1)
129 136
137instance KnownNat n => Show (ReturnPath n) where
138 show rpath = "ReturnPath" ++ show (natVal rpath)
139
140
130-- instance KnownNat n => Serialize (ReturnPath n) where 141-- instance KnownNat n => Serialize (ReturnPath n) where
131-- -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce) 142-- -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce)
132-- get = ReturnPath <$> getBytes ( 59 * (fromIntegral $ natVal $ Proxy @n) ) 143-- get = ReturnPath <$> getBytes ( 59 * (fromIntegral $ natVal $ Proxy @n) )
@@ -194,3 +205,49 @@ data DataToRoute = DataToRoute
194 , dataToRoute :: Encrypted (Word8,ByteString) 205 , dataToRoute :: Encrypted (Word8,ByteString)
195 } 206 }
196 207
208instance Serialize DataToRoute where
209 get = return $ DataToRoute _todo _todo
210 put _ = return () -- todo
211
212encrypt :: TransportCrypto -> OnionMessage Identity -> OnionToOwner -> (OnionMessage Encrypted, OnionToOwner)
213encrypt crypto msg rpath = (transcode (encryptMessage crypto) msg, rpath)
214
215encryptMessage :: Serialize a =>
216 TransportCrypto -> Nonce24 -> Either (Identity a) (Assym (Identity a)) -> Encrypted a
217encryptMessage crypto n (Right a) = ToxCrypto.encrypt secret plain
218 where
219 secret = computeSharedSecret (transportSecret crypto) (senderKey a) n
220 plain = encodePlain $ runIdentity $ assymData a
221encryptMessage crypto n (Left x) = ToxCrypto.encrypt secret plain
222 where
223 secret = computeSharedSecret (transportSecret crypto) _todo n
224 plain = encodePlain $ runIdentity $ x
225
226decrypt :: TransportCrypto -> OnionMessage Encrypted -> OnionToOwner -> Either String (OnionMessage Identity, OnionToOwner)
227decrypt crypto msg addr = (, addr) <$> (sequenceMessage $ transcode (decryptMessage crypto) msg)
228
229decryptMessage :: Serialize x =>
230 TransportCrypto
231 -> Nonce24
232 -> Either (Encrypted x) (Assym (Encrypted x))
233 -> (Either String ∘ Identity) x
234decryptMessage crypto n (Right assymE) = plain $ ToxCrypto.decrypt secret e
235 where
236 secret = computeSharedSecret (transportSecret crypto) (senderKey assymE) n
237 e = assymData assymE
238 plain = Composed . fmap Identity . (>>= decodePlain)
239decryptMessage crypto n (Left e) = _todo
240
241
242sequenceMessage :: Applicative m => OnionMessage (m ∘ f) -> m (OnionMessage f)
243sequenceMessage (OnionAnnounce a) = fmap OnionAnnounce $ sequenceA $ fmap uncomposed a
244sequenceMessage (OnionToRoute pub a) = fmap (OnionToRoute pub) $ sequenceA $ fmap uncomposed a
245sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a
246sequenceMessage (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 <$> uncomposed dta
247
248transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> OnionMessage f -> OnionMessage g
249transcode f (OnionAnnounce a) = OnionAnnounce $ a { assymData = f (assymNonce a) (Right a) }
250transcode f (OnionToRoute pub a) = OnionToRoute pub $ a { assymData = f (assymNonce a) (Right a) }
251transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { assymData = f (assymNonce a) (Right a) }
252transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta
253
diff --git a/ToxAddress.hs b/ToxAddress.hs
index f0d4aba3..ea69f6e3 100644
--- a/ToxAddress.hs
+++ b/ToxAddress.hs
@@ -13,7 +13,7 @@
13{-# LANGUAGE ScopedTypeVariables #-} 13{-# LANGUAGE ScopedTypeVariables #-}
14{-# LANGUAGE TupleSections #-} 14{-# LANGUAGE TupleSections #-}
15{-# LANGUAGE TypeApplications #-} 15{-# LANGUAGE TypeApplications #-}
16module ToxAddress (NodeInfo(..),NodeId(..),nodeInfo) where 16module ToxAddress (NodeInfo(..),NodeId(..),nodeInfo,zeroID) where
17 17
18import Control.Applicative 18import Control.Applicative
19import Control.Monad 19import Control.Monad
@@ -88,6 +88,9 @@ instance S.Serialize NodeId where
88 88
89instance Bits NodeId where -- TODO 89instance Bits NodeId where -- TODO
90 90
91instance Hashable NodeId where
92 hashWithSalt salt (NodeId key) = hashWithSalt salt (BA.convert key :: ByteString)
93
91instance FiniteBits NodeId where 94instance FiniteBits NodeId where
92 finiteBitSize _ = 256 95 finiteBitSize _ = 256
93 96
diff --git a/ToxCrypto.hs b/ToxCrypto.hs
index 6b5e6f19..c2e2bbeb 100644
--- a/ToxCrypto.hs
+++ b/ToxCrypto.hs
@@ -2,6 +2,10 @@
2{-# LANGUAGE ScopedTypeVariables #-} 2{-# LANGUAGE ScopedTypeVariables #-}
3{-# LANGUAGE KindSignatures #-} 3{-# LANGUAGE KindSignatures #-}
4{-# LANGUAGE DeriveDataTypeable #-} 4{-# LANGUAGE DeriveDataTypeable #-}
5{-# LANGUAGE DeriveFunctor #-}
6{-# LANGUAGE DeriveTraversable #-}
7{-# LANGUAGE ExplicitNamespaces #-}
8{-# LANGUAGE TypeOperators #-}
5module ToxCrypto 9module ToxCrypto
6 ( PublicKey 10 ( PublicKey
7 , publicKey 11 , publicKey
@@ -9,9 +13,12 @@ module ToxCrypto
9 , SymmetricKey(..) 13 , SymmetricKey(..)
10 , TransportCrypto(..) 14 , TransportCrypto(..)
11 , Encrypted 15 , Encrypted
12 , Encrypted8 16 , Encrypted8(..)
17 , type (∘)(..)
13 , Assym(..) 18 , Assym(..)
14 , Plain 19 , Plain
20 , encodePlain
21 , decodePlain
15 , computeSharedSecret 22 , computeSharedSecret
16 , encrypt 23 , encrypt
17 , decrypt 24 , decrypt
@@ -24,6 +31,8 @@ module ToxCrypto
24 , Sized(..) 31 , Sized(..)
25 , Size(..) 32 , Size(..)
26 , State(..) 33 , State(..)
34 , zeros32
35 , zeros24
27 ) where 36 ) where
28 37
29import qualified Crypto.Cipher.Salsa as Salsa 38import qualified Crypto.Cipher.Salsa as Salsa
@@ -56,6 +65,7 @@ newtype Encrypted a = Encrypted ByteString
56newtype Encrypted8 a = E8 (Encrypted (a,Nonce8)) 65newtype Encrypted8 a = E8 (Encrypted (a,Nonce8))
57 deriving Serialize 66 deriving Serialize
58 67
68newtype (f ∘ g) x = Composed { uncomposed :: f (g x) }
59 69
60newtype Auth = Auth Poly1305.Auth deriving (Eq, ByteArrayAccess) 70newtype Auth = Auth Poly1305.Auth deriving (Eq, ByteArrayAccess)
61instance Ord Auth where 71instance Ord Auth where
@@ -229,6 +239,7 @@ data Assym a = Assym
229 , assymNonce :: Nonce24 239 , assymNonce :: Nonce24
230 , assymData :: a 240 , assymData :: a
231 } 241 }
242 deriving (Functor,Foldable,Traversable)
232 243
233newtype SymmetricKey = SymmetricKey ByteString 244newtype SymmetricKey = SymmetricKey ByteString
234 245