diff options
Diffstat (limited to 'src/Network/BitTorrent/DHT/Protocol.hs')
-rw-r--r-- | src/Network/BitTorrent/DHT/Protocol.hs | 329 |
1 files changed, 0 insertions, 329 deletions
diff --git a/src/Network/BitTorrent/DHT/Protocol.hs b/src/Network/BitTorrent/DHT/Protocol.hs deleted file mode 100644 index 8528f0e0..00000000 --- a/src/Network/BitTorrent/DHT/Protocol.hs +++ /dev/null | |||
@@ -1,329 +0,0 @@ | |||
1 | module Network.BitTorrent.DHT.Protocol | ||
2 | ( | ||
3 | newNodeSession | ||
4 | |||
5 | -- * Tracker | ||
6 | , ping | ||
7 | , findNode | ||
8 | , getPeers | ||
9 | , announcePeer | ||
10 | |||
11 | -- * Server | ||
12 | , dhtServer | ||
13 | ) where | ||
14 | |||
15 | import Control.Applicative | ||
16 | import Control.Concurrent | ||
17 | import Control.Concurrent.STM | ||
18 | import Control.Monad | ||
19 | import Control.Exception | ||
20 | import Data.ByteString | ||
21 | import Data.Serialize as S | ||
22 | import Data.Function | ||
23 | import Data.Ord | ||
24 | import Data.Maybe | ||
25 | import Data.List as L | ||
26 | import Data.Map as M | ||
27 | import Data.HashMap.Strict as HM | ||
28 | import Network | ||
29 | import Network.Socket | ||
30 | import System.Entropy | ||
31 | |||
32 | import Data.BEncode | ||
33 | import Network.KRPC | ||
34 | import Network.KRPC.Protocol | ||
35 | import Network.BitTorrent.Peer | ||
36 | import Network.BitTorrent.Exchange.Protocol () | ||
37 | |||
38 | {----------------------------------------------------------------------- | ||
39 | Node | ||
40 | -----------------------------------------------------------------------} | ||
41 | |||
42 | type NodeId = ByteString | ||
43 | |||
44 | -- TODO WARN is the 'system' random suitable for this? | ||
45 | -- | Generate random NodeID used for the entire session. | ||
46 | -- Distribution of ID's should be as uniform as possible. | ||
47 | -- | ||
48 | genNodeId :: IO NodeId | ||
49 | genNodeId = getEntropy 20 | ||
50 | |||
51 | data NodeAddr = NodeAddr { | ||
52 | nodeIP :: {-# UNPACK #-} !HostAddress | ||
53 | , nodePort :: {-# UNPACK #-} !PortNumber | ||
54 | } deriving (Show, Eq) | ||
55 | |||
56 | instance Serialize NodeAddr where | ||
57 | get = NodeAddr <$> getWord32be <*> get | ||
58 | put NodeAddr {..} = putWord32be nodeIP >> put nodePort | ||
59 | |||
60 | data NodeInfo = NodeInfo { | ||
61 | nodeID :: !NodeId | ||
62 | , nodeAddr :: !NodeAddr | ||
63 | } deriving (Show, Eq) | ||
64 | |||
65 | instance Serialize NodeInfo where | ||
66 | get = NodeInfo <$> getByteString 20 <*> get | ||
67 | put NodeInfo {..} = put nodeID >> put nodeAddr | ||
68 | |||
69 | type CompactInfo = ByteString | ||
70 | |||
71 | decodeCompact :: CompactInfo -> [NodeInfo] | ||
72 | decodeCompact = either (const []) id . S.runGet (many get) | ||
73 | |||
74 | encodeCompact :: [NodeId] -> CompactInfo | ||
75 | encodeCompact = S.runPut . mapM_ put | ||
76 | |||
77 | decodePeerList :: [BEncode] -> [PeerAddr] | ||
78 | decodePeerList = undefined | ||
79 | |||
80 | encodePeerList :: [PeerAddr] -> [BEncode] | ||
81 | encodePeerList = undefined | ||
82 | |||
83 | type Distance = NodeId | ||
84 | |||
85 | {----------------------------------------------------------------------- | ||
86 | Tokens | ||
87 | -----------------------------------------------------------------------} | ||
88 | |||
89 | type Secret = Int | ||
90 | |||
91 | genSecret :: IO Secret | ||
92 | genSecret = error "secret" | ||
93 | |||
94 | -- | Instead of periodically loop over the all nodes in the routing | ||
95 | -- table with some given interval (or some other tricky method | ||
96 | -- e.g. using timeouts) we can just update tokens on demand - if no | ||
97 | -- one asks for a token then the token _should_ not change at all. | ||
98 | -- | ||
99 | type Token = ByteString | ||
100 | |||
101 | defaultToken :: Token | ||
102 | defaultToken = "0xdeadbeef" | ||
103 | |||
104 | genToken :: NodeAddr -> Secret -> Token | ||
105 | genToken _ _ = defaultToken | ||
106 | |||
107 | {----------------------------------------------------------------------- | ||
108 | Routing table | ||
109 | -----------------------------------------------------------------------} | ||
110 | |||
111 | type ContactInfo = HashMap InfoHash [PeerAddr] | ||
112 | |||
113 | insertPeer :: InfoHash -> PeerAddr -> ContactInfo -> ContactInfo | ||
114 | insertPeer ih addr = HM.insertWith (++) ih [addr] | ||
115 | |||
116 | lookupPeers :: InfoHash -> ContactInfo -> [PeerAddr] | ||
117 | lookupPeers ih = fromMaybe [] . HM.lookup ih | ||
118 | |||
119 | -- TODO use more compact routing table | ||
120 | type RoutingTable = HashMap NodeId NodeAddr | ||
121 | |||
122 | insertNode :: NodeId -> NodeAddr -> RoutingTable -> RoutingTable | ||
123 | insertNode = HM.insert | ||
124 | |||
125 | type Alpha = Int | ||
126 | |||
127 | defaultAlpha :: Alpha | ||
128 | defaultAlpha = 8 | ||
129 | |||
130 | -- TODO | ||
131 | kclosest :: Int -> NodeId -> RoutingTable -> [NodeId] | ||
132 | kclosest = undefined | ||
133 | |||
134 | {----------------------------------------------------------------------- | ||
135 | Node session | ||
136 | -----------------------------------------------------------------------} | ||
137 | |||
138 | data NodeSession = NodeSession { | ||
139 | nodeId :: !NodeId | ||
140 | , routingTable :: !(TVar RoutingTable) | ||
141 | , contactInfo :: !(TVar ContactInfo) | ||
142 | -- , currentSecret :: !(TVar Secret) | ||
143 | -- , secretTimestamp :: !(TVar Timestamp) | ||
144 | , alpha :: !Alpha | ||
145 | , listenerPort :: !PortNumber | ||
146 | } | ||
147 | |||
148 | instance Eq NodeSession where | ||
149 | (==) = (==) `on` nodeId | ||
150 | |||
151 | instance Ord NodeSession where | ||
152 | compare = comparing nodeId | ||
153 | |||
154 | newNodeSession :: PortNumber -> IO NodeSession | ||
155 | newNodeSession lport | ||
156 | = NodeSession | ||
157 | <$> genNodeId | ||
158 | <*> newTVarIO HM.empty | ||
159 | <*> newTVarIO HM.empty | ||
160 | <*> pure defaultAlpha | ||
161 | <*> pure lport | ||
162 | |||
163 | assignToken :: NodeSession -> NodeId -> IO Token | ||
164 | assignToken _ _ = return "" | ||
165 | |||
166 | -- TODO | ||
167 | checkToken :: NodeId -> Token -> NodeSession -> IO Bool | ||
168 | checkToken _ _ _ = return True | ||
169 | |||
170 | updateTimestamp :: NodeSession -> NodeId -> IO () | ||
171 | updateTimestamp = error "updateTimestamp" | ||
172 | |||
173 | updateToken :: NodeSession -> NodeId -> Token -> IO () | ||
174 | updateToken _ _ _ = error "updateToken" | ||
175 | |||
176 | {----------------------------------------------------------------------- | ||
177 | DHT Queries | ||
178 | -----------------------------------------------------------------------} | ||
179 | |||
180 | pingM :: Method NodeId NodeId | ||
181 | pingM = method "ping" ["id"] ["id"] | ||
182 | |||
183 | findNodeM :: Method (NodeId, NodeId) (NodeId, CompactInfo) | ||
184 | findNodeM = method "find_node" ["id", "target"] ["id", "nodes"] | ||
185 | |||
186 | -- | Lookup peers by a torrent infohash. This method might return | ||
187 | -- different kind of responses depending on the routing table of | ||
188 | -- queried node: | ||
189 | -- | ||
190 | -- * If quieried node contains a peer list for the given infohash | ||
191 | -- then the node should return the list in a "value" key. Note that | ||
192 | -- list is encoded as compact peer address, not a compact node info. | ||
193 | -- The result of 'get_peers' method have the following scheme: | ||
194 | -- | ||
195 | -- > { "id" : "dht_server_node_id" | ||
196 | -- > , "token" : "assigned_token" | ||
197 | -- > , "values" : ["_IP_PO", "_ip_po"] | ||
198 | -- > } | ||
199 | -- | ||
200 | -- * If quieried node does not contain a list of peers associated | ||
201 | -- with the given infohash, then node should return | ||
202 | -- | ||
203 | -- > { "id" : "dht_server_node_id" | ||
204 | -- > , "token" : "assigned_token" | ||
205 | -- > , "nodes" : "compact_nodes_info" | ||
206 | -- > } | ||
207 | -- | ||
208 | -- The resulting dictionaries might differ only in a values\/nodes | ||
209 | -- keys. | ||
210 | -- | ||
211 | getPeersM :: Method (NodeId, InfoHash) BEncode | ||
212 | getPeersM = method "get_peers" ["id", "info_hash"] [] | ||
213 | |||
214 | -- | Used to announce that the peer, controlling the quering node is | ||
215 | -- downloading a torrent on a port. | ||
216 | announcePeerM :: Method (NodeId, InfoHash, PortNumber, Token) NodeId | ||
217 | announcePeerM = method "announce_peer" ["id", "info_hash", "port", "token"] ["id"] | ||
218 | |||
219 | {----------------------------------------------------------------------- | ||
220 | DHT Tracker | ||
221 | -----------------------------------------------------------------------} | ||
222 | -- TODO: update node timestamp on each successful call | ||
223 | |||
224 | -- | Note that tracker side query functions could throw RPCException. | ||
225 | type DHT a b = NodeSession -> NodeAddr -> a -> IO b | ||
226 | |||
227 | ping :: DHT () () | ||
228 | ping NodeSession {..} addr @ NodeAddr {..} () = do | ||
229 | nid <- call (nodeIP, nodePort) pingM nodeId | ||
230 | atomically $ modifyTVar' routingTable $ HM.insert nid addr | ||
231 | |||
232 | findNode :: DHT NodeId [NodeInfo] | ||
233 | findNode ses @ NodeSession {..} NodeAddr {..} qnid = do | ||
234 | (nid, info) <- call (nodeIP, nodePort) findNodeM (nodeId, qnid) | ||
235 | updateTimestamp ses nid | ||
236 | return (decodeCompact info) | ||
237 | |||
238 | getPeers :: DHT InfoHash (Either [NodeInfo] [PeerAddr]) | ||
239 | getPeers ses @ NodeSession {..} NodeAddr {..} ih = do | ||
240 | resp <- call (nodeIP, nodePort) getPeersM (nodeId, ih) | ||
241 | (nid, tok, res) <- extrResp resp | ||
242 | updateTimestamp ses nid | ||
243 | updateToken ses nid tok | ||
244 | return res | ||
245 | where | ||
246 | extrResp (BDict d) | ||
247 | | Just (BString nid ) <- M.lookup "id" d | ||
248 | , Just (BString tok ) <- M.lookup "token" d | ||
249 | , Just (BList values) <- M.lookup "values" d | ||
250 | = return $ (nid, tok, Right $ decodePeerList values) | ||
251 | |||
252 | | Just (BString nid ) <- M.lookup "id" d | ||
253 | , Just (BString tok ) <- M.lookup "token" d | ||
254 | , Just (BString nodes) <- M.lookup "nodes" d | ||
255 | = return (nid, tok, Left $ decodeCompact nodes) | ||
256 | |||
257 | extrResp _ = throw $ RPCException msg | ||
258 | where msg = ProtocolError "unable to extract getPeers resp" | ||
259 | |||
260 | -- remove token from signature, handle the all token stuff by NodeSession | ||
261 | |||
262 | -- | Note that before ever calling this method you should call the | ||
263 | -- getPeerList. | ||
264 | announcePeer :: DHT (InfoHash, Token) NodeId | ||
265 | announcePeer ses @ NodeSession {..} NodeAddr {..} (ih, tok) = do | ||
266 | nid <- call (nodeIP, nodePort) announcePeerM (nodeId, ih, listenerPort, tok) | ||
267 | updateTimestamp ses nid | ||
268 | return nid | ||
269 | |||
270 | {----------------------------------------------------------------------- | ||
271 | DHT Server | ||
272 | -----------------------------------------------------------------------} | ||
273 | -- TODO: update node timestamp on each successful call | ||
274 | -- NOTE: ensure all server operations run in O(1) | ||
275 | |||
276 | type ServerHandler a b = NodeSession -> NodeAddr -> a -> IO b | ||
277 | |||
278 | pingS :: ServerHandler NodeId NodeId | ||
279 | pingS NodeSession {..} addr nid = do | ||
280 | atomically $ modifyTVar' routingTable $ insertNode nid addr | ||
281 | return nodeId | ||
282 | |||
283 | findNodeS :: ServerHandler (NodeId, NodeId) (NodeId, CompactInfo) | ||
284 | findNodeS ses @ NodeSession {..} _ (nid, qnid) = do | ||
285 | updateTimestamp ses nid | ||
286 | rt <- atomically $ readTVar routingTable | ||
287 | return (nodeId, encodeCompact $ kclosest alpha qnid rt) | ||
288 | |||
289 | getPeersS :: ServerHandler (NodeId, InfoHash) BEncode | ||
290 | getPeersS ses @ NodeSession {..} _ (nid, ih) = do | ||
291 | updateTimestamp ses nid | ||
292 | mkResp <$> assignToken ses nid <*> findPeers | ||
293 | where | ||
294 | findPeers = do | ||
295 | list <- lookupPeers ih <$> readTVarIO contactInfo | ||
296 | if not (L.null list) | ||
297 | then return $ Right list | ||
298 | else do | ||
299 | rt <- readTVarIO routingTable | ||
300 | let nodes = kclosest alpha (getInfoHash ih) rt | ||
301 | return $ Left nodes | ||
302 | |||
303 | mkDict tok res = [("id",BString nodeId), ("token", BString tok), res] | ||
304 | mkResult (Left nodes ) = ("nodes", BString $ encodeCompact nodes) | ||
305 | mkResult (Right values) = ("values", BList $ encodePeerList values) | ||
306 | mkResp tok = BDict . M.fromList . mkDict tok . mkResult | ||
307 | |||
308 | announcePeerS :: ServerHandler (NodeId, InfoHash, PortNumber, Token) NodeId | ||
309 | announcePeerS ses @ NodeSession {..} NodeAddr {..} (nid, ih, port, token) = do | ||
310 | updateTimestamp ses nid | ||
311 | registered <- checkToken nid token ses | ||
312 | when registered $ do | ||
313 | atomically $ do | ||
314 | let peerAddr = PeerAddr Nothing nodeIP port | ||
315 | modifyTVar contactInfo $ insertPeer ih peerAddr | ||
316 | return nodeId | ||
317 | |||
318 | dhtTracker :: NodeSession -> InfoHash -> Chan PeerAddr -> IO () | ||
319 | dhtTracker = undefined | ||
320 | |||
321 | dhtServer :: NodeSession -> PortNumber -> IO () | ||
322 | dhtServer s p = server p methods | ||
323 | where | ||
324 | methods = | ||
325 | [ pingM ==> pingS s undefined | ||
326 | , findNodeM ==> findNodeS s undefined | ||
327 | , getPeersM ==> getPeersS s undefined | ||
328 | , announcePeerM ==> announcePeerS s undefined | ||
329 | ] \ No newline at end of file | ||