summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/DHT/Message.hs
blob: 706d181a7cfb853755af832bd1ac61ba888f65c7 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
-- |
--   Copyright   :  (c) Sam Truzjan 2013
--   License     :  BSD3
--   Maintainer  :  pxqr.sta@gmail.com
--   Stability   :  experimental
--   Portability :  portable
--
--   This module provides message datatypes which is used for /Node to
--   Node/ communication. Bittorrent DHT is based on Kademlia
--   specification, but have a slightly different set of messages
--   which have been adopted for /peer/ discovery mechanism. Messages
--   are sent over "Network.KRPC" protocol, but normally you should
--   use "Network.BitTorrent.DHT.Session" to send and receive
--   messages.
--
--   DHT queries are not /recursive/, they are /iterative/. This means
--   that /querying/ node . While original specification (namely BEP5)
--   do not impose any restrictions for /quered/ node behaviour, a
--   good DHT implementation should follow some rules to guarantee
--   that unlimit recursion will never happen. The following set of
--   restrictions:
--
--     * 'Ping' query must not trigger any message.
--
--     * 'FindNode' query /may/ trigger 'Ping' query to check if a
--     list of nodes to return is /good/. See
--     'Network.BitTorrent.DHT.Routing.Routing' for further explanation.
--
--     * 'GetPeers' query may trigger 'Ping' query for the same reason.
--
--     * 'Announce' query must trigger 'Ping' query for the same reason.
--
--   It is easy to see that the most long RPC chain is:
--
--   @
--     |                                            |                |
--   Node_A                                         |                |
--     |   FindNode or GetPeers or Announce         |                |
--     |  ------------------------------------>   Node_B             |
--     |                                            |      Ping      |
--     |                                            |  ----------->  |
--     |                                            |              Node_C
--     |                                            |      Pong      |
--     |     NodeFound or GotPeers or Announced     |  <-----------  |
--     |  <-------------------------------------  Node_B             |
--   Node_A                                         |                |
--     |                                            |                |
--   @
--
--   where in some cases 'Node_C' is 'Node_A'.
--
--   For more info see:
--   <http://www.bittorrent.org/beps/bep_0005.html#dht-queries>
--
--   For Kamelia messages see original Kademlia paper:
--   <http://pdos.csail.mit.edu/~petar/papers/maymounkov-kademlia-lncs.pdf>
--
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances  #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies #-}
module Network.BitTorrent.DHT.Message
       ( -- * Envelopes
         Query (..)
       , Response (..)

         -- * Queries
         -- ** ping
       , Ping (..)

         -- ** find_node
       , FindNode (..)
       , NodeFound (..)


#ifdef VERSION_bencoding
         -- ** get_peers
       , PeerList
       , GetPeers (..)
       , GotPeers (..)

         -- ** announce_peer
       , Announce  (..)
       , Announced (..)
#endif
       ) where

import Control.Applicative
import Data.Bool
#ifdef VERSION_bencoding
import Data.BEncode as BE
import Data.BEncode.BDict as BDict
#else
import qualified Data.Tox as Tox
import Data.Tox (NodeId)
import Data.Word
import Control.Monad
import Network.KRPC.Method
#endif
import Network.BitTorrent.Address hiding (NodeId)
import Data.ByteString (ByteString)
import Data.List as L
import Data.Monoid
import Data.Serialize as S
import Data.Typeable
import Network
import Network.DatagramServer
import Network.KRPC.Message (KMessageOf)
import Data.Maybe

import Data.Torrent (InfoHash)
import Network.BitTorrent.DHT.Token
#ifdef VERSION_bencoding
import Network.DatagramServer ()
import Network.DHT.Mainline ()
#endif
import Network.RPC hiding (Query,Response)

{-----------------------------------------------------------------------
-- envelopes
-----------------------------------------------------------------------}

#ifndef VERSION_bencoding
type BKey = ByteString
#endif

node_id_key :: BKey
node_id_key = "id"

read_only_key :: BKey
read_only_key = "ro"


#ifdef VERSION_bencoding
-- | All queries have an \"id\" key and value containing the node ID
-- of the querying node.
data Query a = Query
  { queringNodeId   :: NodeId KMessageOf -- ^ node id of /quering/ node;
  , queryIsReadOnly :: Bool   -- ^ node is read-only as per BEP 43
  , queryParams     :: a      -- ^ query parameters.
  } deriving (Show, Eq, Typeable)

instance BEncode a => BEncode (Query a) where
  toBEncode Query {..} = toDict $
      BDict.union ( node_id_key .=! queringNodeId
                   .: read_only_key .=? bool Nothing (Just (1 :: Integer)) queryIsReadOnly
                   .: endDict)
                  (dict (toBEncode queryParams))
    where
      dict (BDict d) = d
      dict    _      = error "impossible: instance BEncode (Query a)"

  fromBEncode v = do
    Query <$> fromDict (field (req node_id_key)) v
          <*> fromDict (fromMaybe False <$>? read_only_key) v
          <*> fromBEncode v
#else
data Query a = Query a
#endif

