summaryrefslogtreecommitdiff
path: root/src/Network/Tox/Onion/Transport.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-10-21 22:01:16 -0400
committerjoe <joe@jerkface.net>2017-10-21 22:01:16 -0400
commit7ab09c43f0bb6f8f42c0156644869dfe78aa0b89 (patch)
tree760fb412fe55e7de11e5011a1f54f1f4ee5afefb /src/Network/Tox/Onion/Transport.hs
parentcbdcc6500d6bda9948268312fc0bfb17955e53c5 (diff)
Renamed Assym -> Asymm (short for asymmetric).
Diffstat (limited to 'src/Network/Tox/Onion/Transport.hs')
-rw-r--r--src/Network/Tox/Onion/Transport.hs74
1 files changed, 37 insertions, 37 deletions
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs
index 82f2c8a7..203d7dc7 100644
--- a/src/Network/Tox/Onion/Transport.hs
+++ b/src/Network/Tox/Onion/Transport.hs
@@ -78,17 +78,17 @@ type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a
78type UDPTransport = Transport String SockAddr ByteString 78type UDPTransport = Transport String SockAddr ByteString
79 79
80 80
81getOnionAssym :: Get (Assym (Encrypted DataToRoute)) 81getOnionAsymm :: Get (Asymm (Encrypted DataToRoute))
82getOnionAssym = getAliasedAssym 82getOnionAsymm = getAliasedAsymm
83 83
84putOnionAssym :: Serialize a => Word8 -> Put -> Assym a -> Put 84putOnionAsymm :: Serialize a => Word8 -> Put -> Asymm a -> Put
85putOnionAssym typ p a = put typ >> p >> putAliasedAssym a 85putOnionAsymm typ p a = put typ >> p >> putAliasedAsymm a
86 86
87data OnionMessage (f :: * -> *) 87data OnionMessage (f :: * -> *)
88 = OnionAnnounce (Assym (f (AnnounceRequest,Nonce8))) 88 = OnionAnnounce (Asymm (f (AnnounceRequest,Nonce8)))
89 | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse) 89 | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse)
90 | OnionToRoute PublicKey (Assym (Encrypted DataToRoute)) -- destination key, aliased Assym 90 | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm
91 | OnionToRouteResponse (Assym (Encrypted DataToRoute)) 91 | OnionToRouteResponse (Asymm (Encrypted DataToRoute))
92 92
93deriving instance ( Show (f (AnnounceRequest, Nonce8)) 93deriving instance ( Show (f (AnnounceRequest, Nonce8))
94 , Show (f AnnounceResponse) 94 , Show (f AnnounceResponse)
@@ -96,10 +96,10 @@ deriving instance ( Show (f (AnnounceRequest, Nonce8))
96 ) => Show (OnionMessage f) 96 ) => Show (OnionMessage f)
97 97
98msgNonce :: OnionMessage f -> Nonce24 98msgNonce :: OnionMessage f -> Nonce24
99msgNonce (OnionAnnounce a) = assymNonce a 99msgNonce (OnionAnnounce a) = asymmNonce a
100msgNonce (OnionAnnounceResponse _ n24 _) = n24 100msgNonce (OnionAnnounceResponse _ n24 _) = n24
101msgNonce (OnionToRoute _ a) = assymNonce a 101msgNonce (OnionToRoute _ a) = asymmNonce a
102msgNonce (OnionToRouteResponse a) = assymNonce a 102msgNonce (OnionToRouteResponse a) = asymmNonce a
103 103
104data AliasSelector = SearchingAlias | AnnouncingAlias SecretKey PublicKey 104data AliasSelector = SearchingAlias | AnnouncingAlias SecretKey PublicKey
105 deriving (Eq,Show) 105 deriving (Eq,Show)
@@ -138,18 +138,18 @@ instance Serialize (OnionMessage Encrypted) where
138 get = do 138 get = do
139 typ <- get 139 typ <- get
140 case typ :: Word8 of 140 case typ :: Word8 of
141 0x83 -> OnionAnnounce <$> getAliasedAssym 141 0x83 -> OnionAnnounce <$> getAliasedAsymm
142 0x85 -> OnionToRoute <$> getPublicKey <*> getAliasedAssym 142 0x85 -> OnionToRoute <$> getPublicKey <*> getAliasedAsymm
143 t -> fail ("Unknown onion payload: " ++ show t) 143 t -> fail ("Unknown onion payload: " ++ show t)
144 `fromMaybe` getOnionReply t 144 `fromMaybe` getOnionReply t
145 put (OnionAnnounce a) = putWord8 0x83 >> putAliasedAssym a 145 put (OnionAnnounce a) = putWord8 0x83 >> putAliasedAsymm a
146 put (OnionToRoute k a) = putWord8 0x85 >> putPublicKey k >> putAliasedAssym a 146 put (OnionToRoute k a) = putWord8 0x85 >> putPublicKey k >> putAliasedAsymm a
147 put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x 147 put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x
148 put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAssym a 148 put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAsymm a
149 149
150onionToOwner :: Assym a -> ReturnPath N3 -> SockAddr -> Either String (OnionDestination r) 150onionToOwner :: Asymm a -> ReturnPath N3 -> SockAddr -> Either String (OnionDestination r)
151onionToOwner assym ret3 saddr = do 151onionToOwner asymm ret3 saddr = do
152 ni <- nodeInfo (key2id $ senderKey assym) saddr 152 ni <- nodeInfo (key2id $ senderKey asymm) saddr
153 return $ OnionToOwner ni ret3 153 return $ OnionToOwner ni ret3
154-- data CookieAddress = WithoutCookie NodeInfo | CookieAddress Cookie SockAddr 154-- data CookieAddress = WithoutCookie NodeInfo | CookieAddress Cookie SockAddr
155 155
@@ -157,11 +157,11 @@ onionToOwner assym ret3 saddr = do
157onion :: Sized msg => 157onion :: Sized msg =>
158 ByteString 158 ByteString
159 -> SockAddr 159 -> SockAddr
160 -> Get (Assym (Encrypted msg) -> t) 160 -> Get (Asymm (Encrypted msg) -> t)
161 -> Either String (t, OnionDestination r) 161 -> Either String (t, OnionDestination r)
162onion bs saddr getf = do (f,(assym,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs 162onion bs saddr getf = do (f,(asymm,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs
163 oaddr <- onionToOwner assym ret3 saddr 163 oaddr <- onionToOwner asymm ret3 saddr
164 return (f assym, oaddr) 164 return (f asymm, oaddr)
165 165
166parseOnionAddr :: (SockAddr -> Nonce8 -> IO (Maybe (OnionDestination r))) 166parseOnionAddr :: (SockAddr -> Nonce8 -> IO (Maybe (OnionDestination r)))
167 -> (ByteString, SockAddr) 167 -> (ByteString, SockAddr)
@@ -187,14 +187,14 @@ parseOnionAddr lookupSender (msg,saddr)
187 187
188getOnionReply :: Word8 -> Maybe (Get (OnionMessage Encrypted)) 188getOnionReply :: Word8 -> Maybe (Get (OnionMessage Encrypted))
189getOnionReply 0x84 = Just $ OnionAnnounceResponse <$> get <*> get <*> get 189getOnionReply 0x84 = Just $ OnionAnnounceResponse <$> get <*> get <*> get
190getOnionReply 0x86 = Just $ OnionToRouteResponse <$> getOnionAssym 190getOnionReply 0x86 = Just $ OnionToRouteResponse <$> getOnionAsymm
191getOnionReply _ = Nothing 191getOnionReply _ = Nothing
192 192
193putOnionMsg :: OnionMessage Encrypted -> Put 193putOnionMsg :: OnionMessage Encrypted -> Put
194putOnionMsg (OnionAnnounce a) = putOnionAssym 0x83 (return ()) a 194putOnionMsg (OnionAnnounce a) = putOnionAsymm 0x83 (return ()) a
195putOnionMsg (OnionToRoute pubkey a) = putOnionAssym 0x85 (putPublicKey pubkey) a 195putOnionMsg (OnionToRoute pubkey a) = putOnionAsymm 0x85 (putPublicKey pubkey) a
196putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x 196putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x
197putOnionMsg (OnionToRouteResponse a) = putOnionAssym 0x86 (return ()) a 197putOnionMsg (OnionToRouteResponse a) = putOnionAsymm 0x86 (return ()) a
198 198
199encodeOnionAddr :: (NodeInfo -> r -> IO (Maybe OnionRoute)) 199encodeOnionAddr :: (NodeInfo -> r -> IO (Maybe OnionRoute))
200 -> (OnionMessage Encrypted,OnionDestination r) 200 -> (OnionMessage Encrypted,OnionDestination r)
@@ -470,7 +470,7 @@ peelOnion :: Serialize (Addressed (Forwarding n t))
470 -> Forwarding (S n) t 470 -> Forwarding (S n) t
471 -> Either String (Addressed (Forwarding n t)) 471 -> Either String (Addressed (Forwarding n t))
472peelOnion crypto nonce (Forwarding k fwd) = 472peelOnion crypto nonce (Forwarding k fwd) =
473 fmap runIdentity $ uncomposed $ decryptMessage (dhtKey crypto) nonce (Right $ Assym k nonce fwd) 473 fmap runIdentity $ uncomposed $ decryptMessage (dhtKey crypto) nonce (Right $ Asymm k nonce fwd)
474 474
475handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a 475handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a
476handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do 476handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do
@@ -499,13 +499,13 @@ instance S.Serialize AnnounceRequest where
499 get = AnnounceRequest <$> S.get <*> S.get <*> S.get 499 get = AnnounceRequest <$> S.get <*> S.get <*> S.get
500 put (AnnounceRequest p s k) = S.put (p,s,k) 500 put (AnnounceRequest p s k) = S.put (p,s,k)
501 501
502getOnionRequest :: Sized msg => Get (Assym (Encrypted msg), ReturnPath N3) 502getOnionRequest :: Sized msg => Get (Asymm (Encrypted msg), ReturnPath N3)
503getOnionRequest = do 503getOnionRequest = do
504 -- Assumes return path is constant size so that we can isolate 504 -- Assumes return path is constant size so that we can isolate
505 -- the variable-sized prefix. 505 -- the variable-sized prefix.
506 cnt <- remaining 506 cnt <- remaining
507 a <- isolate (case size :: Size (ReturnPath N3) of ConstSize n -> cnt - n) 507 a <- isolate (case size :: Size (ReturnPath N3) of ConstSize n -> cnt - n)
508 getAliasedAssym 508 getAliasedAsymm
509 path <- get 509 path <- get
510 return (a,path) 510 return (a,path)
511 511
@@ -619,7 +619,7 @@ encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> IO
619encrypt crypto msg rpath = do 619encrypt crypto msg rpath = do
620 (skey,pkey) <- selectKey crypto msg rpath -- source key 620 (skey,pkey) <- selectKey crypto msg rpath -- source key
621 let okey = onionKey rpath -- destination key 621 let okey = onionKey rpath -- destination key
622 return ( transcode ( (. (runIdentity . either id assymData)) 622 return ( transcode ( (. (runIdentity . either id asymmData))
623 . encryptMessage skey okey) 623 . encryptMessage skey okey)
624 msg 624 msg
625 , rpath) 625 , rpath)
@@ -652,12 +652,12 @@ decryptMessage :: Serialize x =>
652 (SecretKey,PublicKey) 652 (SecretKey,PublicKey)
653 -> Nonce24 653 -> Nonce24
654 -> Either (PublicKey, Encrypted x) 654 -> Either (PublicKey, Encrypted x)
655 (Assym (Encrypted x)) 655 (Asymm (Encrypted x))
656 -> (Either String ∘ Identity) x 656 -> (Either String ∘ Identity) x
657decryptMessage crypto n arg = plain $ ToxCrypto.decrypt secret e 657decryptMessage crypto n arg = plain $ ToxCrypto.decrypt secret e
658 where 658 where
659 secret = computeSharedSecret (fst crypto) sender n 659 secret = computeSharedSecret (fst crypto) sender n
660 (sender,e) = either id (senderKey &&& assymData) arg 660 (sender,e) = either id (senderKey &&& asymmData) arg
661 plain = Composed . fmap Identity . (>>= decodePlain) 661 plain = Composed . fmap Identity . (>>= decodePlain)
662 662
663 663
@@ -668,12 +668,12 @@ sequenceMessage (OnionToRoute pub a) = pure $ OnionToRoute pub a
668sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a 668sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a
669-- sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a 669-- sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a
670 670
671transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> OnionMessage f -> OnionMessage g 671transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Asymm (f a)) -> g a) -> OnionMessage f -> OnionMessage g
672transcode f (OnionAnnounce a) = OnionAnnounce $ a { assymData = f (assymNonce a) (Right a) } 672transcode f (OnionAnnounce a) = OnionAnnounce $ a { asymmData = f (asymmNonce a) (Right a) }
673transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta 673transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta
674transcode f (OnionToRoute pub a) = OnionToRoute pub a 674transcode f (OnionToRoute pub a) = OnionToRoute pub a
675transcode f (OnionToRouteResponse a) = OnionToRouteResponse a 675transcode f (OnionToRouteResponse a) = OnionToRouteResponse a
676-- transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { assymData = f (assymNonce a) (Right a) } 676-- transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { asymmData = f (asymmNonce a) (Right a) }
677 677
678 678
679data OnionRoute = OnionRoute 679data OnionRoute = OnionRoute
@@ -738,14 +738,14 @@ instance Show Rendezvous where
738parseDataToRoute 738parseDataToRoute
739 :: TransportCrypto 739 :: TransportCrypto
740 -> (OnionMessage Encrypted,OnionDestination r) 740 -> (OnionMessage Encrypted,OnionDestination r)
741 -> Either (Assym (Encrypted DataToRoute),Rendezvous) (OnionMessage Encrypted, OnionDestination r) 741 -> Either (Asymm (Encrypted DataToRoute),Rendezvous) (OnionMessage Encrypted, OnionDestination r)
742parseDataToRoute crypto (OnionToRouteResponse dta, od) 742parseDataToRoute crypto (OnionToRouteResponse dta, od)
743 = Left ( dta 743 = Left ( dta
744 , Rendezvous (onionAliasPublic crypto) $ onionNodeInfo od ) 744 , Rendezvous (onionAliasPublic crypto) $ onionNodeInfo od )
745parseDataToRoute _ msg = Right msg 745parseDataToRoute _ msg = Right msg
746 746
747encodeDataToRoute :: TransportCrypto 747encodeDataToRoute :: TransportCrypto
748 -> (Assym (Encrypted DataToRoute),Rendezvous) 748 -> (Asymm (Encrypted DataToRoute),Rendezvous)
749 -> Maybe (OnionMessage Encrypted,OnionDestination r) 749 -> Maybe (OnionMessage Encrypted,OnionDestination r)
750encodeDataToRoute crypto (dta, Rendezvous pub ni) 750encodeDataToRoute crypto (dta, Rendezvous pub ni)
751 = Just ( OnionToRoute pub -- Public key of destination node 751 = Just ( OnionToRoute pub -- Public key of destination node