diff options
Diffstat (limited to 'src/Network/Tox')
-rw-r--r-- | src/Network/Tox/NodeId.hs | 15 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 48 |
2 files changed, 63 insertions, 0 deletions
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs index dc600db7..97faa942 100644 --- a/src/Network/Tox/NodeId.hs +++ b/src/Network/Tox/NodeId.hs | |||
@@ -13,6 +13,7 @@ | |||
13 | {-# LANGUAGE LambdaCase #-} | 13 | {-# LANGUAGE LambdaCase #-} |
14 | {-# LANGUAGE PatternSynonyms #-} | 14 | {-# LANGUAGE PatternSynonyms #-} |
15 | {-# LANGUAGE ScopedTypeVariables #-} | 15 | {-# LANGUAGE ScopedTypeVariables #-} |
16 | {-# LANGUAGE StandaloneDeriving #-} | ||
16 | {-# LANGUAGE TupleSections #-} | 17 | {-# LANGUAGE TupleSections #-} |
17 | {- LANGUAGE TypeApplications -} | 18 | {- LANGUAGE TypeApplications -} |
18 | module Network.Tox.NodeId | 19 | module Network.Tox.NodeId |
@@ -118,6 +119,19 @@ packPublicKey ws = BA.allocAndFreeze (8 * length ws) $ | |||
118 | -- convenient for short-circuiting xor/distance comparisons. The PublicKey | 119 | -- convenient for short-circuiting xor/distance comparisons. The PublicKey |
119 | -- format is convenient for encryption. | 120 | -- format is convenient for encryption. |
120 | data NodeId = NodeId [Word64] !(Maybe PublicKey) | 121 | data NodeId = NodeId [Word64] !(Maybe PublicKey) |
122 | deriving Data | ||
123 | |||
124 | instance Data PublicKey where | ||
125 | -- Data a => (forall d b . Data d => c (d -> b) -> d -> c b) -> (forall g . g -> c g) -> a -> c a | ||
126 | gfoldl f z txt = z (throwCryptoError . publicKey) `f` (BA.convert txt :: ByteString) | ||
127 | toConstr _ = error "Crypto.PubKey.Curve25519.toConstr" | ||
128 | gunfold _ _ = error "Crypto.PubKey.Curve25519.gunfold" | ||
129 | #if MIN_VERSION_base(4,2,0) | ||
130 | dataTypeOf _ = mkNoRepType "Crypto.PubKey.Curve25519.PublicKey" | ||
131 | #else | ||
132 | dataTypeOf _ = mkNorepType "Crypto.PubKey.Curve25519.PublicKey" | ||
133 | #endif | ||
134 | |||
121 | 135 | ||
122 | instance Eq NodeId where | 136 | instance Eq NodeId where |
123 | (NodeId ws _) == (NodeId xs _) | 137 | (NodeId ws _) == (NodeId xs _) |
@@ -586,6 +600,7 @@ parseNoSpamJID jid = do | |||
586 | '$' : b64digits -> solveBase64NoSpamID b64digits pub | 600 | '$' : b64digits -> solveBase64NoSpamID b64digits pub |
587 | '0' : 'x' : hexdigits -> do nospam <- readEither ('0':'x':hexdigits) | 601 | '0' : 'x' : hexdigits -> do nospam <- readEither ('0':'x':hexdigits) |
588 | return $ NoSpamId nospam pub | 602 | return $ NoSpamId nospam pub |
603 | _ -> Left "Missing nospam." | ||
589 | 604 | ||
590 | solveBase64NoSpamID :: String -> PublicKey -> Either String NoSpamId | 605 | solveBase64NoSpamID :: String -> PublicKey -> Either String NoSpamId |
591 | solveBase64NoSpamID b64digits pub = do | 606 | solveBase64NoSpamID b64digits pub = do |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 10bd5a44..ef9121f2 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -1,5 +1,6 @@ | |||
1 | {-# LANGUAGE CPP #-} | 1 | {-# LANGUAGE CPP #-} |
2 | {-# LANGUAGE DataKinds #-} | 2 | {-# LANGUAGE DataKinds #-} |
3 | {-# LANGUAGE DeriveDataTypeable #-} | ||
3 | {-# LANGUAGE FlexibleContexts #-} | 4 | {-# LANGUAGE FlexibleContexts #-} |
4 | {-# LANGUAGE FlexibleInstances #-} | 5 | {-# LANGUAGE FlexibleInstances #-} |
5 | {-# LANGUAGE GADTs #-} | 6 | {-# LANGUAGE GADTs #-} |
@@ -41,6 +42,8 @@ module Network.Tox.Onion.Transport | |||
41 | , decrypt | 42 | , decrypt |
42 | , peelSymmetric | 43 | , peelSymmetric |
43 | , OnionRoute(..) | 44 | , OnionRoute(..) |
45 | , N0 | ||
46 | , N1 | ||
44 | , N3 | 47 | , N3 |
45 | , onionKey | 48 | , onionKey |
46 | , onionAliasSelector | 49 | , onionAliasSelector |
@@ -62,6 +65,7 @@ import Control.Concurrent.STM | |||
62 | import Control.Monad | 65 | import Control.Monad |
63 | import qualified Data.ByteString as B | 66 | import qualified Data.ByteString as B |
64 | ;import Data.ByteString (ByteString) | 67 | ;import Data.ByteString (ByteString) |
68 | import Data.Data | ||
65 | import Data.Function | 69 | import Data.Function |
66 | import Data.Functor.Contravariant | 70 | import Data.Functor.Contravariant |
67 | import Data.Functor.Identity | 71 | import Data.Functor.Identity |
@@ -101,6 +105,16 @@ data OnionMessage (f :: * -> *) | |||
101 | | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm | 105 | | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm |
102 | | OnionToRouteResponse (Asymm (Encrypted DataToRoute)) | 106 | | OnionToRouteResponse (Asymm (Encrypted DataToRoute)) |
103 | 107 | ||
108 | deriving instance ( Eq (f (AnnounceRequest, Nonce8)) | ||
109 | , Eq (f AnnounceResponse) | ||
110 | , Eq (f DataToRoute) | ||
111 | ) => Eq (OnionMessage f) | ||
112 | |||
113 | deriving instance ( Ord (f (AnnounceRequest, Nonce8)) | ||
114 | , Ord (f AnnounceResponse) | ||
115 | , Ord (f DataToRoute) | ||
116 | ) => Ord (OnionMessage f) | ||
117 | |||
104 | deriving instance ( Show (f (AnnounceRequest, Nonce8)) | 118 | deriving instance ( Show (f (AnnounceRequest, Nonce8)) |
105 | , Show (f AnnounceResponse) | 119 | , Show (f AnnounceResponse) |
106 | , Show (f DataToRoute) | 120 | , Show (f DataToRoute) |
@@ -304,6 +318,30 @@ data OnionRequest n = OnionRequest | |||
304 | , onionForward :: Forwarding (ThreeMinus n) (OnionMessage Encrypted) | 318 | , onionForward :: Forwarding (ThreeMinus n) (OnionMessage Encrypted) |
305 | , pathFromOwner :: ReturnPath n | 319 | , pathFromOwner :: ReturnPath n |
306 | } | 320 | } |
321 | deriving (Eq,Ord) | ||
322 | |||
323 | |||
324 | instance (Typeable n, Sized (ReturnPath n), Serialize (ReturnPath n) | ||
325 | , Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) | ||
326 | ) => Data (OnionRequest n) where | ||
327 | gfoldl f z txt = z (either error id . S.decode) `f` S.encode txt | ||
328 | toConstr _ = error "OnionRequest.toConstr" | ||
329 | gunfold _ _ = error "OnionRequest.gunfold" | ||
330 | #if MIN_VERSION_base(4,2,0) | ||
331 | dataTypeOf _ = mkNoRepType "Network.Tox.Onion.Transport.OnionRequest" | ||
332 | #else | ||
333 | dataTypeOf _ = mkNorepType "Network.Tox.Onion.Transport.OnionRequest" | ||
334 | #endif | ||
335 | |||
336 | instance (Typeable n, Serialize (ReturnPath n)) => Data (OnionResponse n) where | ||
337 | gfoldl f z txt = z (either error id . S.decode) `f` S.encode txt | ||
338 | toConstr _ = error "OnionResponse.toConstr" | ||
339 | gunfold _ _ = error "OnionResponse.gunfold" | ||
340 | #if MIN_VERSION_base(4,2,0) | ||
341 | dataTypeOf _ = mkNoRepType "Network.Tox.Onion.Transport.OnionResponse" | ||
342 | #else | ||
343 | dataTypeOf _ = mkNorepType "Network.Tox.Onion.Transport.OnionResponse" | ||
344 | #endif | ||
307 | 345 | ||
308 | deriving instance ( Show (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) | 346 | deriving instance ( Show (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) |
309 | , KnownNat (PeanoNat n) | 347 | , KnownNat (PeanoNat n) |
@@ -336,6 +374,7 @@ data OnionResponse n = OnionResponse | |||
336 | { pathToOwner :: ReturnPath n | 374 | { pathToOwner :: ReturnPath n |
337 | , msgToOwner :: OnionMessage Encrypted | 375 | , msgToOwner :: OnionMessage Encrypted |
338 | } | 376 | } |
377 | deriving (Eq,Ord) | ||
339 | 378 | ||
340 | deriving instance KnownNat (PeanoNat n) => Show (OnionResponse n) | 379 | deriving instance KnownNat (PeanoNat n) => Show (OnionResponse n) |
341 | 380 | ||
@@ -383,6 +422,9 @@ type N1 = S N0 | |||
383 | type N2 = S N1 | 422 | type N2 = S N1 |
384 | type N3 = S N2 | 423 | type N3 = S N2 |
385 | 424 | ||
425 | deriving instance Data N0 | ||
426 | deriving instance Data n => Data (S n) | ||
427 | |||
386 | class KnownPeanoNat n where | 428 | class KnownPeanoNat n where |
387 | peanoVal :: p n -> Int | 429 | peanoVal :: p n -> Int |
388 | 430 | ||
@@ -399,6 +441,9 @@ data ReturnPath n where | |||
399 | NoReturnPath :: ReturnPath N0 | 441 | NoReturnPath :: ReturnPath N0 |
400 | ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath n)) -> ReturnPath (S n) | 442 | ReturnPath :: Nonce24 -> Encrypted (Addressed (ReturnPath n)) -> ReturnPath (S n) |
401 | 443 | ||
444 | deriving instance Eq (ReturnPath n) | ||
445 | deriving instance Ord (ReturnPath n) | ||
446 | |||
402 | -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce) | 447 | -- Size: 59 = 1(family) + 16(ip) + 2(port) +16(mac) + 24(nonce) |
403 | instance Sized (ReturnPath N0) where size = ConstSize 0 | 448 | instance Sized (ReturnPath N0) where size = ConstSize 0 |
404 | instance Sized (ReturnPath n) => Sized (ReturnPath (S n)) where | 449 | instance Sized (ReturnPath n) => Sized (ReturnPath (S n)) where |
@@ -444,6 +489,9 @@ data Forwarding n msg where | |||
444 | NotForwarded :: msg -> Forwarding N0 msg | 489 | NotForwarded :: msg -> Forwarding N0 msg |
445 | Forwarding :: PublicKey -> Encrypted (Addressed (Forwarding n msg)) -> Forwarding (S n) msg | 490 | Forwarding :: PublicKey -> Encrypted (Addressed (Forwarding n msg)) -> Forwarding (S n) msg |
446 | 491 | ||
492 | deriving instance Eq msg => Eq (Forwarding n msg) | ||
493 | deriving instance Ord msg => Ord (Forwarding n msg) | ||
494 | |||
447 | instance Show msg => Show (Forwarding N0 msg) where | 495 | instance Show msg => Show (Forwarding N0 msg) where |
448 | show (NotForwarded x) = "NotForwarded "++show x | 496 | show (NotForwarded x) = "NotForwarded "++show x |
449 | 497 | ||