#ifdef VERSION_bencoding
-- | All responses have an \"id\" key and value containing the node ID
-- of the responding node.
data Response a = Response
  { queredNodeId :: NodeId KMessageOf -- ^ node id of /quered/ node;
  , responseVals :: a      -- ^ query result.
  } deriving (Show, Eq, Typeable)

instance BEncode a => BEncode (Response a) where
  toBEncode = toBEncode . toQuery
    where
      toQuery (Response nid a) = Query nid False a

  fromBEncode b = fromQuery <$> fromBEncode b
    where
      fromQuery (Query nid _ a) = Response nid a
#else
data Response a = Response a
#endif

{-----------------------------------------------------------------------
-- ping method
-----------------------------------------------------------------------}

-- | The most basic query is a ping. Ping query is used to check if a
-- quered node is still alive.
#ifdef VERSION_bencoding
data Ping = Ping
#else
data Ping = Ping Tox.Nonce8
#endif
  deriving (Show, Eq, Typeable)

#ifdef VERSION_bencoding
instance BEncode Ping where
  toBEncode Ping = toDict endDict
  fromBEncode _  = pure Ping
#else
instance Serialize (Query Ping) where
    get = do
        b <- get
        when ( (b::Word8) /= 0) $ fail "Bad ping request"
        nonce <- get
        return $ Query (Ping nonce)
    put (Query (Ping nonce)) = do
        put (0 :: Word8)
        put nonce
instance Serialize (Response Ping) where
    get = do
        b <- get
        when ( (b::Word8) /= 1) $ fail "Bad ping response"
        nonce <- get
        return $ Response (Ping nonce)
    put (Response (Ping nonce)) = do
        put (1 :: Word8)
        put nonce
#endif

-- | \"q\" = \"ping\"
instance KRPC (Query Ping) (Response Ping) where
#ifdef VERSION_bencoding
  type Envelope (Query Ping) (Response Ping) = BValue
  seal = toBEncode
  unseal = fromBEncode
  method = "ping"
#else
  method = Method Tox.Ping -- response: Tox.Pong
#endif

{-----------------------------------------------------------------------
-- find_node method
-----------------------------------------------------------------------}

-- | Find node is used to find the contact information for a node
-- given its ID.
#ifdef VERSION_bencoding
newtype FindNode ip = FindNode (NodeId KMessageOf)
#else
data FindNode ip = FindNode (NodeId Tox.Message) Tox.Nonce8 -- Tox: Get Nodes
#endif
  deriving (Show, Eq, Typeable)

target_key :: BKey
target_key = "target"

#ifdef VERSION_bencoding
instance Typeable ip => BEncode (FindNode ip) where
  toBEncode (FindNode nid) = toDict   $ target_key .=! nid .: endDict
  fromBEncode              = fromDict $ FindNode  <$>! target_key
#else
instance Serialize (Query (FindNode ip)) where
    get = do
        nid <- get
        nonce <- get
        return $ Query (FindNode nid nonce)
    put (Query (FindNode nid nonce)) = do
        put nid
        put nonce
#endif

-- | When a node receives a 'FindNode' query, it should respond with a
-- the compact node info for the target node or the K (8) closest good
-- nodes in its own routing table.
--
#ifdef VERSION_bencoding
newtype NodeFound ip = NodeFound [NodeInfo KMessageOf ip ()]
#else
data NodeFound ip = NodeFound [Tox.NodeFormat] Tox.Nonce8
#endif
-- Tox: send_nodes
  deriving (Show, Eq, Typeable)

nodes_key :: BKey
nodes_key = "nodes"

-- Convert IPv4 address.  Useful for using variadic IP type.
from4 :: forall dht u s. Address s => NodeInfo dht IPv4 u -> Either String (NodeInfo dht s u)
from4 n = maybe (Left "Error converting IPv4") Right
                    $ traverseAddress (fromAddr :: IPv4 -> Maybe s) n

#ifdef VERSION_bencoding
binary :: Serialize a => BKey -> BE.Get [a]
binary k = field (req k) >>= either (fail . format) return .
    runGet (many get)
  where
    format str = "fail to deserialize " ++ show k ++ " field: " ++ str

instance Address ip => BEncode (NodeFound ip) where
  toBEncode (NodeFound ns) = toDict $
       nodes_key .=! runPut (mapM_ put ns)
    .: endDict

  -- TODO: handle IPv6 by reading the "nodes6" key (see bep 32)
  fromBEncode bval = NodeFound <$> (traverse from4 =<< fromDict (binary nodes_key) bval)
#else
instance Serialize (Response (NodeFound ip)) where
    get = do
        count <- get :: Get Word8
        nodes <- sequence $ replicate (fromIntegral count) get
        nonce <- get :: Get Tox.Nonce8
        return $ Response $ NodeFound nodes nonce

    put (Response (NodeFound nodes nonce)) = do
        put (fromIntegral (length nodes) :: Word8)
        mapM_ put nodes
        put nonce

#endif

-- | \"q\" == \"find_node\"
instance (Address ip, Typeable ip)
      => KRPC (Query (FindNode ip)) (Response (NodeFound ip)) where
