diff options
author | joe <joe@jerkface.net> | 2017-09-05 18:14:13 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-09-05 18:14:13 -0400 |
commit | 186a0c7e24efc8e70274076ebf106e7e23085561 (patch) | |
tree | 115f64f5a6025fe6604b2b972349711f390329b7 | |
parent | 4f9ad88773271a46ed1df899ad9a360de6c09a4e (diff) |
Implemented onion routing.
-rw-r--r-- | OnionTransport.hs | 220 | ||||
-rw-r--r-- | ToxAddress.hs | 2 | ||||
-rw-r--r-- | ToxCrypto.hs | 1 |
3 files changed, 171 insertions, 52 deletions
diff --git a/OnionTransport.hs b/OnionTransport.hs index 7a837a2b..e05e2ca0 100644 --- a/OnionTransport.hs +++ b/OnionTransport.hs | |||
@@ -4,11 +4,15 @@ | |||
4 | {-# LANGUAGE GADTs #-} | 4 | {-# LANGUAGE GADTs #-} |
5 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 5 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
6 | {-# LANGUAGE KindSignatures #-} | 6 | {-# LANGUAGE KindSignatures #-} |
7 | {-# LANGUAGE StandaloneDeriving #-} | ||
8 | {-# LANGUAGE LambdaCase #-} | 7 | {-# LANGUAGE LambdaCase #-} |
8 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
9 | {-# LANGUAGE PartialTypeSignatures #-} | ||
9 | {-# LANGUAGE RankNTypes #-} | 10 | {-# LANGUAGE RankNTypes #-} |
10 | {-# LANGUAGE ScopedTypeVariables #-} | 11 | {-# LANGUAGE ScopedTypeVariables #-} |
12 | {-# LANGUAGE StandaloneDeriving #-} | ||
11 | {-# LANGUAGE TupleSections #-} | 13 | {-# LANGUAGE TupleSections #-} |
14 | {-# LANGUAGE TypeFamilies #-} | ||
15 | {-# LANGUAGE TypeFamilyDependencies #-} | ||
12 | {-# LANGUAGE TypeOperators #-} | 16 | {-# LANGUAGE TypeOperators #-} |
13 | {-# LANGUAGE UndecidableInstances #-} | 17 | {-# LANGUAGE UndecidableInstances #-} |
14 | module OnionTransport | 18 | module OnionTransport |
@@ -31,6 +35,7 @@ module OnionTransport | |||
31 | , decrypt | 35 | , decrypt |
32 | ) where | 36 | ) where |
33 | 37 | ||
38 | import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort) | ||
34 | import Network.QueryResponse | 39 | import Network.QueryResponse |
35 | import ToxCrypto hiding (encrypt,decrypt) | 40 | import ToxCrypto hiding (encrypt,decrypt) |
36 | import ToxAddress | 41 | import ToxAddress |
@@ -38,18 +43,22 @@ import qualified ToxCrypto | |||
38 | import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey) | 43 | import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey) |
39 | 44 | ||
40 | import Control.Arrow | 45 | import Control.Arrow |
46 | import Control.Concurrent.STM | ||
41 | import qualified Data.ByteString as B | 47 | import qualified Data.ByteString as B |
42 | ;import Data.ByteString (ByteString) | 48 | ;import Data.ByteString (ByteString) |
43 | import Data.Coerce | 49 | import Data.Coerce |
44 | import Data.Functor.Contravariant | 50 | import Data.Functor.Contravariant |
45 | import Data.Functor.Identity | 51 | import Data.Functor.Identity |
52 | import Data.IP | ||
53 | import Data.Maybe | ||
46 | import Data.Monoid | 54 | import Data.Monoid |
47 | import Data.Serialize as S | 55 | import Data.Serialize as S |
48 | import Data.Typeable | 56 | import Data.Typeable |
49 | import Data.Word | 57 | import Data.Word |
50 | import GHC.TypeLits | 58 | import GHC.TypeLits |
51 | import Network.Socket | 59 | import Network.Socket |
52 | import GHC.Generics | 60 | import GHC.Generics () |
61 | import Data.Type.Equality | ||
53 | 62 | ||
54 | type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a | 63 | type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a |
55 | 64 | ||
@@ -68,7 +77,7 @@ data OnionMessage (f :: * -> *) | |||
68 | | OnionToRoute PublicKey (Assym (f DataToRoute)) -- destination key, aliased Assym | 77 | | OnionToRoute PublicKey (Assym (f DataToRoute)) -- destination key, aliased Assym |
69 | | OnionToRouteResponse (Assym (f DataToRoute)) | 78 | | OnionToRouteResponse (Assym (f DataToRoute)) |
70 | 79 | ||
71 | data OnionToOwner = OnionToOwner NodeInfo (ReturnPath 3) | 80 | data OnionToOwner = OnionToOwner NodeInfo (ReturnPath N3) |
72 | | OnionToMe SockAddr -- SockAddr is immediate peer in route | 81 | | OnionToMe SockAddr -- SockAddr is immediate peer in route |
73 | deriving Show | 82 | deriving Show |
74 | 83 | ||
@@ -83,7 +92,21 @@ instance Sized (OnionMessage Encrypted) where | |||
83 | OnionToRouteResponse a -> case size of ConstSize n -> n + 1 | 92 | OnionToRouteResponse a -> case size of ConstSize n -> n + 1 |
84 | VarSize f -> f a + 1 | 93 | VarSize f -> f a + 1 |
85 | 94 | ||
86 | onionToOwner :: Assym a -> ReturnPath 3 -> SockAddr -> Either String OnionToOwner | 95 | instance Serialize (OnionMessage Encrypted) where |
96 | get = do | ||
97 | typ <- get | ||
98 | case typ :: Word8 of | ||
99 | 0x83 -> OnionAnnounce <$> getAliasedAssym | ||
100 | 0x85 -> OnionToRoute <$> getPublicKey <*> getAliasedAssym | ||
101 | 0x84 -> getOnionReply typ | ||
102 | 0x86 -> getOnionReply typ | ||
103 | t -> fail $ "Unknown onion payload: " ++ show t | ||
104 | put (OnionAnnounce a) = putWord8 0x83 >> putAliasedAssym a | ||
105 | put (OnionToRoute k a) = putWord8 0x85 >> putPublicKey k >> putAliasedAssym a | ||
106 | put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x | ||
107 | put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAssym a | ||
108 | |||
109 | onionToOwner :: Assym a -> ReturnPath N3 -> SockAddr -> Either String OnionToOwner | ||
87 | onionToOwner assym ret3 saddr = do | 110 | onionToOwner assym ret3 saddr = do |
88 | ni <- nodeInfo (NodeId $ senderKey assym) saddr | 111 | ni <- nodeInfo (NodeId $ senderKey assym) saddr |
89 | return $ OnionToOwner ni ret3 | 112 | return $ OnionToOwner ni ret3 |
@@ -137,12 +160,12 @@ forwardOnions crypto udp = udp { awaitMessage = await' } | |||
137 | await' :: HandleLo a -> IO a | 160 | await' :: HandleLo a -> IO a |
138 | await' forThem = awaitMessage udp $ \case | 161 | await' forThem = awaitMessage udp $ \case |
139 | m@(Just (Right (bs,saddr))) -> case B.head bs of | 162 | m@(Just (Right (bs,saddr))) -> case B.head bs of |
140 | 0x80 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy 0) crypto saddr (forThem m) | 163 | 0x80 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N0) crypto saddr udp (await' forThem) |
141 | 0x81 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy 1) crypto saddr (forThem m) | 164 | 0x81 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N1) crypto saddr udp (await' forThem) |
142 | 0x82 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy 2) crypto saddr (forThem m) | 165 | 0x82 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N2) crypto saddr udp (await' forThem) |
143 | 0x8c -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy 3) crypto saddr (forThem m) | 166 | 0x8c -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N3) crypto saddr udp (await' forThem) |
144 | 0x8d -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy 2) crypto saddr (forThem m) | 167 | 0x8d -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N2) crypto saddr udp (await' forThem) |
145 | 0x8e -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy 1) crypto saddr (forThem m) | 168 | 0x8e -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N1) crypto saddr udp (await' forThem) |
146 | _ -> forThem m | 169 | _ -> forThem m |
147 | m -> forThem m | 170 | m -> forThem m |
148 | 171 | ||
@@ -150,23 +173,47 @@ forward :: forall c b b1. Serialize b => | |||
150 | (Maybe (Either String b1) -> c) -> ByteString -> (b -> c) -> c | 173 | (Maybe (Either String b1) -> c) -> ByteString -> (b -> c) -> c |
151 | forward forMe bs f = either (forMe . Just . Left) f $ decode $ B.tail bs | 174 | forward forMe bs f = either (forMe . Just . Left) f $ decode $ B.tail bs |
152 | 175 | ||
176 | class SumToThree a b | ||
177 | |||
178 | instance SumToThree N0 N3 | ||
179 | instance SumToThree (S a) b => SumToThree a (S b) | ||
180 | |||
181 | class ( Serialize (ReturnPath n) | ||
182 | , Serialize (ReturnPath (S n)) | ||
183 | , Serialize (Forwarding (ThreeMinus (S n)) (OnionMessage Encrypted)) | ||
184 | , ThreeMinus n ~ S (ThreeMinus (S n)) | ||
185 | ) => LessThanThree n | ||
186 | |||
187 | instance LessThanThree N0 | ||
188 | instance LessThanThree N1 | ||
189 | instance LessThanThree N2 | ||
190 | |||
191 | type family ThreeMinus n = r | r -> n where | ||
192 | ThreeMinus N3 = N0 | ||
193 | ThreeMinus N2 = N1 | ||
194 | ThreeMinus N1 = N2 | ||
195 | ThreeMinus N0 = N3 | ||
196 | |||
153 | -- n = 0, 1, 2 | 197 | -- n = 0, 1, 2 |
154 | data OnionRequest (n :: Nat) = OnionRequest | 198 | data OnionRequest n = OnionRequest |
155 | { onionNonce :: Nonce24 | 199 | { onionNonce :: Nonce24 |
156 | , onionForward :: Forwarding (3 - n) (OnionMessage Encrypted) | 200 | , onionForward :: Forwarding (ThreeMinus n) (OnionMessage Encrypted) |
157 | , pathFromOwner :: ReturnPath n | 201 | , pathFromOwner :: ReturnPath n |
158 | } | 202 | } |
159 | 203 | ||
160 | instance ( Serialize (Forwarding (3 - n) (OnionMessage Encrypted)) | 204 | instance ( Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) |
161 | , Serialize (ReturnPath n) | 205 | , Serialize (ReturnPath n) |
162 | ) => Serialize (OnionRequest n) where | 206 | ) => Serialize (OnionRequest n) where |
163 | get = OnionRequest <$> get <*> get <*> get | 207 | get = OnionRequest <$> get <*> get <*> get |
164 | put (OnionRequest n f p) = put n >> put f >> put p | 208 | put (OnionRequest n f p) = put n >> put f >> put p |
165 | 209 | ||
210 | -- getRequest :: _ | ||
211 | -- getRequest = OnionRequest <$> get <*> get <*> get | ||
212 | |||
166 | -- n = 1, 2, 3 | 213 | -- n = 1, 2, 3 |
167 | -- Attributed (Encrypted ( | 214 | -- Attributed (Encrypted ( |
168 | 215 | ||
169 | data OnionResponse (n :: Nat) = OnionResponse | 216 | data OnionResponse n = OnionResponse |
170 | { pathToOwner :: ReturnPath n | 217 | { pathToOwner :: ReturnPath n |
171 | , msgToOwner :: OnionMessage Encrypted | 218 | , msgToOwner :: OnionMessage Encrypted |
172 | } | 219 | } |
@@ -183,25 +230,67 @@ instance Sized a => Sized (Addressed a) where | |||
183 | ConstSize n -> ConstSize $ 1{-family-} + 16{-ip-} + 2{-port-} + n | 230 | ConstSize n -> ConstSize $ 1{-family-} + 16{-ip-} + 2{-port-} + n |
184 | VarSize f -> VarSize $ \x -> 1{-family-} + 16{-ip-} + 2{-port-} + f x | 231 | VarSize f -> VarSize $ \x -> 1{-family-} + 16{-ip-} + 2{-port-} + f x |
185 | 232 | ||
186 | data ReturnPath (n :: Nat) where | 233 | getForwardAddr :: S.Get SockAddr |
187 | NoReturnPath :: ReturnPath 0 | 234 | getForwardAddr = do |
188 | ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath (n - 1))) -> ReturnPath n | 235 | addrfam <- S.get :: S.Get Word8 |
236 | ip <- getIP addrfam | ||
237 | case ip of IPv4 _ -> S.skip 12 -- compliant peers would zero-fill this. | ||
238 | IPv6 _ -> return () | ||
239 | port <- S.get :: S.Get PortNumber | ||
240 | return $ setPort port $ toSockAddr ip | ||
241 | |||
242 | |||
243 | putForwardAddr :: SockAddr -> S.Put | ||
244 | putForwardAddr saddr = fromMaybe (return $ error "unsupported SockAddr family") $ do | ||
245 | port <- sockAddrPort saddr | ||
246 | ip <- fromSockAddr $ either id id $ either4or6 saddr | ||
247 | return $ do | ||
248 | case ip of | ||
249 | IPv4 ip4 -> S.put (0x02 :: Word8) >> S.put ip4 >> S.putByteString (B.replicate 12 0) | ||
250 | IPv6 ip6 -> S.put (0x0a :: Word8) >> S.put ip6 | ||
251 | S.put port | ||
252 | |||
253 | instance Serialize a => Serialize (Addressed a) where | ||
254 | get = Addressed <$> getForwardAddr <*> get | ||
255 | put (Addressed addr x) = putForwardAddr addr >> put x | ||
256 | |||
257 | data N0 | ||
258 | data S n | ||
259 | type N1 = S N0 | ||
260 | type N2 = S N1 | ||
261 | type N3 = S N2 | ||
262 | |||
263 | type family PeanoNat p where | ||
264 | PeanoNat N0 = 0 | ||
265 | PeanoNat (S n) = 1 + PeanoNat n | ||
266 | |||
267 | data ReturnPath n where | ||
268 | NoReturnPath :: ReturnPath N0 | ||
269 | ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath n)) -> ReturnPath (S n) | ||
189 | 270 | ||
190 | -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce) | 271 | -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce) |
191 | instance KnownNat n => Sized (ReturnPath n) where | 272 | instance Sized (ReturnPath N0) where size = ConstSize 0 |
192 | size = ConstSize $ 59 * fromIntegral (natVal (Proxy :: Proxy n)) | 273 | instance Sized (ReturnPath n) => Sized (ReturnPath (S n)) where |
274 | size = ConstSize 59 <> contramap (\x -> let _ = x :: ReturnPath (S n) | ||
275 | in error "non-constant ReturnPath size") | ||
276 | (size :: Size (ReturnPath n)) | ||
277 | |||
278 | {- | ||
279 | instance KnownNat (PeanoNat n) => Sized (ReturnPath n) where | ||
280 | size = ConstSize $ 59 * fromIntegral (natVal (Proxy :: Proxy (PeanoNat n))) | ||
281 | -} | ||
193 | 282 | ||
194 | instance Serialize (ReturnPath 0) where get = pure NoReturnPath | 283 | instance Serialize (ReturnPath N0) where get = pure NoReturnPath |
195 | put NoReturnPath = pure () | 284 | put NoReturnPath = pure () |
196 | 285 | ||
197 | instance Serialize (ReturnPath 1) where get = ReturnPath <$> get <*> get | 286 | instance Serialize (ReturnPath N1) where |
198 | put (ReturnPath n24 p) = put n24 >> put p | 287 | get = ReturnPath <$> get <*> get |
288 | put (ReturnPath n24 p) = put n24 >> put p | ||
199 | 289 | ||
200 | instance Serialize (ReturnPath 2) where get = ReturnPath <$> get <*> get | 290 | instance (Sized (ReturnPath n), Serialize (ReturnPath n)) => Serialize (ReturnPath (S (S n))) where |
201 | put (ReturnPath n24 p) = put n24 >> put p | 291 | get = ReturnPath <$> get <*> get |
292 | put (ReturnPath n24 p) = put n24 >> put p | ||
202 | 293 | ||
203 | instance Serialize (ReturnPath 3) where get = ReturnPath <$> get <*> get | ||
204 | put (ReturnPath n24 p) = put n24 >> put p | ||
205 | 294 | ||
206 | {- | 295 | {- |
207 | -- This doesn't work because it tried to infer it for (0 - 1) | 296 | -- This doesn't work because it tried to infer it for (0 - 1) |
@@ -210,8 +299,8 @@ instance (Serialize (Encrypted (Addressed (ReturnPath (n - 1))))) => Serialize ( | |||
210 | put (ReturnPath n24 p) = put n24 >> put p | 299 | put (ReturnPath n24 p) = put n24 >> put p |
211 | -} | 300 | -} |
212 | 301 | ||
213 | instance KnownNat n => Show (ReturnPath n) where | 302 | instance KnownNat (PeanoNat n) => Show (ReturnPath n) where |
214 | show rpath = "ReturnPath" ++ show (natVal rpath) | 303 | show rpath = "ReturnPath" ++ show (natVal (Proxy :: Proxy (PeanoNat n))) |
215 | 304 | ||
216 | 305 | ||
217 | -- instance KnownNat n => Serialize (ReturnPath n) where | 306 | -- instance KnownNat n => Serialize (ReturnPath n) where |
@@ -220,38 +309,67 @@ instance KnownNat n => Show (ReturnPath n) where | |||
220 | -- put (ReturnPath bs) = putByteString bs | 309 | -- put (ReturnPath bs) = putByteString bs |
221 | 310 | ||
222 | 311 | ||
223 | data Forwarding (n :: Nat) msg where | 312 | data Forwarding n msg where |
224 | NotForwarded :: msg -> Forwarding 0 msg | 313 | NotForwarded :: msg -> Forwarding N0 msg |
225 | Forwarding :: Assym (Encrypted (Addressed (Forwarding (n - 1) msg))) -> Forwarding n msg | 314 | Forwarding :: Assym (Encrypted (Addressed (Forwarding n msg))) -> Forwarding (S n) msg |
226 | 315 | ||
227 | instance Sized msg => Sized (Forwarding 0 msg) | 316 | instance Sized msg => Sized (Forwarding N0 msg) |
228 | where size = case size :: Size msg of | 317 | where size = case size :: Size msg of |
229 | ConstSize n -> ConstSize n | 318 | ConstSize n -> ConstSize n |
230 | VarSize f -> VarSize $ \(NotForwarded x) -> f x | 319 | VarSize f -> VarSize $ \(NotForwarded x) -> f x |
231 | instance Sized msg => Sized (Forwarding 1 msg) | 320 | |
232 | where size = case size :: Size (Assym (Encrypted (Addressed (Forwarding 0 msg)))) of | 321 | instance Sized (Forwarding n msg) => Sized (Forwarding (S n) msg) |
233 | ConstSize n -> ConstSize n | 322 | where size = case size :: Size (Assym (Encrypted (Addressed (Forwarding n msg)))) of |
234 | VarSize f -> VarSize $ \(Forwarding a) -> f a | ||
235 | instance Sized msg => Sized (Forwarding 2 msg) | ||
236 | where size = case size :: Size (Assym (Encrypted (Addressed (Forwarding 1 msg)))) of | ||
237 | ConstSize n -> ConstSize n | ||
238 | VarSize f -> VarSize $ \(Forwarding a) -> f a | ||
239 | instance Sized msg => Sized (Forwarding 3 msg) | ||
240 | where size = case size :: Size (Assym (Encrypted (Addressed (Forwarding 2 msg)))) of | ||
241 | ConstSize n -> ConstSize n | 323 | ConstSize n -> ConstSize n |
242 | VarSize f -> VarSize $ \(Forwarding a) -> f a | 324 | VarSize f -> VarSize $ \(Forwarding a) -> f a |
243 | 325 | ||
326 | instance Serialize msg => Serialize (Forwarding N0 msg) where | ||
327 | get = NotForwarded <$> get | ||
328 | put (NotForwarded msg) = put msg | ||
244 | 329 | ||
245 | instance (Serialize (Encrypted (Addressed (Forwarding (n - 1) msg)))) => Serialize (Forwarding n msg) where | 330 | instance (Serialize (Encrypted (Addressed (Forwarding n msg)))) => Serialize (Forwarding (S n) msg) where |
246 | get = Forwarding <$> getAliasedAssym | 331 | get = Forwarding <$> getAliasedAssym |
247 | put (Forwarding x) = putAliasedAssym x | 332 | put (Forwarding x) = putAliasedAssym x |
248 | 333 | ||
334 | handleOnionRequest :: LessThanThree n => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a | ||
335 | handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do | ||
336 | (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto | ||
337 | <*> transportNewNonce crypto ) | ||
338 | case peelOnion crypto msg of | ||
339 | Left e -> do | ||
340 | -- todo report encryption error | ||
341 | kont | ||
342 | Right (Addressed dst msg') -> do | ||
343 | sendMessage udp dst (S.encode $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath) | ||
344 | kont | ||
345 | |||
346 | wrapSymmetric :: Serialize (ReturnPath n) => | ||
347 | SymmetricKey -> Nonce24 -> SockAddr -> ReturnPath n -> ReturnPath (S n) | ||
348 | wrapSymmetric sym n saddr rpath = ReturnPath n $ encryptSymmetric sym n (encodePlain $ Addressed saddr rpath) | ||
349 | |||
350 | peelSymmetric :: Serialize (Addressed (ReturnPath n)) | ||
351 | => SymmetricKey -> ReturnPath (S n) -> Either String (Addressed (ReturnPath n)) | ||
352 | peelSymmetric sym (ReturnPath nonce e) = decryptSymmetric sym nonce e >>= decodePlain | ||
353 | |||
354 | |||
355 | peelOnion :: Serialize (Addressed (Forwarding n t)) | ||
356 | => TransportCrypto | ||
357 | -> Forwarding (S n) t | ||
358 | -> Either String (Addressed (Forwarding n t)) | ||
359 | peelOnion crypto (Forwarding fwd) = | ||
360 | fmap runIdentity $ uncomposed $ decryptMessage crypto (assymNonce fwd) (Right fwd) | ||
361 | |||
362 | handleOnionResponse :: Serialize (ReturnPath n) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a | ||
363 | handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do | ||
364 | sym <- atomically $ transportSymmetric crypto | ||
365 | case peelSymmetric sym path of | ||
366 | Left e -> do | ||
367 | -- todo report encryption error | ||
368 | kont | ||
369 | Right (Addressed dst path') -> do | ||
370 | sendMessage udp dst (S.encode $ OnionResponse path' msg) | ||
371 | kont | ||
249 | 372 | ||
250 | handleOnionRequest :: KnownNat n => proxy n -> TransportCrypto -> SockAddr -> IO a -> OnionRequest n -> IO a | ||
251 | handleOnionRequest = _todo | ||
252 | |||
253 | handleOnionResponse :: KnownNat n => proxy n -> TransportCrypto -> SockAddr -> IO a -> OnionResponse n -> IO a | ||
254 | handleOnionResponse = _todo | ||
255 | 373 | ||
256 | data AnnounceRequest = AnnounceRequest | 374 | data AnnounceRequest = AnnounceRequest |
257 | { announcePingId :: Nonce32 -- Ping ID | 375 | { announcePingId :: Nonce32 -- Ping ID |
@@ -265,12 +383,12 @@ instance S.Serialize AnnounceRequest where | |||
265 | get = AnnounceRequest <$> S.get <*> S.get <*> S.get | 383 | get = AnnounceRequest <$> S.get <*> S.get <*> S.get |
266 | put (AnnounceRequest p s k) = S.put (p,s,k) | 384 | put (AnnounceRequest p s k) = S.put (p,s,k) |
267 | 385 | ||
268 | getOnionRequest :: Sized msg => Get (Assym (Encrypted msg), ReturnPath 3) | 386 | getOnionRequest :: Sized msg => Get (Assym (Encrypted msg), ReturnPath N3) |
269 | getOnionRequest = do | 387 | getOnionRequest = do |
270 | -- Assumes return path is constant size so that we can isolate | 388 | -- Assumes return path is constant size so that we can isolate |
271 | -- the variable-sized prefix. | 389 | -- the variable-sized prefix. |
272 | cnt <- remaining | 390 | cnt <- remaining |
273 | a <- isolate (case size :: Size (ReturnPath 3) of ConstSize n -> cnt - n) | 391 | a <- isolate (case size :: Size (ReturnPath N3) of ConstSize n -> cnt - n) |
274 | getAliasedAssym | 392 | getAliasedAssym |
275 | path <- get | 393 | path <- get |
276 | return (a,path) | 394 | return (a,path) |
diff --git a/ToxAddress.hs b/ToxAddress.hs index 04ee7d6f..c95c221b 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 #-} |
16 | module ToxAddress (NodeInfo(..),NodeId(..),nodeInfo,nodeAddr,zeroID,key2id,id2key) where | 16 | module ToxAddress (NodeInfo(..),NodeId(..),nodeInfo,nodeAddr,zeroID,key2id,id2key,getIP) where |
17 | 17 | ||
18 | import Control.Applicative | 18 | import Control.Applicative |
19 | import Control.Monad | 19 | import Control.Monad |
diff --git a/ToxCrypto.hs b/ToxCrypto.hs index 9dea7477..5e602fc9 100644 --- a/ToxCrypto.hs +++ b/ToxCrypto.hs | |||
@@ -309,6 +309,7 @@ data TransportCrypto = TransportCrypto | |||
309 | { transportSecret :: SecretKey | 309 | { transportSecret :: SecretKey |
310 | , transportPublic :: PublicKey | 310 | , transportPublic :: PublicKey |
311 | , transportSymmetric :: STM SymmetricKey | 311 | , transportSymmetric :: STM SymmetricKey |
312 | , transportNewNonce :: STM Nonce24 | ||
312 | } | 313 | } |
313 | 314 | ||
314 | getPublicKey :: S.Get PublicKey | 315 | getPublicKey :: S.Get PublicKey |