summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/DHT.hs
blob: a098d339d408589a9c3c46ee3069d6e53c5a12e3 (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
-- |
--   Copyright   :  (c) Sam Truzjan 2013
--   License     :  BSD3
--   Maintainer  :  pxqr.sta@gmail.com
--   Stability   :  experimental
--   Portability :  portable
--
--   BitTorrent uses a \"distributed sloppy hash table\" (DHT) for
--   storing peer contact information for \"trackerless\" torrents. In
--   effect, each peer becomes a tracker.
--
--   Normally you don't need to import other DHT modules.
--
--   For more info see:
--   <http://www.bittorrent.org/beps/bep_0005.html>
--
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TemplateHaskell   #-}
module Network.BitTorrent.DHT
       ( -- * Distributed Hash Table
         DHT
       , dht
       , Network.BitTorrent.DHT.bootstrap
       , Network.BitTorrent.DHT.lookup
       , Network.BitTorrent.DHT.insert
       , Network.BitTorrent.DHT.delete
       ) where

import Control.Applicative
import Control.Concurrent.Lifted hiding (yield)
import Control.Exception.Lifted
import Control.Monad
import Control.Monad.Logger
import Data.List as L
import Data.Monoid
import Data.Text as T
import Network.Socket (PortNumber)
import Text.PrettyPrint as PP hiding ((<>))
import Text.PrettyPrint.Class

import Data.Torrent.InfoHash
import Network.BitTorrent.Core
import Network.BitTorrent.DHT.Message
import Network.BitTorrent.DHT.Session
import Network.KRPC


{-----------------------------------------------------------------------
--  Handlers
-----------------------------------------------------------------------}

pingH :: Address ip => NodeHandler ip
pingH = nodeHandler $ \ _ Ping -> do
  $(logDebug) "ping received, sending pong"
  return Ping

findNodeH :: Address ip => NodeHandler ip
findNodeH = nodeHandler $ \ _ (FindNode nid) -> do
  $(logDebug) "find_node received, sending closest nodes back"
  NodeFound <$> getClosest nid

getPeersH :: Address ip => NodeHandler ip
getPeersH = nodeHandler $ \ naddr (GetPeers ih) -> do
  $(logDebug) "get_peers received, trying to find peers"
  GotPeers <$> getPeerList ih <*> grantToken naddr

announceH :: Address ip => NodeHandler ip
announceH = nodeHandler $ \ naddr (Announce {..}) -> do
  $(logDebug) "announce received, trying to check token"
  checkToken naddr sessionToken
  case fromAddr naddr of
    Nothing    -> throw $ KError ProtocolError "bad address" ""
    Just paddr -> do
      insertPeer topic paddr
      return Announced

handlers :: Address ip => [NodeHandler ip]
handlers = [pingH, findNodeH, getPeersH, announceH]

{-----------------------------------------------------------------------
--  Query
-----------------------------------------------------------------------}

-- | Run DHT on specified port. <add note about resources>
dht :: Address ip
    => Options     -- ^ normally you need to use 'Data.Default.def';
    -> NodeAddr ip -- ^ address to bind this node;
    -> DHT ip a    -- ^ actions to run: 'bootstrap', 'lookup', etc;
    -> IO a        -- ^ result.
dht = runDHT handlers
{-# INLINE dht #-}

-- | One good node may be sufficient. The list of bootstrapping nodes
-- usually obtained from 'Data.Torrent.tNodes' field. Bootstrapping
-- process can take up to 5 minutes.
--
-- (TODO) This operation is asynchronous and do not block.
--
bootstrap :: Address ip => [NodeAddr ip] -> DHT ip ()
bootstrap startNodes = do
    $(logInfoS) "bootstrap" "Start node bootstrapping"
    mapM_ insertClosest startNodes
    $(logInfoS) "bootstrap" "Node bootstrapping finished"
  where
    insertClosest addr = do
      nid <- getNodeId
      result <- try $ FindNode nid <@> addr
      case result of
        Left                    e -> do
          $(logWarnS) "bootstrap" $ T.pack $ show (e :: IOError)

        Right (NodeFound closest) -> do
          $(logDebug) $ "Get a list of closest nodes: " <>
                         T.pack (PP.render (pretty closest))
          forM_ closest $ \ info @ NodeInfo {..} -> do
            let prettyAddr = T.pack (show (pretty nodeAddr))
            $(logInfoS) "bootstrap" $ "table detalization" <> prettyAddr
            insertClosest nodeAddr

-- | Get list of peers which downloading this torrent.
--
-- (TODO) This operation is synchronous and do block.
--
lookup :: Address ip => InfoHash -> DHT ip [PeerAddr ip]
lookup topic = getClosestHash topic >>= collect
     -- TODO retry getClosestHash if bucket is empty
  where
    collect nodes = L.concat <$> forM (nodeAddr <$> nodes) retrieve
    retrieve addr = do
      GotPeers {..} <- GetPeers topic <@> addr
      either collect pure peers

-- | Announce that /this/ peer may have some pieces of the specified
-- torrent.
--
-- (TODO) This operation is asynchronous and do not block.
--
insert :: Address ip => InfoHash -> PortNumber -> DHT ip ()
insert ih port = do
  nodes <- getClosestHash ih
  forM_ (nodeAddr <$> nodes) $ \ addr -> do
--    GotPeers {..} <- GetPeers ih <@> addr
--    Announced     <- Announce False ih undefined grantedToken <@> addr
    return ()

-- | Stop announcing /this/ peer for the specified torrent.
--
--   This operation is atomic and do not block.
--
delete :: Address ip => InfoHash -> DHT ip ()
delete = error "DHT.delete: not implemented"