diff options
author | joe <joe@jerkface.net> | 2017-09-13 22:39:35 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-09-13 22:39:35 -0400 |
commit | e6680dfb566c692d410a357f32ce021da871eb64 (patch) | |
tree | cc7275bcee046702774273bd5392fd2ceef6de87 /OnionTransport.hs | |
parent | 3029c5c5ea5c01ed4471d63d6f384ba3ac55164c (diff) |
Correctly isolate variable-width onion payloads.
Diffstat (limited to 'OnionTransport.hs')
-rw-r--r-- | OnionTransport.hs | 80 |
1 files changed, 56 insertions, 24 deletions
diff --git a/OnionTransport.hs b/OnionTransport.hs index 485f9d64..2a1003dc 100644 --- a/OnionTransport.hs +++ b/OnionTransport.hs | |||
@@ -43,23 +43,25 @@ import ToxAddress | |||
43 | import qualified ToxCrypto | 43 | import qualified ToxCrypto |
44 | import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey) | 44 | import DHTTransport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey) |
45 | 45 | ||
46 | import Debug.Trace | ||
46 | import Control.Arrow | 47 | import Control.Arrow |
47 | import Control.Concurrent.STM | 48 | import Control.Concurrent.STM |
48 | import qualified Data.ByteString as B | 49 | import qualified Data.ByteString as B |
49 | ;import Data.ByteString (ByteString) | 50 | ;import Data.ByteString (ByteString) |
50 | import Data.Coerce | 51 | import Data.Coerce |
52 | import Data.Function | ||
51 | import Data.Functor.Contravariant | 53 | import Data.Functor.Contravariant |
52 | import Data.Functor.Identity | 54 | import Data.Functor.Identity |
53 | import Data.IP | 55 | import Data.IP |
54 | import Data.Maybe | 56 | import Data.Maybe |
55 | import Data.Monoid | 57 | import Data.Monoid |
56 | import Data.Serialize as S | 58 | import Data.Serialize as S |
59 | import Data.Type.Equality | ||
57 | import Data.Typeable | 60 | import Data.Typeable |
58 | import Data.Word | 61 | import Data.Word |
62 | import GHC.Generics () | ||
59 | import GHC.TypeLits | 63 | import GHC.TypeLits |
60 | import Network.Socket | 64 | import Network.Socket |
61 | import GHC.Generics () | ||
62 | import Data.Type.Equality | ||
63 | 65 | ||
64 | type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a | 66 | type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a |
65 | 67 | ||
@@ -163,25 +165,27 @@ encodeOnionAddr (msg,addr) = ( runPut (putOnionMsg msg >> putpath), saddr ) | |||
163 | | OnionToMe a <- addr = (a, return ()) | 165 | | OnionToMe a <- addr = (a, return ()) |
164 | 166 | ||
165 | forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport -- HandleHi a -> IO a -> HandleLo a | 167 | forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport -- HandleHi a -> IO a -> HandleLo a |
166 | forwardOnions crypto udp = udp { awaitMessage = await' } | 168 | forwardOnions crypto udp = udp { awaitMessage = forwardAwait crypto udp } |
167 | where | 169 | |
168 | -- forMe :: HandleHi | 170 | -- forMe :: HandleHi |
169 | -- forThem :: handleLo | 171 | -- forThem :: handleLo |
170 | await' :: HandleLo a -> IO a | 172 | forwardAwait :: TransportCrypto -> UDPTransport -> HandleLo a -> IO a |
171 | await' forThem = awaitMessage udp $ \case | 173 | forwardAwait crypto udp kont = do |
174 | fix $ \another -> do | ||
175 | awaitMessage udp $ \case | ||
172 | m@(Just (Right (bs,saddr))) -> case B.head bs of | 176 | m@(Just (Right (bs,saddr))) -> case B.head bs of |
173 | 0x80 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N0) crypto saddr udp (await' forThem) | 177 | 0x80 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N0) crypto saddr udp another |
174 | 0x81 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N1) crypto saddr udp (await' forThem) | 178 | 0x81 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N1) crypto saddr udp another |
175 | 0x82 -> forward forThem bs $ handleOnionRequest (Proxy :: Proxy N2) crypto saddr udp (await' forThem) | 179 | 0x82 -> forward kont bs $ handleOnionRequest (Proxy :: Proxy N2) crypto saddr udp another |
176 | 0x8c -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N3) crypto saddr udp (await' forThem) | 180 | 0x8c -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N3) crypto saddr udp another |
177 | 0x8d -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N2) crypto saddr udp (await' forThem) | 181 | 0x8d -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N2) crypto saddr udp another |
178 | 0x8e -> forward forThem bs $ handleOnionResponse (Proxy :: Proxy N1) crypto saddr udp (await' forThem) | 182 | 0x8e -> forward kont bs $ handleOnionResponse (Proxy :: Proxy N1) crypto saddr udp another |
179 | _ -> forThem m | 183 | _ -> kont m |
180 | m -> forThem m | 184 | m -> kont m |
181 | 185 | ||
182 | forward :: forall c b b1. Serialize b => | 186 | forward :: forall c b b1. (Serialize b, Show b) => |
183 | (Maybe (Either String b1) -> c) -> ByteString -> (b -> c) -> c | 187 | (Maybe (Either String b1) -> c) -> ByteString -> (b -> c) -> c |
184 | forward forMe bs f = either (forMe . Just . Left) f $ decode $ B.tail bs | 188 | forward kont bs f = either (kont . Just . Left) f $ decode $ B.tail bs |
185 | 189 | ||
186 | class SumToThree a b | 190 | class SumToThree a b |
187 | 191 | ||
@@ -211,10 +215,21 @@ data OnionRequest n = OnionRequest | |||
211 | , pathFromOwner :: ReturnPath n | 215 | , pathFromOwner :: ReturnPath n |
212 | } | 216 | } |
213 | 217 | ||
218 | deriving instance ( Show (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) | ||
219 | , KnownNat (PeanoNat n) | ||
220 | ) => Show (OnionRequest n) | ||
221 | |||
214 | instance ( Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) | 222 | instance ( Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) |
223 | , Sized (ReturnPath n) | ||
215 | , Serialize (ReturnPath n) | 224 | , Serialize (ReturnPath n) |
216 | ) => Serialize (OnionRequest n) where | 225 | ) => Serialize (OnionRequest n) where |
217 | get = OnionRequest <$> get <*> get <*> get | 226 | get = do |
227 | n24 <- get | ||
228 | cnt <- remaining | ||
229 | let fwdsize = case size :: Size (ReturnPath n) of ConstSize n -> cnt - n | ||
230 | fwd <- isolate fwdsize get | ||
231 | rpath <- get | ||
232 | return $ OnionRequest n24 fwd rpath | ||
218 | put (OnionRequest n f p) = put n >> put f >> put p | 233 | put (OnionRequest n f p) = put n >> put f >> put p |
219 | 234 | ||
220 | -- getRequest :: _ | 235 | -- getRequest :: _ |
@@ -228,6 +243,8 @@ data OnionResponse n = OnionResponse | |||
228 | , msgToOwner :: OnionMessage Encrypted | 243 | , msgToOwner :: OnionMessage Encrypted |
229 | } | 244 | } |
230 | 245 | ||
246 | deriving instance KnownNat (PeanoNat n) => Show (OnionResponse n) | ||
247 | |||
231 | instance ( Serialize (ReturnPath n) ) => Serialize (OnionResponse n) where | 248 | instance ( Serialize (ReturnPath n) ) => Serialize (OnionResponse n) where |
232 | get = OnionResponse <$> get <*> (get >>= getOnionReply) | 249 | get = OnionResponse <$> get <*> (get >>= getOnionReply) |
233 | put (OnionResponse p m) = put p >> putOnionMsg m | 250 | put (OnionResponse p m) = put p >> putOnionMsg m |
@@ -324,6 +341,17 @@ data Forwarding n msg where | |||
324 | NotForwarded :: msg -> Forwarding N0 msg | 341 | NotForwarded :: msg -> Forwarding N0 msg |
325 | Forwarding :: Assym (Encrypted (Addressed (Forwarding n msg))) -> Forwarding (S n) msg | 342 | Forwarding :: Assym (Encrypted (Addressed (Forwarding n msg))) -> Forwarding (S n) msg |
326 | 343 | ||
344 | instance Show msg => Show (Forwarding N0 msg) where | ||
345 | show (NotForwarded x) = "NotForwarded "++show x | ||
346 | |||
347 | instance ( KnownNat (PeanoNat (S n)) | ||
348 | , Show (Encrypted (Addressed (Forwarding n msg))) | ||
349 | ) => Show (Forwarding (S n) msg) where | ||
350 | show (Forwarding a) = unwords [ "Forwarding" | ||
351 | , "("++show (natVal (Proxy :: Proxy (PeanoNat (S n))))++")" | ||
352 | , show a | ||
353 | ] | ||
354 | |||
327 | instance Sized msg => Sized (Forwarding N0 msg) | 355 | instance Sized msg => Sized (Forwarding N0 msg) |
328 | where size = case size :: Size msg of | 356 | where size = case size :: Size msg of |
329 | ConstSize n -> ConstSize n | 357 | ConstSize n -> ConstSize n |
@@ -342,13 +370,17 @@ instance (Serialize (Encrypted (Addressed (Forwarding n msg)))) => Serialize (Fo | |||
342 | get = Forwarding <$> getAliasedAssym | 370 | get = Forwarding <$> getAliasedAssym |
343 | put (Forwarding x) = putAliasedAssym x | 371 | put (Forwarding x) = putAliasedAssym x |
344 | 372 | ||
345 | handleOnionRequest :: LessThanThree n => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a | 373 | handleOnionRequest :: ( LessThanThree n |
374 | , Sized (ReturnPath n) | ||
375 | ) => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a | ||
346 | handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do | 376 | handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do |
377 | putStrLn "handleOnionRequest" | ||
347 | (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto | 378 | (sym, snonce) <- atomically ( (,) <$> transportSymmetric crypto |
348 | <*> transportNewNonce crypto ) | 379 | <*> transportNewNonce crypto ) |
349 | case peelOnion crypto msg of | 380 | case peelOnion crypto msg of |
350 | Left e -> do | 381 | Left e -> do |
351 | -- todo report encryption error | 382 | -- todo report encryption error |
383 | putStrLn $ "peelOnion: " ++ e | ||
352 | kont | 384 | kont |
353 | Right (Addressed dst msg') -> do | 385 | Right (Addressed dst msg') -> do |
354 | sendMessage udp dst (S.encode $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath) | 386 | sendMessage udp dst (S.encode $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath) |