summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2014-02-26 11:50:06 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2014-02-26 11:50:06 +0400
commit6d381df09aecc797d9e20acaf5996399c21a6916 (patch)
treeab64c9c13f1e032069f780055e8a89ee191b54b3 /src/Network/BitTorrent
parent2bdeb03de13456945a50ceb3f0d01ba7c27462dc (diff)
Remove WAI dependency
Diffstat (limited to 'src/Network/BitTorrent')
-rw-r--r--src/Network/BitTorrent/Tracker/Wai.hs252
1 files changed, 0 insertions, 252 deletions
diff --git a/src/Network/BitTorrent/Tracker/Wai.hs b/src/Network/BitTorrent/Tracker/Wai.hs
deleted file mode 100644
index df56e378..00000000
--- a/src/Network/BitTorrent/Tracker/Wai.hs
+++ /dev/null
@@ -1,252 +0,0 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Tracker WAI application.
9--
10{-# LANGUAGE RecordWildCards #-}
11module Network.BitTorrent.Tracker.Wai
12 ( -- * Configuration
13 TrackerSettings (..)
14
15 -- * Tracker
16 , Tracker
17 , newTracker
18 , closeTracker
19 , withTracker
20
21 -- * Application
22 , tracker
23 ) where
24
25import Control.Applicative
26import Control.Concurrent.STM
27import Control.Exception
28import Control.Monad.Trans
29import Control.Monad.Trans.Resource
30import Data.BEncode as BE
31import Data.Default
32import Data.HashMap.Strict as HM
33import Data.List as L
34import Data.Maybe
35import Network.HTTP.Types
36import Network.Wai
37
38import Data.Torrent.InfoHash
39import Data.Torrent.Progress
40import Network.BitTorrent.Tracker.Message
41
42
43-- | Various configuration settings used to generate tracker response.
44data TrackerSettings = TrackerSettings
45 { announcePath :: !RawPath
46 , scrapePath :: !RawPath
47
48 -- | If peer did not specified the "numwant" then this value is
49 -- used.
50 , defNumWant :: {-# UNPACK #-} !Int
51
52 -- | If peer specified too big numwant value.
53 , maxNumWant :: {-# UNPACK #-} !Int
54
55 -- | Recommended time interval to wait between regular announce
56 -- requests.
57 , reannounceInterval :: {-# UNPACK #-} !Int
58
59 -- | Minimum time interval to wait between regular announce
60 -- requests.
61 , reannounceMinInterval :: !(Maybe Int)
62
63 -- | Whether to send count of seeders.
64 , completePeers :: !Bool
65
66 -- | Whether to send count of leechers.
67 , incompletePeers :: !Bool
68
69 -- | Do not send peer id in response. Peer can override this value
70 -- by setting "no_peer_id" to 0 or 1.
71 , noPeerId :: !Bool
72
73 -- | Whether to send compact peer list. Peer can override this
74 -- value by setting "compact" to 0 or 1.
75 , compactPeerList :: !Bool
76 } deriving (Show, Read, Eq)
77
78-- | Conservative tracker settings compatible with any client.
79instance Default TrackerSettings where
80 def = TrackerSettings
81 { announcePath = defaultAnnouncePath
82 , scrapePath = defaultScrapePath
83 , defNumWant = defaultNumWant
84 , maxNumWant = defaultMaxNumWant
85 , reannounceInterval = defaultReannounceInterval
86 , reannounceMinInterval = Nothing
87 , compactPeerList = False
88 , completePeers = False
89 , incompletePeers = False
90 , noPeerId = False
91 }
92
93{-----------------------------------------------------------------------
94-- Swarm
95-----------------------------------------------------------------------}
96
97type PeerSet = [()]
98
99data Swarm = Swarm
100 { leechers :: !PeerSet
101 , seeders :: !PeerSet
102 , downloaded :: {-# UNPACK #-} !Int
103 }
104
105instance Default Swarm where
106 def = Swarm
107 { leechers = []
108 , seeders = []
109 , downloaded = 0
110 }
111{-
112started :: PeerInfo -> Swarm -> Swarm
113started info Swarm {..} = Swarm
114 { leechers = insert info leechers
115 , seeders = delete info seeders
116 , downloaded = downloaded
117 }
118
119regular :: PeerInfo -> Swarm -> Swarm
120regular info Swarm {..} = undefined
121
122stopped :: PeerInfo -> Swarm -> Swarm
123stopped info Swarm {..} = Swarm
124 { leechers = delete info leechers
125 , seeders = delete info seeders
126 , downloaded = downloaded
127 }
128
129completed :: PeerInfo -> Swarm -> Swarm
130completed info Swarm {..} = Swarm
131 { leechers = delete info leechers
132 , seeders = insert info seeders
133 , downloaded = succ downloaded
134 }
135
136event :: Maybe Event -> Swarm -> Swarm
137event = undefined
138-}
139--peerList :: TrackerSettings -> Swarm -> PeerList IP
140peerList TrackerSettings {..} Swarm {..} = undefined --envelope peers
141 where
142 envelope = if compactPeerList then CompactPeerList else PeerList
143 peers = []
144
145announceInfo :: TrackerSettings -> Swarm -> AnnounceInfo
146announceInfo settings @ TrackerSettings {..} swarm @ Swarm {..} = AnnounceInfo
147 { respComplete = Just (L.length seeders)
148 , respIncomplete = Just (L.length leechers)
149 , respInterval = reannounceInterval
150 , respMinInterval = reannounceMinInterval
151 , respPeers = undefined -- peerList settings swarm
152 , respWarning = Nothing
153 }
154
155scrapeEntry :: Swarm -> ScrapeEntry
156scrapeEntry Swarm {..} = ScrapeEntry
157 { siComplete = L.length seeders
158 , siDownloaded = downloaded
159 , siIncomplete = L.length leechers
160 , siName = Nothing
161 }
162
163{-----------------------------------------------------------------------
164-- Tracker state
165-----------------------------------------------------------------------}
166
167type Table = HashMap InfoHash Swarm
168
169withSwarm :: TVar Table -> InfoHash -> (Maybe Swarm -> STM (a, Swarm)) -> STM a
170withSwarm tableRef infohash action = do
171 table <- readTVar tableRef
172 (res, swarm') <- action (HM.lookup infohash table)
173 writeTVar tableRef (HM.insert infohash swarm' table)
174 return res
175
176scrapeInfo :: ScrapeQuery -> Table -> [ScrapeEntry]
177scrapeInfo query table = do
178 infohash <- query
179 swarm <- maybeToList $ HM.lookup infohash table
180 return $ scrapeEntry swarm
181
182data TrackerState = TrackerState
183 { swarms :: !(TVar Table)
184 }
185
186newState :: IO TrackerState
187newState = TrackerState <$> newTVarIO HM.empty
188
189data Tracker = Tracker
190 { options :: !TrackerSettings
191 , state :: !TrackerState
192 }
193
194newTracker :: TrackerSettings -> IO Tracker
195newTracker opts = Tracker opts <$> newState
196
197closeTracker :: Tracker -> IO ()
198closeTracker _ = return ()
199
200withTracker :: TrackerSettings -> (Tracker -> IO a) -> IO a
201withTracker opts = bracket (newTracker opts) closeTracker
202
203{-----------------------------------------------------------------------
204-- Handlers
205-----------------------------------------------------------------------}
206
207getAnnounceR :: Tracker -> AnnounceRequest -> ResourceT IO AnnounceInfo
208getAnnounceR Tracker {..} AnnounceRequest {..} = do
209 return undefined
210{-
211 atomically $ do
212 withSwarm (swarms state) (reqInfoHash announceQuery) $ \ mswarm ->
213 case mswarm of
214 Nothing -> return undefined
215 Just s -> return undefined
216-}
217getScrapeR :: Tracker -> ScrapeQuery -> ResourceT IO ScrapeInfo
218getScrapeR Tracker {..} query = do
219 table <- liftIO $ readTVarIO (swarms state)
220 return $ undefined $ scrapeInfo query table
221
222{-----------------------------------------------------------------------
223-- Routing
224-----------------------------------------------------------------------}
225
226announceResponse :: AnnounceInfo -> Response
227announceResponse info = responseLBS ok200 headers $ BE.encode info
228 where
229 headers = [(hContentType, announceType)]
230
231scrapeResponse :: ScrapeInfo -> Response
232scrapeResponse info = responseLBS ok200 headers $ BE.encode info
233 where
234 headers = [(hContentType, scrapeType)]
235
236-- content-type: "text/plain"!
237tracker :: Tracker -> Application
238tracker t @ (Tracker TrackerSettings {..} _) Request {..}
239 | requestMethod /= methodGet
240 = return $ responseLBS methodNotAllowed405 [] ""
241
242 | rawPathInfo == announcePath = do
243 case parseAnnounceRequest $ queryToSimpleQuery queryString of
244 Right query -> announceResponse <$> getAnnounceR t query
245 Left msg -> return $ responseLBS (parseFailureStatus msg) [] ""
246
247 | rawPathInfo == scrapePath = do
248 case Right $ parseScrapeQuery $ queryToSimpleQuery queryString of -- TODO
249 Right query -> scrapeResponse <$> getScrapeR t query
250 Left msg -> return $ responseLBS badRequest400 [] ""
251
252 | otherwise = undefined --badPath