summaryrefslogtreecommitdiff
path: root/dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs
diff options
context:
space:
mode:
Diffstat (limited to 'dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs')
-rw-r--r--dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs175
1 files changed, 175 insertions, 0 deletions
diff --git a/dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs b/dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs
new file mode 100644
index 00000000..45fef05e
--- /dev/null
+++ b/dht/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs
@@ -0,0 +1,175 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- This module provides unified RPC interface to BitTorrent
9-- trackers. The tracker is an UDP/HTTP/HTTPS service used to
10-- discovery peers for a particular existing torrent and keep
11-- statistics about the swarm. This module also provides a way to
12-- request scrape info for a particular torrent list.
13--
14{-# LANGUAGE DeriveDataTypeable #-}
15module Network.BitTorrent.Tracker.RPC
16 ( PeerInfo (..)
17
18 -- * Manager
19 , Options (..)
20 , Manager
21 , newManager
22 , closeManager
23 , withManager
24
25 -- * RPC
26 , SAnnounceQuery (..)
27 , RpcException (..)
28 , Network.BitTorrent.Tracker.RPC.announce
29 , scrape
30 ) where
31
32import Control.Exception
33import Data.Default
34import Data.Typeable
35import Network
36import Network.URI
37import Network.Socket (HostAddress)
38
39import Data.Torrent
40import Network.Address
41import Network.BitTorrent.Internal.Progress
42import Network.BitTorrent.Tracker.Message
43import qualified Network.BitTorrent.Tracker.RPC.HTTP as HTTP
44import qualified Network.BitTorrent.Tracker.RPC.UDP as UDP
45
46
47{-----------------------------------------------------------------------
48-- Simplified announce
49-----------------------------------------------------------------------}
50
51-- | Info to advertise to trackers.
52data PeerInfo = PeerInfo
53 { peerId :: !PeerId
54 , peerIP :: !(Maybe HostAddress)
55 , peerPort :: !PortNumber
56 } deriving (Show, Eq)
57
58instance Default PeerInfo where
59 def = PeerInfo def Nothing 6881
60
61-- | Simplified announce query.
62data SAnnounceQuery = SAnnounceQuery
63 { sInfoHash :: InfoHash
64 , sProgress :: Progress
65 , sNumWant :: Maybe Int
66 , sEvent :: Maybe AnnounceEvent
67 }
68
69fillAnnounceQuery :: PeerInfo -> SAnnounceQuery -> AnnounceQuery
70fillAnnounceQuery PeerInfo{..} SAnnounceQuery {..} = AnnounceQuery
71 { reqInfoHash = sInfoHash
72 , reqPeerId = peerId
73 , reqPort = peerPort
74 , reqProgress = sProgress
75 , reqIP = peerIP
76 , reqNumWant = sNumWant
77 , reqEvent = sEvent
78 }
79
80{-----------------------------------------------------------------------
81-- RPC manager
82-----------------------------------------------------------------------}
83
84-- | Tracker manager settings.
85data Options = Options
86 { -- | HTTP tracker protocol specific options.
87 optHttpRPC :: !HTTP.Options
88
89 -- | UDP tracker protocol specific options.
90 , optUdpRPC :: !UDP.Options
91
92 -- | Whether to use multitracker extension.
93 , optMultitracker :: !Bool
94 }
95
96instance Default Options where
97 def = Options
98 { optHttpRPC = def
99 , optUdpRPC = def
100 , optMultitracker = True
101 }
102
103-- | Tracker RPC Manager.
104data Manager = Manager
105 { options :: !Options
106 , peerInfo :: !PeerInfo
107 , httpMgr :: !HTTP.Manager
108 , udpMgr :: !UDP.Manager
109 }
110
111-- | Create a new 'Manager'. You /must/ manually 'closeManager'
112-- otherwise resource leakage is possible. Normally, a bittorrent
113-- client need a single RPC manager only.
114--
115-- This function can throw 'IOException' on invalid 'Options'.
116--
117newManager :: Options -> PeerInfo -> IO Manager
118newManager opts info = do
119 h <- HTTP.newManager (optHttpRPC opts)
120 u <- UDP.newManager (optUdpRPC opts) `onException` HTTP.closeManager h
121 return $ Manager opts info h u
122
123-- | Close all pending RPCs. Behaviour of currently in-flight RPCs can
124-- differ depending on underlying protocol used. No rpc calls should
125-- be performed after manager becomes closed.
126closeManager :: Manager -> IO ()
127closeManager Manager {..} = do
128 UDP.closeManager udpMgr `finally` HTTP.closeManager httpMgr
129
130-- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'.
131withManager :: Options -> PeerInfo -> (Manager -> IO a) -> IO a
132withManager opts info = bracket (newManager opts info) closeManager
133
134{-----------------------------------------------------------------------
135-- Exceptions
136-----------------------------------------------------------------------}
137-- TODO Catch IO exceptions on rpc calls (?)
138
139data RpcException
140 = UdpException UDP.RpcException -- ^ UDP RPC driver failure;
141 | HttpException HTTP.RpcException -- ^ HTTP RPC driver failure;
142 | UnrecognizedScheme String -- ^ unsupported scheme in announce URI;
143 | GenericException String -- ^ for furter extensibility.
144 deriving (Show, Typeable)
145
146instance Exception RpcException
147
148packException :: Exception e => (e -> RpcException) -> IO a -> IO a
149packException f m = try m >>= either (throwIO . f) return
150{-# INLINE packException #-}
151
152{-----------------------------------------------------------------------
153-- RPC calls
154-----------------------------------------------------------------------}
155
156dispatch :: URI -> IO a -> IO a -> IO a
157dispatch URI {..} http udp
158 | uriScheme == "http:" ||
159 uriScheme == "https:" = packException HttpException http
160 | uriScheme == "udp:" = packException UdpException udp
161 | otherwise = throwIO $ UnrecognizedScheme uriScheme
162
163announce :: Manager -> URI -> SAnnounceQuery -> IO AnnounceInfo
164announce Manager {..} uri simpleQuery
165 = dispatch uri
166 (HTTP.announce httpMgr uri annQ)
167 ( UDP.announce udpMgr uri annQ)
168 where
169 annQ = fillAnnounceQuery peerInfo simpleQuery
170
171scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo
172scrape Manager {..} uri q
173 = dispatch uri
174 (HTTP.scrape httpMgr uri q)
175 ( UDP.scrape udpMgr uri q)