#ifdef VERSION_bencoding
  type Envelope (Query (FindNode ip)) (Response (NodeFound ip)) = BValue
  seal = toBEncode
  unseal = fromBEncode
  method = "find_node"
#else
  method = Method Tox.GetNodes -- response: Tox.SendNodes
#endif

#ifdef VERSION_bencoding
{-----------------------------------------------------------------------
-- get_peers method
-----------------------------------------------------------------------}

-- | Get peers associated with a torrent infohash.
newtype GetPeers ip = GetPeers InfoHash
  deriving (Show, Eq, Typeable)

info_hash_key :: BKey
info_hash_key = "info_hash"

instance Typeable ip => BEncode (GetPeers ip) where
  toBEncode (GetPeers ih) = toDict   $ info_hash_key .=! ih .: endDict
  fromBEncode             = fromDict $ GetPeers <$>! info_hash_key

type PeerList ip = Either [NodeInfo KMessageOf ip ()] [PeerAddr ip]

data GotPeers ip = GotPeers
  { -- | If the queried node has no peers for the infohash, returned
    -- the K nodes in the queried nodes routing table closest to the
    -- infohash supplied in the query.
    peers        :: PeerList ip

    -- | The token value is a required argument for a future
    -- announce_peer query.
  , grantedToken :: Token
  } deriving (Show, Eq, Typeable)

peers_key :: BKey
peers_key = "values"

token_key :: BKey
token_key = "token"

name_key :: BKey
name_key = "name"

instance (Typeable ip, Serialize ip) => BEncode (GotPeers ip) where
  toBEncode GotPeers {..} = toDict $
    case peers of
      Left  ns ->
           nodes_key .=! runPut (mapM_ put ns)
        .: token_key .=! grantedToken
        .: endDict
      Right ps ->
           token_key .=! grantedToken
        .: peers_key .=! L.map S.encode ps
        .: endDict

  fromBEncode = fromDict $ do
     mns <- optional (binary nodes_key)                      -- "nodes"
     tok <- field    (req    token_key)                      -- "token"
     mps <- optional (field (req peers_key) >>= decodePeers) -- "values"
     case (Right <$> mps) <|> (Left <$> mns) of
       Nothing -> fail "get_peers: neihter peers nor nodes key is valid"
       Just xs -> pure $ GotPeers xs tok
     where
       decodePeers = either fail pure . mapM S.decode

-- | \"q" = \"get_peers\"
instance (Typeable ip, Serialize ip) =>
         KRPC (Query (GetPeers ip)) (Response (GotPeers ip)) where
  type Envelope (Query (GetPeers ip)) (Response (GotPeers ip)) = BValue
  seal = toBEncode
  unseal = fromBEncode
  method = "get_peers"

{-----------------------------------------------------------------------
-- announce method
-----------------------------------------------------------------------}

-- | Announce that the peer, controlling the querying node, is
-- downloading a torrent on a port.
data Announce = Announce
  { -- | If set, the 'port' field should be ignored and the source
    -- port of the UDP packet should be used as the peer's port
    -- instead. This is useful for peers behind a NAT that may not
    -- know their external port, and supporting uTP, they accept
    -- incoming connections on the same port as the DHT port.
    impliedPort :: Bool

    -- | infohash of the torrent;
  , topic    :: InfoHash

    -- | some clients announce the friendly name of the torrent here.
  , announcedName :: Maybe ByteString

    -- | the port /this/ peer is listening;
  , port     :: PortNumber

    -- TODO: optional boolean "seed" key

    -- | received in response to a previous get_peers query.
  , sessionToken :: Token

  } deriving (Show, Eq, Typeable)

port_key :: BKey
port_key = "port"

implied_port_key :: BKey
implied_port_key = "implied_port"

instance BEncode Announce where
  toBEncode Announce {..} = toDict $
       implied_port_key .=? flagField impliedPort
    .: info_hash_key    .=! topic
    .: name_key         .=? announcedName
    .: port_key         .=! port
    .: token_key        .=! sessionToken
    .: endDict
    where
      flagField flag = if flag then Just (1 :: Int) else Nothing

  fromBEncode = fromDict $ do
    Announce <$> (boolField <$> optional (field (req implied_port_key)))
             <*>! info_hash_key
             <*>? name_key
             <*>! port_key
             <*>! token_key
    where
      boolField = maybe False (/= (0 :: Int))

-- | The queried node must verify that the token was previously sent
-- to the same IP address as the querying node. Then the queried node
-- should store the IP address of the querying node and the supplied
-- port number under the infohash in its store of peer contact
-- information.
data Announced = Announced
  deriving (Show, Eq, Typeable)

instance BEncode Announced where
  toBEncode   _ = toBEncode Ping
  fromBEncode _ = pure  Announced

-- | \"q" = \"announce\"
instance KRPC (Query Announce) (Response Announced) where
  type Envelope (Query Announce) (Response Announced) = BValue
  seal = toBEncode
  unseal = fromBEncode
  method = "announce_peer"

-- endif VERSION_bencoding
#endif