summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSam T <pxqr.sta@gmail.com>2013-06-07 18:17:01 +0400
committerSam T <pxqr.sta@gmail.com>2013-06-07 18:17:01 +0400
commit7f299646b8c761f28b101b6232cc183712dcfa2e (patch)
tree17454c364bc0158628182ea9d201a520e70c23fd
parenta2c8d014636103da15dc013ad3015c8150db0e42 (diff)
~ Polish documentation for Tracker.Protocol.
-rw-r--r--src/Network/BitTorrent/Tracker/Protocol.hs132
1 files changed, 91 insertions, 41 deletions
diff --git a/src/Network/BitTorrent/Tracker/Protocol.hs b/src/Network/BitTorrent/Tracker/Protocol.hs
index 1bd70268..0371a187 100644
--- a/src/Network/BitTorrent/Tracker/Protocol.hs
+++ b/src/Network/BitTorrent/Tracker/Protocol.hs
@@ -7,17 +7,15 @@
7-- 7--
8-- 8--
9-- This module provides straigthforward Tracker protocol 9-- This module provides straigthforward Tracker protocol
10-- implementation. The tracker is an HTTP/HTTPS service: 10-- implementation. The tracker is an HTTP/HTTPS service used to
11-- discovery peers for a particular existing torrent and keep
12-- statistics about the swarm.
11-- 13--
12-- * A tracker request is HTTP GET request; used to include 14-- For more convenient high level API see
13-- metrics from clients that help the tracker keep overall 15-- "Network.BitTorrent.Tracker" module.
14-- statistics about the torrent.
15-- 16--
16-- * The tracker response includes a peer list that helps the 17-- For more information see:
17-- client participate in the torrent. 18-- <https://wiki.theory.org/BitTorrentSpecification#Tracker_HTTP.2FHTTPS_Protocol>
18--
19-- For more convenient high level API see Network.BitTorrent.Tracker
20-- module.
21-- 19--
22{-# OPTIONS -fno-warn-orphans #-} 20{-# OPTIONS -fno-warn-orphans #-}
23{-# LANGUAGE OverloadedStrings #-} 21{-# LANGUAGE OverloadedStrings #-}
@@ -41,7 +39,6 @@ import Data.Map as M
41import Data.Monoid 39import Data.Monoid
42import Data.BEncode 40import Data.BEncode
43import Data.ByteString as B 41import Data.ByteString as B
44import Data.ByteString.Char8 as BC
45import Data.Text as T 42import Data.Text as T
46import Data.Serialize.Get hiding (Result) 43import Data.Serialize.Get hiding (Result)
47import Data.URLEncoded as URL 44import Data.URLEncoded as URL
@@ -56,36 +53,90 @@ import Network.BitTorrent.Peer
56import Network.BitTorrent.Tracker.Scrape 53import Network.BitTorrent.Tracker.Scrape
57 54
58 55
59data Event = Started -- ^ For first request. 56
60 | Stopped -- ^ Sent when the peer is shutting down. 57-- | Events used to specify which kind of tracker request is performed.
61 | Completed -- ^ To be sent when the peer completes a download. 58data Event = Started
59 -- ^ For the first request: when a peer join the swarm.
60 | Stopped
61 -- ^ Sent when the peer is shutting down.
62 | Completed
63 -- ^ To be sent when the peer completes a download.
62 deriving (Show, Read, Eq, Ord, Enum, Bounded) 64 deriving (Show, Read, Eq, Ord, Enum, Bounded)
63 65
66
67-- | A tracker request is HTTP GET request; used to include metrics
68-- from clients that help the tracker keep overall statistics about
69-- the torrent. The most important, requests are used by the tracker
70-- to keep track lists of active peer for a particular torrent.
71--
64data TRequest = TRequest { -- TODO peer here -- TODO detach announce 72data TRequest = TRequest { -- TODO peer here -- TODO detach announce
65 reqAnnounce :: URI -- ^ Announce url of the torrent. 73 reqAnnounce :: URI
66 , reqInfoHash :: InfoHash -- ^ Hash of info part of the torrent. 74 -- ^ Announce url of the torrent usually obtained from 'Torrent'.
67 , reqPeerID :: PeerID -- ^ Id of the peer doing request. () 75
68 , reqPort :: PortNumber -- ^ Port to listen to for connection from other peers. 76 , reqInfoHash :: InfoHash
69 , reqUploaded :: Integer -- ^ # of bytes that the peer has uploaded in the swarm. 77 -- ^ Hash of info part of the torrent usually obtained from
70 , reqDownloaded :: Integer -- ^ # of bytes downloaded in the swarm by the peer. 78 -- 'Torrent'.
71 , reqLeft :: Integer -- ^ # of bytes needed in order to complete download. 79
72 , reqIP :: Maybe HostAddress -- ^ The peer IP. 80 , reqPeerID :: PeerID
73 , reqNumWant :: Maybe Int -- ^ Number of peers that the peers wants to receive from. 81 -- ^ ID of the peer doing request.
74 , reqEvent :: Maybe Event -- ^ If not specified, 82
75 -- the request is regular periodic request. 83 , reqPort :: PortNumber
84 -- ^ Port to listen to for connections from other
85 -- peers. Normally, tracker should respond with this port when
86 -- some peer request the tracker with the same info hash.
87
88 , reqUploaded :: Integer
89 -- ^ Number of bytes that the peer has uploaded in the swarm.
90
91 , reqDownloaded :: Integer
92 -- ^ Number of bytes downloaded in the swarm by the peer.
93
94 , reqLeft :: Integer
95 -- ^ Number of bytes needed in order to complete download.
96
97 , reqIP :: Maybe HostAddress
98 -- ^ The peer IP. Needed only when client communicated with
99 -- tracker throught a proxy.
100
101 , reqNumWant :: Maybe Int
102 -- ^ Number of peers that the peers wants to receive from. See
103 -- note for 'defaultNumWant'.
104
105 , reqEvent :: Maybe Event
106 -- ^ If not specified, the request is regular periodic request.
76 } deriving Show 107 } deriving Show
77 108
109
110-- | The tracker response includes a peer list that helps the client
111-- participate in the torrent. The most important is 'respPeer' list
112-- used to join the swarm.
113--
78data TResponse = 114data TResponse =
79 Failure Text -- ^ Failure reason in human readable form. 115 Failure Text -- ^ Failure reason in human readable form.
80 | OK { 116 | OK {
81 respWarning :: Maybe Text 117 respWarning :: Maybe Text
82 , respInterval :: Int -- ^ Recommended interval to wait between requests. 118 -- ^ Human readable warning.
83 , respMinInterval :: Maybe Int -- ^ Minimal amount of time between requests. 119
84 , respComplete :: Maybe Int -- ^ Number of peers completed the torrent. (seeders) 120 , respInterval :: Int
85 , respIncomplete :: Maybe Int -- ^ Number of peers downloading the torrent. 121 -- ^ Recommended interval to wait between requests.
86 , respPeers :: [PeerAddr] -- ^ Peers that must be contacted. 122
123 , respMinInterval :: Maybe Int
124 -- ^ Minimal amount of time between requests. A peer /should/
125 -- make timeout with at least 'respMinInterval' value,
126 -- otherwise tracker might not respond. If not specified the
127 -- same applies to 'respInterval'.
128
129 , respComplete :: Maybe Int
130 -- ^ Number of peers completed the torrent. (seeders)
131
132 , respIncomplete :: Maybe Int
133 -- ^ Number of peers downloading the torrent. (leechers)
134
135 , respPeers :: [PeerAddr]
136 -- ^ Peers that must be contacted.
87 } deriving Show 137 } deriving Show
88 138
139
89instance BEncodable TResponse where 140instance BEncodable TResponse where
90 toBEncode (Failure t) = fromAssocs ["failure reason" --> t] 141 toBEncode (Failure t) = fromAssocs ["failure reason" --> t]
91 toBEncode resp@(OK {}) = fromAssocs 142 toBEncode resp@(OK {}) = fromAssocs
@@ -117,8 +168,8 @@ instance BEncodable TResponse where
117 peerG = do 168 peerG = do
118 pip <- getWord32be 169 pip <- getWord32be
119 pport <- getWord16be 170 pport <- getWord16be
120 return (PeerAddr Nothing (fromIntegral pip) (fromIntegral pport)) 171 return $ PeerAddr Nothing (fromIntegral pip)
121 172 (fromIntegral pport)
122 getPeers _ = decodingError "Peers" 173 getPeers _ = decodingError "Peers"
123 174
124 fromBEncode _ = decodingError "TResponse" 175 fromBEncode _ = decodingError "TResponse"
@@ -133,7 +184,7 @@ instance URLShow Word32 where
133instance URLShow Event where 184instance URLShow Event where
134 urlShow e = urlShow (Char.toLower x : xs) 185 urlShow e = urlShow (Char.toLower x : xs)
135 where 186 where
136 -- this is always nonempty list 187 -- INVARIANT: this is always nonempty list
137 (x : xs) = show e 188 (x : xs) = show e
138 189
139instance URLEncode TRequest where 190instance URLEncode TRequest where
@@ -155,21 +206,20 @@ encodeRequest req = URL.urlEncode req
155 `addHashToURI` reqInfoHash req 206 `addHashToURI` reqInfoHash req
156 207
157 208
158-- | Ports typically reserved for bittorrent. 209-- | Ports typically reserved for bittorrent P2P communication.
159defaultPorts :: [PortNumber] 210defaultPorts :: [PortNumber]
160defaultPorts = [6881..6889] 211defaultPorts = [6881..6889]
161 212
162-- | Above 25, new peers are highly unlikely to increase download speed. 213-- | Above 25, new peers are highly unlikely to increase download
163-- Even 30 peers is _plenty_, the official client version 3 in fact only 214-- speed. Even 30 peers is /plenty/, the official client version 3
164-- actively forms new connections if it has less than 30 peers and will 215-- in fact only actively forms new connections if it has less than
165-- refuse connections if it has 55. So default value is set to 25. 216-- 30 peers and will refuse connections if it has 55.
217--
218-- So the default value is set to 25.
166-- 219--
167defaultNumWant :: Int 220defaultNumWant :: Int
168defaultNumWant = 25 221defaultNumWant = 25
169 222
170
171
172
173-- | TODO rename to ask for peers 223-- | TODO rename to ask for peers
174-- 224--
175sendRequest :: TRequest -> IO (Result TResponse) 225sendRequest :: TRequest -> IO (Result TResponse)