summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Tracker/Protocol.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/Tracker/Protocol.hs')
-rw-r--r--src/Network/BitTorrent/Tracker/Protocol.hs204
1 files changed, 204 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Tracker/Protocol.hs b/src/Network/BitTorrent/Tracker/Protocol.hs
new file mode 100644
index 00000000..000b38c1
--- /dev/null
+++ b/src/Network/BitTorrent/Tracker/Protocol.hs
@@ -0,0 +1,204 @@
1-- |
2-- Copyright : (c) Sam T. 2013
3-- License : MIT
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : non-portable
7--
8--
9-- This module provides straigthforward Tracker protocol
10-- implementation. The tracker is an HTTP/HTTPS service:
11--
12-- * A tracker request is HTTP GET request; used to include
13-- metrics from clients that help the tracker keep overall
14-- statistics about the torrent.
15--
16-- * The tracker response includes a peer list that helps the
17-- client participate in the torrent.
18--
19-- For more convenient high level API see Network.BitTorrent.Tracker
20-- module.
21--
22{-# OPTIONS -fno-warn-orphans #-}
23{-# LANGUAGE OverloadedStrings #-}
24-- TODO: add "compact" field to TRequest
25module Network.BitTorrent.Tracker.Protocol
26 ( module Network.BitTorrent.Tracker.Scrape
27
28 , Event(..), TRequest(..), TResponse(..)
29 , sendRequest
30
31 -- * Defaults
32 , defaultPorts, defaultNumWant
33 )
34 where
35
36import Control.Applicative
37import Data.Char as Char
38import Data.Word (Word32)
39import Data.List as L
40import Data.Map as M
41import Data.Monoid
42import Data.BEncode
43import Data.ByteString as B
44import Data.ByteString.Char8 as BC
45import Data.Text as T
46import Data.Serialize.Get hiding (Result)
47import Data.URLEncoded as URL
48import Data.Torrent
49
50import Network
51import Network.Socket
52import Network.HTTP
53import Network.URI
54
55import Network.BitTorrent.Peer
56import Network.BitTorrent.PeerID
57import Network.BitTorrent.Tracker.Scrape
58
59
60data Event = Started -- ^ For first request.
61 | Stopped -- ^ Sent when the peer is shutting down.
62 | Completed -- ^ To be sent when the peer completes a download.
63 deriving (Show, Read, Eq, Ord, Enum, Bounded)
64
65data TRequest = TRequest { -- TODO peer here -- TODO detach announce
66 reqAnnounce :: URI -- ^ Announce url of the torrent.
67 , reqInfoHash :: InfoHash -- ^ Hash of info part of the torrent.
68 , reqPeerID :: PeerID -- ^ Id of the peer doing request. ()
69 , reqPort :: PortNumber -- ^ Port to listen to for connection from other peers.
70 , reqUploaded :: Integer -- ^ # of bytes that the peer has uploaded in the swarm.
71 , reqDownloaded :: Integer -- ^ # of bytes downloaded in the swarm by the peer.
72 , reqLeft :: Integer -- ^ # of bytes needed in order to complete download.
73 , reqIP :: Maybe HostAddress -- ^ The peer IP.
74 , reqNumWant :: Maybe Int -- ^ Number of peers that the peers wants to receive from.
75 , reqEvent :: Maybe Event -- ^ If not specified,
76 -- the request is regular periodic request.
77 } deriving Show
78
79data TResponse =
80 Failure Text -- ^ Failure reason in human readable form.
81 | OK {
82 respWarning :: Maybe Text
83 , respInterval :: Int -- ^ Recommended interval to wait between requests.
84 , respMinInterval :: Maybe Int -- ^ Minimal amount of time between requests.
85 , respComplete :: Maybe Int -- ^ Number of peers completed the torrent. (seeders)
86 , respIncomplete :: Maybe Int -- ^ Number of peers downloading the torrent.
87 , respPeers :: [Peer] -- ^ Peers that must be contacted.
88 } deriving Show
89
90instance BEncodable PortNumber where
91 toBEncode = toBEncode . fromEnum
92 fromBEncode b = toEnum <$> fromBEncode b
93
94instance BEncodable Peer where
95 toBEncode (Peer pid pip pport) = fromAssocs
96 [ "peer id" -->? pid
97 , "ip" --> pip
98 , "port" --> pport
99 ]
100
101 fromBEncode (BDict d) =
102 Peer <$> d >--? "peer id"
103 <*> d >-- "ip"
104 <*> d >-- "port"
105
106 fromBEncode _ = decodingError "Peer"
107
108instance BEncodable TResponse where
109 toBEncode (Failure t) = fromAssocs ["failure reason" --> t]
110 toBEncode resp@(OK {}) = fromAssocs
111 [ "interval" --> respInterval resp
112 , "min interval" -->? respMinInterval resp
113 , "complete" -->? respComplete resp
114 , "incomplete" -->? respIncomplete resp
115 , "peers" --> respPeers resp
116 ]
117
118 fromBEncode (BDict d)
119 | Just t <- M.lookup "failure reason" d = Failure <$> fromBEncode t
120 | otherwise = OK <$> d >--? "warning message"
121 <*> d >-- "interval"
122 <*> d >--? "min interval"
123 <*> d >--? "complete"
124 <*> d >--? "incomplete"
125 <*> getPeers (M.lookup "peers" d)
126
127 where
128 getPeers :: Maybe BEncode -> Result [Peer]
129 getPeers (Just (BList l)) = fromBEncode (BList l)
130 getPeers (Just (BString s))
131 | B.length s `mod` 6 == 0 =
132 let cnt = B.length s `div` 6 in
133 runGet (sequence (L.replicate cnt peerG)) s
134 | otherwise = decodingError "peers length not a multiple of 6"
135 where
136 peerG = do
137 pip <- getWord32be
138 pport <- getWord16be
139 return (Peer Nothing (fromIntegral pip) (fromIntegral pport))
140
141 getPeers _ = decodingError "Peers"
142
143 fromBEncode _ = decodingError "TResponse"
144
145
146instance URLShow PortNumber where
147 urlShow = urlShow . fromEnum
148
149instance URLShow Word32 where
150 urlShow = show
151
152instance URLShow Event where
153 urlShow e = urlShow (Char.toLower x : xs)
154 where
155 -- this is always nonempty list
156 (x : xs) = show e
157
158instance URLEncode TRequest where
159 urlEncode req = mconcat
160 [ s "peer_id" %= reqPeerID req
161 , s "port" %= reqPort req
162 , s "uploaded" %= reqUploaded req
163 , s "downloaded" %= reqDownloaded req
164 , s "left" %= reqLeft req
165 , s "ip" %=? reqIP req
166 , s "numwant" %=? reqNumWant req
167 , s "event" %=? reqEvent req
168 ]
169 where s :: String -> String; s = id; {-# INLINE s #-}
170
171encodeRequest :: TRequest -> URI
172encodeRequest req = URL.urlEncode req
173 `addToURI` reqAnnounce req
174 `addHashToURI` reqInfoHash req
175
176
177-- | Ports typically reserved for bittorrent.
178defaultPorts :: [PortNumber]
179defaultPorts = [6881..6889]
180
181-- | Above 25, new peers are highly unlikely to increase download speed.
182-- Even 30 peers is _plenty_, the official client version 3 in fact only
183-- actively forms new connections if it has less than 30 peers and will
184-- refuse connections if it has 55. So default value is set to 25.
185--
186defaultNumWant :: Int
187defaultNumWant = 25
188
189
190
191
192-- | TODO rename to ask for peers
193--
194sendRequest :: TRequest -> IO (Result TResponse)
195sendRequest req = do
196 let r = mkHTTPRequest (encodeRequest req)
197
198 rawResp <- simpleHTTP r
199 respBody <- getResponseBody rawResp
200 return (decoded (BC.pack respBody))
201
202 where
203 mkHTTPRequest :: URI -> Request String
204 mkHTTPRequest uri = Request uri GET [] ""