summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Tracker/Session.hs
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2014-04-04 04:51:36 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2014-04-04 04:51:36 +0400
commit1beb66f98504a39c8a6c976f243a1f69ffb48d8d (patch)
treee26f7eff93b2ef100a768e01b0fbeb239c09dd8a /src/Network/BitTorrent/Tracker/Session.hs
parent13793b8d4cf7c5b4a914d778e3523e950aa2493a (diff)
[Internal] Add EventSource class
Diffstat (limited to 'src/Network/BitTorrent/Tracker/Session.hs')
-rw-r--r--src/Network/BitTorrent/Tracker/Session.hs49
1 files changed, 22 insertions, 27 deletions
diff --git a/src/Network/BitTorrent/Tracker/Session.hs b/src/Network/BitTorrent/Tracker/Session.hs
index e82501dd..5aa9c0eb 100644
--- a/src/Network/BitTorrent/Tracker/Session.hs
+++ b/src/Network/BitTorrent/Tracker/Session.hs
@@ -8,17 +8,18 @@
8-- Multitracker sessions. 8-- Multitracker sessions.
9-- 9--
10{-# LANGUAGE FlexibleInstances #-} 10{-# LANGUAGE FlexibleInstances #-}
11{-# LANGUAGE TypeFamilies #-}
11{-# LANGUAGE TypeSynonymInstances #-} 12{-# LANGUAGE TypeSynonymInstances #-}
12{-# LANGUAGE TemplateHaskell #-} 13{-# LANGUAGE TemplateHaskell #-}
13module Network.BitTorrent.Tracker.Session 14module Network.BitTorrent.Tracker.Session
14 ( -- * Session 15 ( -- * Session
15 Session 16 Session
17 , Event (..)
16 , newSession 18 , newSession
17 , closeSession 19 , closeSession
18 , withSession 20 , withSession
19 21
20 -- * Client send notifications 22 -- * Client send notifications
21 , Event (..)
22 , notify 23 , notify
23 , askPeers 24 , askPeers
24 25
@@ -39,16 +40,12 @@ module Network.BitTorrent.Tracker.Session
39 , addTracker 40 , addTracker
40 , removeTracker 41 , removeTracker
41 , getTrustedTrackers 42 , getTrustedTrackers
42
43 -- * Events
44 , SessionEvent (..)
45 , subscribe
46 ) where 43 ) where
47 44
48import Control.Applicative 45import Control.Applicative
49import Control.Exception 46import Control.Exception
50import Control.Concurrent 47import Control.Concurrent
51import Control.Concurrent.Chan.Split 48import Control.Concurrent.Chan.Split as CS
52import Control.Monad 49import Control.Monad
53import Data.Aeson 50import Data.Aeson
54import Data.Aeson.TH 51import Data.Aeson.TH
@@ -66,6 +63,7 @@ import Data.Torrent.InfoHash
66import Data.Torrent.JSON 63import Data.Torrent.JSON
67import Network.BitTorrent.Core 64import Network.BitTorrent.Core
68import Network.BitTorrent.Internal.Cache 65import Network.BitTorrent.Internal.Cache
66import Network.BitTorrent.Internal.Types
69import Network.BitTorrent.Tracker.List as TL 67import Network.BitTorrent.Tracker.List as TL
70import Network.BitTorrent.Tracker.Message 68import Network.BitTorrent.Tracker.Message
71import Network.BitTorrent.Tracker.RPC as RPC 69import Network.BitTorrent.Tracker.RPC as RPC
@@ -123,7 +121,7 @@ instance Default TrackerSession where
123 def = TrackerSession Nothing def def 121 def = TrackerSession Nothing def def
124 122
125-- | Do we need to notify this /specific/ tracker? 123-- | Do we need to notify this /specific/ tracker?
126needNotify :: Event -> Maybe Status -> Maybe Bool 124needNotify :: AnnounceEvent -> Maybe Status -> Maybe Bool
127needNotify Started Nothing = Just True 125needNotify Started Nothing = Just True
128needNotify Stopped Nothing = Just False 126needNotify Stopped Nothing = Just False
129needNotify Completed Nothing = Just False 127needNotify Completed Nothing = Just False
@@ -135,7 +133,7 @@ needNotify Stopped (Just Paused ) = Just False
135needNotify Completed (Just Paused ) = Just True 133needNotify Completed (Just Paused ) = Just True
136 134
137-- | Client status after event announce succeed. 135-- | Client status after event announce succeed.
138nextStatus :: Event -> Maybe Status 136nextStatus :: AnnounceEvent -> Maybe Status
139nextStatus Started = Just Running 137nextStatus Started = Just Running
140nextStatus Stopped = Just Paused 138nextStatus Stopped = Just Paused
141nextStatus Completed = Nothing -- must keep previous status 139nextStatus Completed = Nothing -- must keep previous status
@@ -159,7 +157,7 @@ cacheScrape AnnounceInfo {..} =
159 } 157 }
160 158
161-- | Make announce request to specific tracker returning new state. 159-- | Make announce request to specific tracker returning new state.
162notifyTo :: Manager -> Session -> Event 160notifyTo :: Manager -> Session -> AnnounceEvent
163 -> TierEntry TrackerSession -> IO TrackerSession 161 -> TierEntry TrackerSession -> IO TrackerSession
164notifyTo mgr s @ Session {..} event (uri, entry @ TrackerSession {..}) = do 162notifyTo mgr s @ Session {..} event (uri, entry @ TrackerSession {..}) = do
165 let shouldNotify = needNotify event statusSent 163 let shouldNotify = needNotify event statusSent
@@ -193,9 +191,20 @@ data Session = Session
193 -- must take a lock. 191 -- must take a lock.
194 , sessionTrackers :: !(MVar (TrackerList TrackerSession)) 192 , sessionTrackers :: !(MVar (TrackerList TrackerSession))
195 193
196 , sessionEvents :: !(SendPort SessionEvent) 194 , sessionEvents :: !(SendPort (Event Session))
197 } 195 }
198 196
197instance EventSource Session where
198 data Event Session
199 = TrackerAdded URI
200 | TrackerConfirmed URI
201 | TrackerRemoved URI
202 | AnnouncedTo URI
203 | SessionClosed
204
205 listen Session {..} = CS.listen sessionEvents
206
207
199-- | Create a new multitracker session in paused state. Tracker list 208-- | Create a new multitracker session in paused state. Tracker list
200-- must contant only /trusted/ tracker uris. To start announcing 209-- must contant only /trusted/ tracker uris. To start announcing
201-- client presence use 'notify'. 210-- client presence use 'notify'.
@@ -221,20 +230,6 @@ closeSession m s @ Session {..} = do
221 send sessionEvents SessionClosed 230 send sessionEvents SessionClosed
222 231
223{----------------------------------------------------------------------- 232{-----------------------------------------------------------------------
224-- Events
225-----------------------------------------------------------------------}
226
227data SessionEvent
228 = TrackerAdded URI
229 | TrackerConfirmed URI
230 | TrackerRemoved URI
231 | AnnouncedTo URI
232 | SessionClosed
233
234subscribe :: Session -> IO (ReceivePort SessionEvent)
235subscribe Session {..} = listen sessionEvents
236
237{-----------------------------------------------------------------------
238-- Operations 233-- Operations
239-----------------------------------------------------------------------} 234-----------------------------------------------------------------------}
240 235
@@ -253,12 +248,12 @@ getSessionState Session {..} = TL.toList <$> readMVar sessionTrackers
253 248
254-- | Do we need to sent this event to a first working tracker or to 249-- | Do we need to sent this event to a first working tracker or to
255-- the all known good trackers? 250-- the all known good trackers?
256allNotify :: Event -> Bool 251allNotify :: AnnounceEvent -> Bool
257allNotify Started = False 252allNotify Started = False
258allNotify Stopped = True 253allNotify Stopped = True
259allNotify Completed = True 254allNotify Completed = True
260 255
261notifyAll :: Manager -> Session -> Event -> IO () 256notifyAll :: Manager -> Session -> AnnounceEvent -> IO ()
262notifyAll mgr s @ Session {..} event = do 257notifyAll mgr s @ Session {..} event = do
263 modifyMVar_ sessionTrackers $ 258 modifyMVar_ sessionTrackers $
264 (traversal (notifyTo mgr s event)) 259 (traversal (notifyTo mgr s event))
@@ -271,7 +266,7 @@ notifyAll mgr s @ Session {..} event = do
271-- | 266-- |
272-- 267--
273-- This function /may/ block until tracker query proceed. 268-- This function /may/ block until tracker query proceed.
274notify :: Manager -> Session -> Event -> IO () 269notify :: Manager -> Session -> AnnounceEvent -> IO ()
275notify mgr ses event = do 270notify mgr ses event = do
276 prevStatus <- atomicModifyIORef (sessionStatus ses) $ \ s -> 271 prevStatus <- atomicModifyIORef (sessionStatus ses) $ \ s ->
277 (fromMaybe s (nextStatus event), s) 272 (fromMaybe s (nextStatus event), s)