diff options
author | joe <joe@jerkface.net> | 2017-07-10 20:30:10 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-07-10 20:30:10 -0400 |
commit | 2fdb0342f8cfcaf4924a0ce43e7fccb236eb0d5e (patch) | |
tree | fe013b9d665d6a6c03f6a35af017851f105115c0 /src/Network/DHT | |
parent | c565ec07f37006a5abb7b3bc5a1b08013fbeb5d7 (diff) |
Fixed Tox decryption.
Diffstat (limited to 'src/Network/DHT')
-rw-r--r-- | src/Network/DHT/Mainline.hs | 7 | ||||
-rw-r--r-- | src/Network/DHT/Tox.hs | 112 | ||||
-rw-r--r-- | src/Network/DHT/Types.hs | 93 |
3 files changed, 212 insertions, 0 deletions
diff --git a/src/Network/DHT/Mainline.hs b/src/Network/DHT/Mainline.hs index 9af42a6d..bdf9e8b2 100644 --- a/src/Network/DHT/Mainline.hs +++ b/src/Network/DHT/Mainline.hs | |||
@@ -56,6 +56,8 @@ | |||
56 | -- <http://pdos.csail.mit.edu/~petar/papers/maymounkov-kademlia-lncs.pdf> | 56 | -- <http://pdos.csail.mit.edu/~petar/papers/maymounkov-kademlia-lncs.pdf> |
57 | -- | 57 | -- |
58 | {-# LANGUAGE CPP #-} | 58 | {-# LANGUAGE CPP #-} |
59 | {-# LANGUAGE StandaloneDeriving #-} | ||
60 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
59 | {-# LANGUAGE DeriveDataTypeable #-} | 61 | {-# LANGUAGE DeriveDataTypeable #-} |
60 | {-# LANGUAGE FlexibleInstances #-} | 62 | {-# LANGUAGE FlexibleInstances #-} |
61 | {-# LANGUAGE MultiParamTypeClasses #-} | 63 | {-# LANGUAGE MultiParamTypeClasses #-} |
@@ -94,6 +96,7 @@ module Network.DHT.Mainline | |||
94 | , checkToken | 96 | , checkToken |
95 | ) where | 97 | ) where |
96 | 98 | ||
99 | import Data.String | ||
97 | import Control.Applicative | 100 | import Control.Applicative |
98 | import Data.Bool | 101 | import Data.Bool |
99 | #ifdef VERSION_bencoding | 102 | #ifdef VERSION_bencoding |
@@ -570,3 +573,7 @@ instance Kademlia KMessageOf where | |||
570 | initializeDHTData = TorrentData | 573 | initializeDHTData = TorrentData |
571 | <$> newTVarIO def | 574 | <$> newTVarIO def |
572 | <*> (newTVarIO =<< nullSessionTokens) | 575 | <*> (newTVarIO =<< nullSessionTokens) |
576 | |||
577 | deriving instance IsString (QueryMethod dht) => IsString (Method dht param result) | ||
578 | deriving instance BEncode (QueryMethod dht) => BEncode (Method dht param result) | ||
579 | |||
diff --git a/src/Network/DHT/Tox.hs b/src/Network/DHT/Tox.hs new file mode 100644 index 00000000..d6fc866f --- /dev/null +++ b/src/Network/DHT/Tox.hs | |||
@@ -0,0 +1,112 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} | ||
3 | module Network.DHT.Tox where | ||
4 | |||
5 | import Data.Serialize | ||
6 | import Data.Default | ||
7 | import Text.PrettyPrint.HughesPJClass | ||
8 | |||
9 | import Network.DHT.Types | ||
10 | import Network.DatagramServer.Types | ||
11 | import qualified Network.DatagramServer.Tox as Tox | ||
12 | import Network.KRPC.Method | ||
13 | import Data.Word | ||
14 | import Data.ByteString (ByteString) | ||
15 | import Data.IP | ||
16 | import Data.Bool | ||
17 | import Data.Maybe | ||
18 | import Control.Monad | ||
19 | import System.Random | ||
20 | |||
21 | instance Kademlia Tox.Message where | ||
22 | data DHTData Tox.Message ip = ToxData | ||
23 | namePing _ = Tox.Ping | ||
24 | nameFindNodes _ = Tox.GetNodes | ||
25 | initializeDHTData = return ToxData | ||
26 | |||
27 | instance Pretty (NodeId Tox.Message) where | ||
28 | pPrint (Tox.NodeId nid) = encodeHexDoc nid | ||
29 | |||
30 | instance Serialize (Query Tox.Message (Ping Tox.Message)) where | ||
31 | get = getToxPing False Network.DHT.Types.Query Tox.QueryNonce | ||
32 | put (Network.DHT.Types.Query extra Ping) = putToxPing False (Tox.qryNonce extra) | ||
33 | instance Serialize (Response Tox.Message (Ping Tox.Message)) where | ||
34 | get = getToxPing True Network.DHT.Types.Response Tox.ResponseNonce | ||
35 | put (Network.DHT.Types.Response extra Ping) = putToxPing True (Tox.rspNonce extra) | ||
36 | |||
37 | instance Serialize (Query Tox.Message (FindNode Tox.Message ip)) where | ||
38 | get = do | ||
39 | nid <- get | ||
40 | n8 <- get | ||
41 | return $ Network.DHT.Types.Query (Tox.QueryNonce n8) (FindNode nid) | ||
42 | put (Network.DHT.Types.Query (Tox.QueryNonce n8) (FindNode nid)) = do | ||
43 | put nid | ||
44 | put n8 | ||
45 | instance Serialize (Response Tox.Message (NodeFound Tox.Message IPv4)) where | ||
46 | get = do | ||
47 | num <- get :: Get Word8 | ||
48 | when (num > 4) $ fail "Too many nodes in Tox get-nodes reply" | ||
49 | ns0 <- sequence $ replicate (fromIntegral num) (nodeFormatToNodeInfo <$> get) | ||
50 | -- TODO: Allow tcp and ipv6. For now filtering to udp ip4... | ||
51 | let ns = flip mapMaybe ns0 $ \(NodeInfo nid addr u) -> do | ||
52 | guard $ not u | ||
53 | ip4 <- fromAddr addr | ||
54 | return $ NodeInfo nid ip4 () | ||
55 | n8 <- get | ||
56 | return $ Network.DHT.Types.Response (Tox.ResponseNonce n8) $ NodeFound ns | ||
57 | put (Network.DHT.Types.Response (Tox.ResponseNonce n8) (NodeFound ns)) = do | ||
58 | put ( fromIntegral (length ns) :: Word8 ) | ||
59 | forM_ ns $ \(NodeInfo nid ip4 ()) -> do | ||
60 | put Tox.NodeFormat { nodePublicKey = nid | ||
61 | , nodeIsTCP = False | ||
62 | , nodeIP = IPv4 (nodeHost ip4) | ||
63 | , nodePort = nodePort ip4 | ||
64 | } | ||
65 | put n8 | ||
66 | |||
67 | instance KRPC Tox.Message (Query Tox.Message (FindNode Tox.Message IPv4)) | ||
68 | (Response Tox.Message (NodeFound Tox.Message IPv4)) where | ||
69 | method = Method Tox.GetNodes | ||
70 | validateExchange = validateToxExchange | ||
71 | makeQueryExtra _ _ _ _ = Tox.QueryNonce <$> randomIO | ||
72 | makeResponseExtra _ _ q _ = return $ Tox.ResponseNonce $ Tox.qryNonce $ queryExtra q | ||
73 | messageSender q _ = Tox.msgClient q | ||
74 | messageResponder _ r = Tox.msgClient r | ||
75 | |||
76 | instance KRPC Tox.Message (Query Tox.Message (Ping Tox.Message)) | ||
77 | (Response Tox.Message (Ping Tox.Message)) where | ||
78 | method = Method Tox.Ping | ||
79 | validateExchange = validateToxExchange | ||
80 | makeQueryExtra _ _ _ _ = Tox.QueryNonce <$> randomIO | ||
81 | makeResponseExtra _ _ q _ = return $ Tox.ResponseNonce $ Tox.qryNonce $ queryExtra q | ||
82 | messageSender q _ = Tox.msgClient q | ||
83 | messageResponder _ r = Tox.msgClient r | ||
84 | |||
85 | instance DataHandlers ByteString Tox.Message | ||
86 | |||
87 | instance Default Bool where def = False | ||
88 | |||
89 | getToxPing isPong c n = do | ||
90 | q'r <- get :: Get Word8 | ||
91 | when (bool 0 1 isPong /= q'r) $ | ||
92 | fail "Tox ping/pong parse fail." | ||
93 | n8 <- get :: Get Tox.Nonce8 | ||
94 | return $ c (n n8) Ping | ||
95 | |||
96 | putToxPing isPong n8 = do | ||
97 | put (bool 0 1 isPong :: Word8) | ||
98 | put n8 | ||
99 | |||
100 | validateToxExchange q r = qnonce == rnonce | ||
101 | where | ||
102 | qnonce = Tox.qryNonce . queryExtra . Tox.msgPayload $ q | ||
103 | rnonce = Tox.rspNonce . responseExtra . Tox.msgPayload $ r | ||
104 | |||
105 | |||
106 | nodeFormatToNodeInfo nf = NodeInfo nid addr u | ||
107 | where | ||
108 | u = Tox.nodeIsTCP nf | ||
109 | addr = NodeAddr (Tox.nodeIP nf) (Tox.nodePort nf) | ||
110 | nid = Tox.nodePublicKey nf | ||
111 | |||
112 | -- instance Default Bool where def = False | ||
diff --git a/src/Network/DHT/Types.hs b/src/Network/DHT/Types.hs index 47f98ebe..287d5680 100644 --- a/src/Network/DHT/Types.hs +++ b/src/Network/DHT/Types.hs | |||
@@ -1,3 +1,6 @@ | |||
1 | {-# LANGUAGE DefaultSignatures #-} | ||
2 | {-# LANGUAGE GADTs, MultiParamTypeClasses #-} | ||
3 | {-# LANGUAGE FunctionalDependencies #-} | ||
1 | {-# LANGUAGE TypeFamilies #-} | 4 | {-# LANGUAGE TypeFamilies #-} |
2 | {-# LANGUAGE ScopedTypeVariables #-} | 5 | {-# LANGUAGE ScopedTypeVariables #-} |
3 | {-# LANGUAGE StandaloneDeriving #-} | 6 | {-# LANGUAGE StandaloneDeriving #-} |
@@ -14,6 +17,11 @@ import Network.DatagramServer.Types | |||
14 | import Network.DHT.Routing | 17 | import Network.DHT.Routing |
15 | import Data.Typeable | 18 | import Data.Typeable |
16 | import GHC.Generics | 19 | import GHC.Generics |
20 | import Data.Serialize | ||
21 | import Data.Hashable | ||
22 | import Data.String | ||
23 | import Data.Monoid | ||
24 | import Data.Char | ||
17 | 25 | ||
18 | data TableParameters msg ip u = TableParameters | 26 | data TableParameters msg ip u = TableParameters |
19 | { maxBuckets :: Int | 27 | { maxBuckets :: Int |
@@ -81,3 +89,88 @@ class Kademlia dht where | |||
81 | namePing :: Proxy dht -> QueryMethod dht | 89 | namePing :: Proxy dht -> QueryMethod dht |
82 | nameFindNodes :: Proxy dht -> QueryMethod dht | 90 | nameFindNodes :: Proxy dht -> QueryMethod dht |
83 | initializeDHTData :: IO (DHTData dht ip) | 91 | initializeDHTData :: IO (DHTData dht ip) |
92 | data MethodHandler raw dht ip = | ||
93 | forall a b. ( SerializableTo raw (Response dht b) | ||
94 | , SerializableTo raw (Query dht a) | ||
95 | , KRPC dht (Query dht a) (Response dht b) | ||
96 | ) => MethodHandler (QueryMethod dht) (NodeAddr ip -> a -> IO b) | ||
97 | |||
98 | class DataHandlers raw dht where | ||
99 | dataHandlers :: | ||
100 | ( Ord ip , Hashable ip, Typeable ip, Serialize ip) => | ||
101 | (NodeId dht -> IO [NodeInfo dht ip ()]) | ||
102 | -> DHTData dht ip | ||
103 | -> [MethodHandler raw dht ip] | ||
104 | dataHandlers _ _ = [] | ||
105 | |||
106 | -- | Method datatype used to describe method name, parameters and | ||
107 | -- return values of procedure. Client use a method to /invoke/, server | ||
108 | -- /implements/ the method to make the actual work. | ||
109 | -- | ||
110 | -- We use the following fantom types to ensure type-safiety: | ||
111 | -- | ||
112 | -- * param: Type of method parameters. | ||
113 | -- | ||
114 | -- * result: Type of return value of the method. | ||
115 | -- | ||
116 | newtype Method dht param result = Method { methodName :: QueryMethod dht } | ||
117 | |||
118 | deriving instance Eq (QueryMethod dht) => Eq (Method dht param result) | ||
119 | deriving instance Ord (QueryMethod dht) => Ord (Method dht param result) | ||
120 | |||
121 | -- | Example: | ||
122 | -- | ||
123 | -- @show (Method \"concat\" :: [Int] Int) == \"concat :: [Int] -> Int\"@ | ||
124 | -- | ||
125 | instance (Show (QueryMethod dht), Typeable a, Typeable b) => Show (Method dht a b) where | ||
126 | showsPrec _ = showsMethod | ||
127 | |||
128 | showsMethod :: forall dht a b. ( Show (QueryMethod dht), Typeable a , Typeable b ) => Method dht a b -> ShowS | ||
129 | showsMethod (Method name) = | ||
130 | -- showString (BC.unpack name) <> | ||
131 | shows (show name) <> | ||
132 | showString " :: " <> | ||
133 | shows paramsTy <> | ||
134 | showString " -> " <> | ||
135 | shows valuesTy | ||
136 | where | ||
137 | impossible = error "KRPC.showsMethod: impossible" | ||
138 | paramsTy = typeOf (impossible :: a) | ||
139 | valuesTy = typeOf (impossible :: b) | ||
140 | |||
141 | -- | In order to perform or handle KRPC query you need to provide | ||
142 | -- corresponding 'KRPC' class. | ||
143 | -- | ||
144 | -- Example: | ||
145 | -- | ||
146 | -- @ | ||
147 | -- data Ping = Ping Text deriving BEncode | ||
148 | -- data Pong = Pong Text deriving BEncode | ||
149 | -- | ||
150 | -- instance 'KRPC' Ping Pong where | ||
151 | -- method = \"ping\" | ||
152 | -- @ | ||
153 | -- | ||
154 | class ( Typeable req, Typeable resp, Envelope dht) | ||
155 | => KRPC dht req resp | req -> resp, resp -> req where | ||
156 | |||
157 | -- | Method name. Default implementation uses lowercased @req@ | ||
158 | -- datatype name. | ||
159 | -- | ||
160 | method :: Method dht req resp | ||
161 | |||
162 | -- TODO add underscores | ||
163 | default method :: (IsString (QueryMethod dht), Typeable req) => Method dht req resp | ||
164 | method = Method $ fromString $ map toLower $ show $ typeOf hole | ||
165 | where | ||
166 | hole = error "krpc.method: impossible" :: req | ||
167 | |||
168 | |||
169 | validateExchange :: dht req -> dht resp -> Bool | ||
170 | validateExchange _ _ = True | ||
171 | |||
172 | makeQueryExtra :: DHTData dht ip -> NodeId dht -> Proxy req -> Proxy resp -> IO (QueryExtra dht) | ||
173 | makeResponseExtra :: DHTData dht ip -> NodeId dht -> req -> Proxy resp -> IO (ResponseExtra dht) | ||
174 | |||
175 | messageSender :: dht req -> Proxy resp -> NodeId dht | ||
176 | messageResponder :: Proxy req -> dht resp -> NodeId dht | ||