summaryrefslogtreecommitdiff
path: root/bittorrent/src/Network/BitTorrent/Client
diff options
context:
space:
mode:
Diffstat (limited to 'bittorrent/src/Network/BitTorrent/Client')
-rw-r--r--bittorrent/src/Network/BitTorrent/Client/Handle.hs188
-rw-r--r--bittorrent/src/Network/BitTorrent/Client/Types.hs163
2 files changed, 351 insertions, 0 deletions
diff --git a/bittorrent/src/Network/BitTorrent/Client/Handle.hs b/bittorrent/src/Network/BitTorrent/Client/Handle.hs
new file mode 100644
index 00000000..66baac48
--- /dev/null
+++ b/bittorrent/src/Network/BitTorrent/Client/Handle.hs
@@ -0,0 +1,188 @@
1module Network.BitTorrent.Client.Handle
2 ( -- * Handle
3 Handle
4
5 -- * Initialization
6 , openTorrent
7 , openMagnet
8 , closeHandle
9
10 -- * Control
11 , start
12 , pause
13 , stop
14
15 -- * Query
16 , getHandle
17 , getStatus
18 ) where
19
20import Control.Concurrent.Chan.Split
21import Control.Concurrent.Lifted as L
22import Control.Monad
23import Control.Monad.Trans
24import Data.Default
25import Data.List as L
26import Data.HashMap.Strict as HM
27
28import Data.Torrent
29import Network.BitTorrent.Client.Types as Types
30import Network.BitTorrent.DHT as DHT
31import Network.BitTorrent.Exchange as Exchange
32import Network.BitTorrent.Tracker as Tracker
33
34{-----------------------------------------------------------------------
35-- Safe handle set manupulation
36-----------------------------------------------------------------------}
37
38allocHandle :: InfoHash -> BitTorrent Handle -> BitTorrent Handle
39allocHandle ih m = do
40 Client {..} <- getClient
41
42 (h, added) <- modifyMVar clientTorrents $ \ handles -> do
43 case HM.lookup ih handles of
44 Just h -> return (handles, (h, False))
45 Nothing -> do
46 h <- m
47 return (HM.insert ih h handles, (h, True))
48
49 when added $ do
50 liftIO $ send clientEvents (TorrentAdded ih)
51
52 return h
53
54freeHandle :: InfoHash -> BitTorrent () -> BitTorrent ()
55freeHandle ih finalizer = do
56 Client {..} <- getClient
57
58 modifyMVar_ clientTorrents $ \ handles -> do
59 case HM.lookup ih handles of
60 Nothing -> return handles
61 Just _ -> do
62 finalizer
63 return (HM.delete ih handles)
64
65lookupHandle :: InfoHash -> BitTorrent (Maybe Handle)
66lookupHandle ih = do
67 Client {..} <- getClient
68 handles <- readMVar clientTorrents
69 return (HM.lookup ih handles)
70
71{-----------------------------------------------------------------------
72-- Initialization
73-----------------------------------------------------------------------}
74
75newExchangeSession :: FilePath -> Either InfoHash InfoDict -> BitTorrent Exchange.Session
76newExchangeSession rootPath source = do
77 c @ Client {..} <- getClient
78 liftIO $ Exchange.newSession clientLogger (externalAddr c) rootPath source
79
80-- | Open a torrent in 'stop'ed state. Use 'nullTorrent' to open
81-- handle from 'InfoDict'. This operation do not block.
82openTorrent :: FilePath -> Torrent -> BitTorrent Handle
83openTorrent rootPath t @ Torrent {..} = do
84 let ih = idInfoHash tInfoDict
85 allocHandle ih $ do
86 statusVar <- newMVar Types.Stopped
87 tses <- liftIO $ Tracker.newSession ih (trackerList t)
88 eses <- newExchangeSession rootPath (Right tInfoDict)
89 eventStream <- liftIO newSendPort
90 return $ Handle
91 { handleTopic = ih
92 , handlePrivate = idPrivate tInfoDict
93 , handleStatus = statusVar
94 , handleTrackers = tses
95 , handleExchange = eses
96 , handleEvents = eventStream
97 }
98
99-- | Use 'nullMagnet' to open handle from 'InfoHash'.
100openMagnet :: FilePath -> Magnet -> BitTorrent Handle
101openMagnet rootPath Magnet {..} = do
102 allocHandle exactTopic $ do
103 statusVar <- newMVar Types.Stopped
104 tses <- liftIO $ Tracker.newSession exactTopic def
105 eses <- newExchangeSession rootPath (Left exactTopic)
106 eventStream <- liftIO newSendPort
107 return $ Handle
108 { handleTopic = exactTopic
109 , handlePrivate = False
110 , handleStatus = statusVar
111 , handleTrackers = tses
112 , handleExchange = eses
113 , handleEvents = eventStream
114 }
115
116-- | Stop torrent and destroy all sessions. You don't need to close
117-- handles at application exit, all handles will be automatically
118-- closed at 'Network.BitTorrent.Client.closeClient'. This operation
119-- may block.
120closeHandle :: Handle -> BitTorrent ()
121closeHandle h @ Handle {..} = do
122 freeHandle handleTopic $ do
123 Client {..} <- getClient
124 stop h
125 liftIO $ Exchange.closeSession handleExchange
126 liftIO $ Tracker.closeSession trackerManager handleTrackers
127
128{-----------------------------------------------------------------------
129-- Control
130-----------------------------------------------------------------------}
131
132modifyStatus :: HandleStatus -> Handle -> (HandleStatus -> BitTorrent ()) -> BitTorrent ()
133modifyStatus targetStatus Handle {..} targetAction = do
134 modifyMVar_ handleStatus $ \ actualStatus -> do
135 unless (actualStatus == targetStatus) $ do
136 targetAction actualStatus
137 return targetStatus
138 liftIO $ send handleEvents (StatusChanged targetStatus)
139
140-- | Start downloading, uploading and announcing this torrent.
141--
142-- This operation is blocking, use
143-- 'Control.Concurrent.Async.Lifted.async' if needed.
144start :: Handle -> BitTorrent ()
145start h @ Handle {..} = do
146 modifyStatus Types.Running h $ \ status -> do
147 case status of
148 Types.Running -> return ()
149 Types.Stopped -> do
150 Client {..} <- getClient
151 liftIO $ Tracker.notify trackerManager handleTrackers Tracker.Started
152 unless handlePrivate $ do
153 liftDHT $ DHT.insert handleTopic (error "start")
154 liftIO $ do
155 peers <- askPeers trackerManager handleTrackers
156 print $ "got: " ++ show (L.length peers) ++ " peers"
157 forM_ peers $ \ peer -> do
158 Exchange.connect peer handleExchange
159
160-- | Stop downloading this torrent.
161pause :: Handle -> BitTorrent ()
162pause _ = return ()
163
164-- | Stop downloading, uploading and announcing this torrent.
165stop :: Handle -> BitTorrent ()
166stop h @ Handle {..} = do
167 modifyStatus Types.Stopped h $ \ status -> do
168 case status of
169 Types.Stopped -> return ()
170 Types.Running -> do
171 Client {..} <- getClient
172 unless handlePrivate $ do
173 liftDHT $ DHT.delete handleTopic (error "stop")
174 liftIO $ Tracker.notify trackerManager handleTrackers Tracker.Stopped
175
176{-----------------------------------------------------------------------
177-- Query
178-----------------------------------------------------------------------}
179
180getHandle :: InfoHash -> BitTorrent Handle
181getHandle ih = do
182 mhandle <- lookupHandle ih
183 case mhandle of
184 Nothing -> error "should we throw some exception?"
185 Just h -> return h
186
187getStatus :: Handle -> IO HandleStatus
188getStatus Handle {..} = readMVar handleStatus
diff --git a/bittorrent/src/Network/BitTorrent/Client/Types.hs b/bittorrent/src/Network/BitTorrent/Client/Types.hs
new file mode 100644
index 00000000..e2ad858f
--- /dev/null
+++ b/bittorrent/src/Network/BitTorrent/Client/Types.hs
@@ -0,0 +1,163 @@
1{-# LANGUAGE CPP #-}
2{-# LANGUAGE FlexibleInstances #-}
3{-# LANGUAGE TypeFamilies #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6module Network.BitTorrent.Client.Types
7 ( -- * Core types
8 HandleStatus (..)
9 , Handle (..)
10 , Client (..)
11 , externalAddr
12
13 -- * Monad BitTorrent
14 , BitTorrent (..)
15 , runBitTorrent
16 , getClient
17
18 , MonadBitTorrent (..)
19
20 -- * Events
21 , Types.Event (..)
22 ) where
23
24import Control.Applicative
25import Control.Concurrent
26import Control.Concurrent.Chan.Split as CS
27import Control.Monad.Base
28import Control.Monad.Logger
29import Control.Monad.Reader
30import Control.Monad.Trans.Control
31import Control.Monad.Trans.Resource
32import Data.Function
33import Data.HashMap.Strict as HM
34import Data.Ord
35import Network
36import System.Log.FastLogger
37
38import Data.Torrent
39import Network.Address
40import Network.BitTorrent.Internal.Types as Types
41import Network.BitTorrent.DHT as DHT
42import Network.BitTorrent.Exchange as Exchange
43import Network.BitTorrent.Tracker as Tracker hiding (Event)
44
45data HandleStatus
46 = Running
47 | Stopped
48 deriving (Show, Eq)
49
50data Handle = Handle
51 { handleTopic :: !InfoHash
52 , handlePrivate :: !Bool
53
54 , handleStatus :: !(MVar HandleStatus)
55 , handleTrackers :: !Tracker.Session
56 , handleExchange :: !Exchange.Session
57 , handleEvents :: !(SendPort (Event Handle))
58 }
59
60instance EventSource Handle where
61 data Event Handle = StatusChanged HandleStatus
62 listen Handle {..} = CS.listen undefined
63
64data Client = Client
65 { clientPeerId :: !PeerId
66 , clientListenerPort :: !PortNumber
67 , allowedExtensions :: !Caps
68 , clientResources :: !InternalState
69 , trackerManager :: !Tracker.Manager
70 , exchangeManager :: !Exchange.Manager
71 , clientNode :: !(Node IPv4)
72 , clientTorrents :: !(MVar (HashMap InfoHash Handle))
73 , clientLogger :: !LogFun
74 , clientEvents :: !(SendPort (Event Client))
75 }
76
77instance Eq Client where
78 (==) = (==) `on` clientPeerId
79
80instance Ord Client where
81 compare = comparing clientPeerId
82
83instance EventSource Client where
84 data Event Client = TorrentAdded InfoHash
85 listen Client {..} = CS.listen clientEvents
86
87-- | External IP address of a host running a bittorrent client
88-- software may be used to acknowledge remote peer the host connected
89-- to. See 'Network.BitTorrent.Exchange.Message.ExtendedHandshake'.
90externalAddr :: Client -> PeerAddr (Maybe IP)
91externalAddr Client {..} = PeerAddr
92 { peerId = Just clientPeerId
93 , peerHost = Nothing -- TODO return external IP address, if known
94 , peerPort = clientListenerPort
95 }
96
97{-----------------------------------------------------------------------
98-- BitTorrent monad
99-----------------------------------------------------------------------}
100
101newtype BitTorrent a = BitTorrent
102 { unBitTorrent :: ReaderT Client IO a
103 } deriving ( Functor, Applicative, Monad
104 , MonadIO, MonadThrow, MonadBase IO
105 )
106
107class MonadBitTorrent m where
108 liftBT :: BitTorrent a -> m a
109
110#if MIN_VERSION_monad_control(1,0,0)
111newtype BTStM a = BTStM { unBTSt :: StM (ReaderT Client IO) a }
112
113instance MonadBaseControl IO BitTorrent where
114 type StM BitTorrent a = BTStM a
115 liftBaseWith cc = BitTorrent $ liftBaseWith $ \ cc' ->
116 cc $ \ (BitTorrent m) -> BTStM <$> cc' m
117 {-# INLINE liftBaseWith #-}
118
119 restoreM = BitTorrent . restoreM . unBTSt
120 {-# INLINE restoreM #-}
121#else
122instance MonadBaseControl IO BitTorrent where
123 newtype StM BitTorrent a = StM { unSt :: StM (ReaderT Client IO) a }
124 liftBaseWith cc = BitTorrent $ liftBaseWith $ \ cc' ->
125 cc $ \ (BitTorrent m) -> StM <$> cc' m
126 {-# INLINE liftBaseWith #-}
127
128 restoreM = BitTorrent . restoreM . unSt
129 {-# INLINE restoreM #-}
130#endif
131
132-- | NOP.
133instance MonadBitTorrent BitTorrent where
134 liftBT = id
135
136instance MonadTrans t => MonadBitTorrent (t BitTorrent) where
137 liftBT = lift
138
139-- | Registered but not closed manually resources will be
140-- automatically closed at 'Network.BitTorrent.Client.closeClient'
141instance MonadResource BitTorrent where
142 liftResourceT m = BitTorrent $ do
143 s <- asks clientResources
144 liftIO $ runInternalState m s
145
146-- | Run DHT operation, only if the client node is running.
147instance MonadDHT BitTorrent where
148 liftDHT action = BitTorrent $ do
149 node <- asks clientNode
150 liftIO $ runDHT node action
151
152instance MonadLogger BitTorrent where
153 monadLoggerLog loc src lvl msg = BitTorrent $ do
154 logger <- asks clientLogger
155 liftIO $ logger loc src lvl (toLogStr msg)
156
157runBitTorrent :: Client -> BitTorrent a -> IO a
158runBitTorrent client action = runReaderT (unBitTorrent action) client
159{-# INLINE runBitTorrent #-}
160
161getClient :: BitTorrent Client
162getClient = BitTorrent ask
163{-# INLINE getClient #-}