diff options
author | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-21 02:18:16 +0400 |
---|---|---|
committer | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-21 02:18:16 +0400 |
commit | e3f7c822a3e6f57260881fa3245ad2b89087ecce (patch) | |
tree | eac74591d19f38d710994264c2549c28ce4a9b56 | |
parent | 4693ed53ec5cdbf0b2fa993d169c96e45f2dce91 (diff) |
Add DHT messages
-rw-r--r-- | bittorrent.cabal | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core/Node.hs | 9 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Message.hs | 240 |
3 files changed, 249 insertions, 2 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal index 0208f0c2..c98c13c7 100644 --- a/bittorrent.cabal +++ b/bittorrent.cabal | |||
@@ -58,7 +58,7 @@ library | |||
58 | Network.BitTorrent.Core.PeerId | 58 | Network.BitTorrent.Core.PeerId |
59 | Network.BitTorrent.Core.PeerAddr | 59 | Network.BitTorrent.Core.PeerAddr |
60 | -- Network.BitTorrent.DHT | 60 | -- Network.BitTorrent.DHT |
61 | -- Network.BitTorrent.DHT.Message | 61 | Network.BitTorrent.DHT.Message |
62 | -- Network.BitTorrent.DHT.Protocol | 62 | -- Network.BitTorrent.DHT.Protocol |
63 | Network.BitTorrent.DHT.Routing | 63 | Network.BitTorrent.DHT.Routing |
64 | -- Network.BitTorrent.DHT.Session | 64 | -- Network.BitTorrent.DHT.Session |
diff --git a/src/Network/BitTorrent/Core/Node.hs b/src/Network/BitTorrent/Core/Node.hs index a1a87135..0cb95dd2 100644 --- a/src/Network/BitTorrent/Core/Node.hs +++ b/src/Network/BitTorrent/Core/Node.hs | |||
@@ -1,6 +1,7 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | 1 | {-# LANGUAGE RecordWildCards #-} |
2 | {-# LANGUAGE TemplateHaskell #-} | 2 | {-# LANGUAGE TemplateHaskell #-} |
3 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 3 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
4 | {-# LANGUAGE DeriveDataTypeable #-} | ||
4 | module Network.BitTorrent.Core.Node | 5 | module Network.BitTorrent.Core.Node |
5 | ( -- * Node ID | 6 | ( -- * Node ID |
6 | NodeId | 7 | NodeId |
@@ -20,7 +21,9 @@ import Data.Aeson.TH | |||
20 | import Data.Bits | 21 | import Data.Bits |
21 | import Data.ByteString as BS | 22 | import Data.ByteString as BS |
22 | import Data.BEncode as BE | 23 | import Data.BEncode as BE |
24 | import Data.Default | ||
23 | import Data.Ord | 25 | import Data.Ord |
26 | import Data.Typeable | ||
24 | import Data.Serialize as S | 27 | import Data.Serialize as S |
25 | import Data.Word | 28 | import Data.Word |
26 | import Network | 29 | import Network |
@@ -37,11 +40,15 @@ import Network.BitTorrent.Core.PeerAddr () | |||
37 | -- | Normally, /this/ node id should we saved between invocations of | 40 | -- | Normally, /this/ node id should we saved between invocations of |
38 | -- the client software. | 41 | -- the client software. |
39 | newtype NodeId = NodeId ByteString | 42 | newtype NodeId = NodeId ByteString |
40 | deriving (Show, Eq, Ord, BEncode, FromJSON, ToJSON) | 43 | deriving (Show, Eq, Ord, BEncode, FromJSON, ToJSON, Typeable) |
41 | 44 | ||
42 | nodeIdSize :: Int | 45 | nodeIdSize :: Int |
43 | nodeIdSize = 20 | 46 | nodeIdSize = 20 |
44 | 47 | ||
48 | -- | Meaningless node id, for testing purposes only. | ||
49 | instance Default NodeId where | ||
50 | def = NodeId (BS.replicate nodeIdSize 0) | ||
51 | |||
45 | instance Serialize NodeId where | 52 | instance Serialize NodeId where |
46 | get = NodeId <$> getByteString nodeIdSize | 53 | get = NodeId <$> getByteString nodeIdSize |
47 | {-# INLINE get #-} | 54 | {-# INLINE get #-} |
diff --git a/src/Network/BitTorrent/DHT/Message.hs b/src/Network/BitTorrent/DHT/Message.hs new file mode 100644 index 00000000..a2a6484a --- /dev/null +++ b/src/Network/BitTorrent/DHT/Message.hs | |||
@@ -0,0 +1,240 @@ | |||
1 | -- | For more info see: | ||
2 | -- <http://www.bittorrent.org/beps/bep_0005.html#dht-queries> | ||
3 | -- | ||
4 | {-# LANGUAGE DeriveDataTypeable #-} | ||
5 | {-# LANGUAGE FlexibleInstances #-} | ||
6 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
7 | {-# LANGUAGE UndecidableInstances #-} | ||
8 | module Network.BitTorrent.DHT.Message | ||
9 | ( -- * Envelopes | ||
10 | Query (..) | ||
11 | , Response (..) | ||
12 | |||
13 | -- * Queries | ||
14 | -- ** ping | ||
15 | , Ping (..) | ||
16 | |||
17 | -- ** find_node | ||
18 | , FindNode (..) | ||
19 | , NodeFound (..) | ||
20 | |||
21 | -- ** get_peers | ||
22 | , GetPeers (..) | ||
23 | , GotPeers (..) | ||
24 | |||
25 | -- ** announce_peer | ||
26 | , Announce (..) | ||
27 | , Announced (..) | ||
28 | ) where | ||
29 | |||
30 | import Control.Applicative | ||
31 | import Data.BEncode as BE | ||
32 | import Data.BEncode.BDict | ||
33 | import Data.ByteString as BS | ||
34 | import Data.Monoid | ||
35 | import Data.Serialize as S | ||
36 | import Data.Typeable | ||
37 | import Network | ||
38 | import Network.KRPC | ||
39 | |||
40 | import Data.Torrent.InfoHash | ||
41 | import Network.BitTorrent.Core | ||
42 | import Network.KRPC () | ||
43 | |||
44 | {----------------------------------------------------------------------- | ||
45 | -- envelopes | ||
46 | -----------------------------------------------------------------------} | ||
47 | |||
48 | type Token = ByteString | ||
49 | |||
50 | node_id_key :: BKey | ||
51 | node_id_key = "id" | ||
52 | |||
53 | -- | All queries have an "id" key and value containing the node ID of | ||
54 | -- the querying node. | ||
55 | data Query a = Query | ||
56 | { thisNodeId :: NodeId | ||
57 | , queryParams :: a | ||
58 | } | ||
59 | |||
60 | instance BEncode a => BEncode (Query a) where | ||
61 | toBEncode Query {..} = toDict $ | ||
62 | node_id_key .=! thisNodeId .: endDict | ||
63 | <> | ||
64 | dict (toBEncode queryParams) | ||
65 | where | ||
66 | dict (BDict d) = d | ||
67 | dict _ = error "impossible: instance BEncode (Query a)" | ||
68 | |||
69 | fromBEncode v = do | ||
70 | Query <$> fromDict (field (req node_id_key)) v | ||
71 | <*> fromBEncode v | ||
72 | |||
73 | -- | All responses have an "id" key and value containing the node ID | ||
74 | -- of the responding node. | ||
75 | data Response a = Response | ||
76 | { remoteNodeId :: NodeId | ||
77 | , responseVals :: a | ||
78 | } | ||
79 | |||
80 | instance BEncode a => BEncode (Response a) where | ||
81 | toBEncode = toBEncode . toQuery | ||
82 | where | ||
83 | toQuery (Response nid a) = Query nid a | ||
84 | |||
85 | fromBEncode b = fromQuery <$> fromBEncode b | ||
86 | where | ||
87 | fromQuery (Query nid a) = Response nid a | ||
88 | |||
89 | |||
90 | {----------------------------------------------------------------------- | ||
91 | -- ping method | ||
92 | -----------------------------------------------------------------------} | ||
93 | |||
94 | -- | The most basic query is a ping. | ||
95 | data Ping = Ping | ||
96 | deriving Typeable | ||
97 | |||
98 | instance BEncode Ping where | ||
99 | toBEncode Ping = toDict endDict | ||
100 | fromBEncode _ = pure Ping | ||
101 | |||
102 | -- | \"q\" = \"ping\" | ||
103 | instance KRPC (Query Ping) [Ping] where | ||
104 | method = "ping" | ||
105 | |||
106 | {----------------------------------------------------------------------- | ||
107 | -- find_node method | ||
108 | -----------------------------------------------------------------------} | ||
109 | |||
110 | -- | Find node is used to find the contact information for a node | ||
111 | -- given its ID. | ||
112 | newtype FindNode = FindNode NodeId | ||
113 | deriving Typeable | ||
114 | |||
115 | target_key :: BKey | ||
116 | target_key = "target" | ||
117 | |||
118 | instance BEncode FindNode where | ||
119 | toBEncode (FindNode nid) = toDict $ target_key .=! nid .: endDict | ||
120 | fromBEncode = fromDict $ FindNode <$>! target_key | ||
121 | |||
122 | -- | When a node receives a find_node query, it should respond with a | ||
123 | -- the compact node info for the target node or the K (8) closest good | ||
124 | -- nodes in its own routing table. | ||
125 | -- | ||
126 | newtype NodeFound ip = NodeFound [NodeInfo ip] | ||
127 | deriving Typeable | ||
128 | |||
129 | nodes_key :: BKey | ||
130 | nodes_key = "nodes" | ||
131 | |||
132 | binary :: Serialize a => BE.Get BS.ByteString -> BE.Get a | ||
133 | binary m = m >>= either fail return . S.decode | ||
134 | |||
135 | instance (Typeable ip, Serialize ip) => BEncode (NodeFound ip) where | ||
136 | toBEncode (NodeFound ns) = toDict $ | ||
137 | nodes_key .=! S.encode ns | ||
138 | .: endDict | ||
139 | |||
140 | fromBEncode = fromDict $ NodeFound <$> binary (field (req nodes_key)) | ||
141 | |||
142 | -- | \"q\" == \"find_node\" | ||
143 | instance (Serialize ip, Typeable ip) | ||
144 | => KRPC (Query FindNode) (Response (NodeFound ip)) where | ||
145 | method = "find_node" | ||
146 | |||
147 | {----------------------------------------------------------------------- | ||
148 | -- get_peers method | ||
149 | -----------------------------------------------------------------------} | ||
150 | |||
151 | -- | Get peers associated with a torrent infohash. | ||
152 | newtype GetPeers = GetPeers InfoHash | ||
153 | deriving Typeable | ||
154 | |||
155 | info_hash_key :: BKey | ||
156 | info_hash_key = "info_hash" | ||
157 | |||
158 | instance BEncode GetPeers where | ||
159 | toBEncode (GetPeers ih) = toDict $ info_hash_key .=! ih .: endDict | ||
160 | fromBEncode = fromDict $ GetPeers <$>! info_hash_key | ||
161 | |||
162 | data GotPeers ip = GotPeers | ||
163 | { -- | If the queried node has no peers for the infohash, returned | ||
164 | -- the K nodes in the queried nodes routing table closest to the | ||
165 | -- infohash supplied in the query. | ||
166 | peers :: Either [NodeAddr ip] [PeerAddr ip] | ||
167 | |||
168 | -- | The token value is a required argument for a future | ||
169 | -- announce_peer query. | ||
170 | , grantedToken :: Token | ||
171 | } deriving Typeable | ||
172 | |||
173 | peers_key :: BKey | ||
174 | peers_key = "peers" | ||
175 | |||
176 | token_key :: BKey | ||
177 | token_key = "token" | ||
178 | |||
179 | instance (Typeable ip, Serialize ip) => BEncode (GotPeers ip) where | ||
180 | toBEncode GotPeers {..} = toDict $ | ||
181 | putPeerList peers | ||
182 | .: token_key .=! grantedToken | ||
183 | .: endDict | ||
184 | where | ||
185 | putPeerList (Right ps) = peers_key .=! S.encode ps | ||
186 | putPeerList (Left ns) = nodes_key .=! S.encode ns | ||
187 | |||
188 | fromBEncode = fromDict $ GotPeers <$> getPeerList <*>! token_key | ||
189 | where | ||
190 | getPeerList = Right <$> binary (field (req peers_key)) | ||
191 | <|> Left <$> binary (field (req nodes_key)) | ||
192 | |||
193 | instance (Typeable ip, Serialize ip) => | ||
194 | KRPC (Query GetPeers) (Response (GotPeers ip)) where | ||
195 | method = "get_peers" | ||
196 | |||
197 | {----------------------------------------------------------------------- | ||
198 | -- announce method | ||
199 | -----------------------------------------------------------------------} | ||
200 | |||
201 | -- | Announce that the peer, controlling the querying node, is | ||
202 | -- downloading a torrent on a port. | ||
203 | data Announce = Announce | ||
204 | { -- | infohash of the torrent; | ||
205 | topic :: InfoHash | ||
206 | |||
207 | -- | the port /this/ peer is listenning; | ||
208 | , port :: PortNumber | ||
209 | |||
210 | -- | received in response to a previous get_peers query. | ||
211 | , sessionToken :: Token | ||
212 | } deriving Typeable | ||
213 | |||
214 | port_key :: BKey | ||
215 | port_key = "port" | ||
216 | |||
217 | instance BEncode Announce where | ||
218 | toBEncode Announce {..} = toDict $ | ||
219 | info_hash_key .=! topic | ||
220 | .: port_key .=! port | ||
221 | .: token_key .=! sessionToken | ||
222 | .: endDict | ||
223 | fromBEncode = fromDict $ do | ||
224 | Announce <$>! info_hash_key | ||
225 | <*>! port_key | ||
226 | <*>! token_key | ||
227 | |||
228 | -- | The queried node must verify that the token was previously sent | ||
229 | -- to the same IP address as the querying node. Then the queried node | ||
230 | -- should store the IP address of the querying node and the supplied | ||
231 | -- port number under the infohash in its store of peer contact | ||
232 | -- information. | ||
233 | data Announced = Announced | ||
234 | |||
235 | instance BEncode Announced where | ||
236 | toBEncode _ = toBEncode Ping | ||
237 | fromBEncode _ = pure Announced | ||
238 | |||
239 | instance KRPC (Query Announce) (Response Announced) where | ||
240 | method = "announce_peer" \ No newline at end of file | ||