summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent')
-rw-r--r--src/Network/BitTorrent/Client.hs137
-rw-r--r--src/Network/BitTorrent/Client/Handle.hs138
-rw-r--r--src/Network/BitTorrent/Client/Swarm.hs52
-rw-r--r--src/Network/BitTorrent/Client/Types.hs84
4 files changed, 266 insertions, 145 deletions
diff --git a/src/Network/BitTorrent/Client.hs b/src/Network/BitTorrent/Client.hs
index fd830239..d8c3ee91 100644
--- a/src/Network/BitTorrent/Client.hs
+++ b/src/Network/BitTorrent/Client.hs
@@ -1,4 +1,5 @@
1{-# LANGUAGE GeneralizedNewtypeDeriving #-} 1{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2{-# LANGUAGE TemplateHaskell #-}
2module Network.BitTorrent.Client 3module Network.BitTorrent.Client
3 ( -- * Options 4 ( -- * Options
4 Options (..) 5 Options (..)
@@ -15,142 +16,92 @@ module Network.BitTorrent.Client
15 , newClient 16 , newClient
16 , closeClient 17 , closeClient
17 , withClient 18 , withClient
19 , simpleClient
18 20
19 -- * BitTorrent monad 21 -- * BitTorrent monad
22 , MonadBitTorrent (..)
20 , BitTorrent 23 , BitTorrent
21 , runBitTorrent 24 , runBitTorrent
22 , MonadBitTorrent (..)
23 , getClient 25 , getClient
24 26
25 -- * Operations 27 -- * Handle
26 , addTorrent 28 , openTorrent
29 , openMagnet
30 , closeHandle
27 ) where 31 ) where
28 32
29import Control.Exception 33import Control.Exception
30import Control.Concurrent.STM 34import Control.Concurrent
31import Control.Monad.Logger
32import Control.Monad.Reader
33import Control.Monad.Trans.Resource 35import Control.Monad.Trans.Resource
36
34import Data.Default 37import Data.Default
35import Data.Function
36import Data.HashMap.Strict as HM 38import Data.HashMap.Strict as HM
37import Data.Maybe 39import Data.Maybe
38import Data.Ord
39import Data.Text 40import Data.Text
40import Network 41import Network
41import System.Log.FastLogger
42 42
43import Data.Torrent 43import Network.BitTorrent.Client.Types
44import Data.Torrent.InfoHash 44import Network.BitTorrent.Client.Handle
45import Network.BitTorrent.Client.Swarm
46import Network.BitTorrent.Core 45import Network.BitTorrent.Core
47import Network.BitTorrent.DHT 46import Network.BitTorrent.DHT
47import Network.BitTorrent.Tracker as Tracker hiding (Options)
48import Network.BitTorrent.Exchange.Message 48import Network.BitTorrent.Exchange.Message
49 49
50 50
51data Options = Options 51data Options = Options
52 { fingerprint :: Fingerprint 52 { optFingerprint :: Fingerprint
53 , name :: Text 53 , optName :: Text
54 , port :: PortNumber 54 , optPort :: PortNumber
55 , extensions :: [Extension] 55 , optExtensions :: [Extension]
56 , nodeAddr :: NodeAddr IPv4 56 , optNodeAddr :: NodeAddr IPv4
57 , bootNode :: Maybe (NodeAddr IPv4) 57 , optBootNode :: Maybe (NodeAddr IPv4)
58 } 58 }
59 59
60instance Default Options where 60instance Default Options where
61 def = Options 61 def = Options
62 { fingerprint = def 62 { optFingerprint = def
63 , name = "hs-bittorrent" 63 , optName = "hs-bittorrent"
64 , port = 6882 64 , optPort = 6882
65 , extensions = [] 65 , optExtensions = []
66 , nodeAddr = "0.0.0.0:6882" 66 , optNodeAddr = "0.0.0.0:6882"
67 , bootNode = Nothing 67 , optBootNode = Nothing
68 } 68 }
69 69
70data Client = Client
71 { clientPeerId :: !PeerId
72 , clientListenerPort :: !PortNumber
73 , allowedExtensions :: !Caps
74 , clientNode :: !(Node IPv4)
75 , clientTorrents :: !(TVar (HashMap InfoHash Swarm))
76 , clientLogger :: !LogFun
77-- , trackerClient :: !(Manager)
78 }
79
80instance Eq Client where
81 (==) = (==) `on` clientPeerId
82
83instance Ord Client where
84 compare = comparing clientPeerId
85
86newClient :: Options -> LogFun -> IO Client 70newClient :: Options -> LogFun -> IO Client
87newClient Options {..} logger = do 71newClient Options {..} logger = do
88 pid <- genPeerId 72 pid <- genPeerId
89 ts <- newTVarIO HM.empty 73 ts <- newMVar HM.empty
74 let peerInfo = PeerInfo pid Nothing optPort
75 mgr <- Tracker.newManager def peerInfo
90 node <- runResourceT $ do 76 node <- runResourceT $ do
91 node <- startNode handlers def nodeAddr logger 77 node <- startNode handlers def optNodeAddr logger
92 runDHT node $ bootstrap (maybeToList bootNode) 78 runDHT node $ bootstrap (maybeToList optBootNode)
93 return node 79 return node
94 80
95 return Client 81 return Client
96 { clientPeerId = pid 82 { clientPeerId = pid
97 , clientListenerPort = port 83 , clientListenerPort = optPort
98 , allowedExtensions = toCaps extensions 84 , allowedExtensions = toCaps optExtensions
99 , clientTorrents = ts 85 , trackerManager = mgr
100 , clientNode = node 86 , clientNode = node
87 , clientTorrents = ts
101 , clientLogger = logger 88 , clientLogger = logger
102 } 89 }
103 90
104closeClient :: Client -> IO () 91closeClient :: Client -> IO ()
105closeClient Client {..} = do 92closeClient Client {..} = do
93 Tracker.closeManager trackerManager
106 return () 94 return ()
107-- closeNode clientNode 95-- closeNode clientNode
108 96
109withClient :: Options -> LogFun -> (Client -> IO a) -> IO a 97withClient :: Options -> LogFun -> (Client -> IO a) -> IO a
110withClient opts log action = bracket (newClient opts log) closeClient action 98withClient opts lf action = bracket (newClient opts lf) closeClient action
111 99
112{----------------------------------------------------------------------- 100-- | Run bittorrent client with default options and log to @stderr@.
113-- BitTorrent monad 101--
114-----------------------------------------------------------------------} 102-- For testing purposes only.
115 103--
116class MonadBitTorrent m where 104simpleClient :: BitTorrent () -> IO ()
117 liftBT :: BitTorrent a -> m a 105simpleClient m = withClient def logger (`runBitTorrent` m)
118 106 where
119newtype BitTorrent a = BitTorrent 107 logger _ _ _ _ = return () \ No newline at end of file
120 { unBitTorrent :: ReaderT Client (ResourceT IO) a
121 } deriving (Monad, MonadIO)
122
123instance MonadBitTorrent BitTorrent where
124 liftBT = id
125
126instance MonadDHT BitTorrent where
127 liftDHT action = BitTorrent $ do
128 node <- asks clientNode
129 liftIO $ runResourceT $ runDHT node action
130
131instance MonadLogger BitTorrent where
132 monadLoggerLog loc src lvl msg = BitTorrent $ do
133 logger <- asks clientLogger
134 liftIO $ logger loc src lvl (toLogStr msg)
135
136runBitTorrent :: Client -> BitTorrent a -> IO a
137runBitTorrent client action = runResourceT $
138 runReaderT (unBitTorrent action) client
139{-# INLINE runBitTorrent #-}
140
141getClient :: BitTorrent Client
142getClient = BitTorrent ask
143
144{-----------------------------------------------------------------------
145-- Operations
146-----------------------------------------------------------------------}
147-- All operations should be non blocking!
148
149addTorrent :: Torrent -> BitTorrent ()
150addTorrent t = do
151 Client {..} <- getClient
152 liftIO $ do
153 leecher <- newLeecher clientPeerId clientListenerPort t
154 let ih = idInfoHash (tInfoDict t)
155 atomically $ modifyTVar' clientTorrents (HM.insert ih leecher)
156 askPeers leecher >>= print \ No newline at end of file
diff --git a/src/Network/BitTorrent/Client/Handle.hs b/src/Network/BitTorrent/Client/Handle.hs
new file mode 100644
index 00000000..467d5745
--- /dev/null
+++ b/src/Network/BitTorrent/Client/Handle.hs
@@ -0,0 +1,138 @@
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 , HandleState
18 , getState
19 ) where
20
21import Control.Applicative
22import Control.Concurrent
23import Control.Monad
24import Control.Monad.Trans
25import Data.HashMap.Strict as HM
26
27import Data.Torrent
28import Data.Torrent.InfoHash
29import Data.Torrent.Magnet
30import Network.BitTorrent.Client.Types
31import Network.BitTorrent.DHT as DHT
32import Network.BitTorrent.Tracker as Tracker
33
34{-----------------------------------------------------------------------
35-- Safe handle set manupulation
36-----------------------------------------------------------------------}
37
38-- | Guarantees that we newer allocate the same handle twice.
39allocHandle :: InfoHash -> BitTorrent Handle -> BitTorrent Handle
40allocHandle ih m = do
41 c @ Client {..} <- getClient
42 liftIO $ modifyMVar clientTorrents $ \ handles -> do
43 case HM.lookup ih handles of
44 Just h -> return (handles, h)
45 Nothing -> do
46 h <- runBitTorrent c m
47 return (HM.insert ih h handles, h)
48
49-- |
50freeHandle :: InfoHash -> BitTorrent () -> BitTorrent ()
51freeHandle ih finalizer = do
52 c @ Client {..} <- getClient
53 liftIO $ modifyMVar_ clientTorrents $ \ handles -> do
54 case HM.lookup ih handles of
55 Nothing -> return handles
56 Just _ -> do
57 runBitTorrent c finalizer
58 return (HM.delete ih handles)
59
60-- |
61lookupHandle :: InfoHash -> BitTorrent (Maybe Handle)
62lookupHandle ih = do
63 Client {..} <- getClient
64 handles <- liftIO $ readMVar clientTorrents
65 return (HM.lookup ih handles)
66
67{-----------------------------------------------------------------------
68-- Initialization
69-----------------------------------------------------------------------}
70
71-- | Open a torrent in 'stop'ed state. Use 'nullTorrent' to open
72-- handle from 'InfoDict'. This operation do not block.
73openTorrent :: Torrent -> BitTorrent Handle
74openTorrent t @ Torrent {..} = do
75 let ih = idInfoHash tInfoDict
76 allocHandle ih $ do
77 ses <- liftIO (Tracker.newSession ih (trackerList t))
78 return $ Handle ih (idPrivate tInfoDict) ses
79
80-- | Use 'nullMagnet' to open handle from 'InfoHash'.
81openMagnet :: Magnet -> BitTorrent Handle
82openMagnet = undefined
83
84-- | Stop torrent and destroy all sessions. You don't need to close
85-- handles at application exit, all handles will be automatically
86-- closed at 'Network.BitTorrent.Client.closeClient'. This operation
87-- may block.
88closeHandle :: Handle -> BitTorrent ()
89closeHandle h @ Handle {..} = do
90 freeHandle topic $ do
91 stop h
92 liftIO $ Tracker.closeSession trackers
93
94{-----------------------------------------------------------------------
95-- Control
96-----------------------------------------------------------------------}
97
98-- | Start downloading, uploading and announcing this torrent.
99--
100-- This operation is blocking, use
101-- 'Control.Concurrent.Async.Lifted.async' if needed.
102start :: Handle -> BitTorrent ()
103start Handle {..} = do
104 Client {..} <- getClient
105 liftIO $ Tracker.notify trackerManager trackers Tracker.Started
106 unless private $ do
107 liftDHT $ DHT.insert topic undefined
108
109-- | Stop downloading this torrent.
110pause :: Handle -> BitTorrent ()
111pause _ = return ()
112
113-- | Stop downloading, uploading and announcing this torrent.
114stop :: Handle -> BitTorrent ()
115stop Handle {..} = do
116 Client {..} <- getClient
117 unless private $ do
118 liftDHT $ DHT.delete topic undefined
119 liftIO $ Tracker.notify trackerManager trackers Tracker.Stopped
120
121{-----------------------------------------------------------------------
122-- Query
123-----------------------------------------------------------------------}
124
125data HandleState
126 = Running
127 | Paused
128 | Stopped
129
130getHandle :: InfoHash -> BitTorrent Handle
131getHandle ih = do
132 mhandle <- lookupHandle ih
133 case mhandle of
134 Nothing -> error "should we throw some exception?"
135 Just h -> return h
136
137getState :: Handle -> IO HandleState
138getState = undefined \ No newline at end of file
diff --git a/src/Network/BitTorrent/Client/Swarm.hs b/src/Network/BitTorrent/Client/Swarm.hs
deleted file mode 100644
index bd48f8a4..00000000
--- a/src/Network/BitTorrent/Client/Swarm.hs
+++ /dev/null
@@ -1,52 +0,0 @@
1module Network.BitTorrent.Client.Swarm
2 ( Swarm
3 , newLeecher
4 , askPeers
5 ) where
6
7import Data.Default
8import Data.Maybe
9import Network
10
11import Data.Torrent
12import Data.Torrent.InfoHash
13import Network.BitTorrent.Core
14import Network.BitTorrent.Tracker.Message
15import Network.BitTorrent.Tracker.RPC as RPC
16
17
18data Swarm = Swarm
19 { swarmTopic :: InfoHash
20 , thisPeerId :: PeerId
21 , listenerPort :: PortNumber
22 }
23
24newLeecher :: PeerId -> PortNumber -> Torrent -> IO Swarm
25newLeecher pid port Torrent {..} = do
26 return Swarm
27 { swarmTopic = idInfoHash tInfoDict
28 , thisPeerId = pid
29 , listenerPort = port
30 }
31
32getAnnounceQuery :: Swarm -> AnnounceQuery
33getAnnounceQuery Swarm {..} = AnnounceQuery
34 { reqInfoHash = swarmTopic
35 , reqPeerId = thisPeerId
36 , reqPort = listenerPort
37 , reqProgress = def
38 , reqIP = Nothing
39 , reqNumWant = Nothing
40 , reqEvent = Nothing
41 }
42
43askPeers :: Swarm -> IO [PeerAddr IP]
44askPeers s @ Swarm {..} = do
45-- AnnounceInfo {..} <- RPC.announce (getAnnounceQuery s) trackerConn
46 return [] -- (getPeerList respPeers)
47
48--reannounce :: HTracker -> IO ()
49--reannounce = undefined
50
51--forceReannounce :: HTracker -> IO ()
52--forceReannounce = undefined
diff --git a/src/Network/BitTorrent/Client/Types.hs b/src/Network/BitTorrent/Client/Types.hs
new file mode 100644
index 00000000..0da24dc2
--- /dev/null
+++ b/src/Network/BitTorrent/Client/Types.hs
@@ -0,0 +1,84 @@
1{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2module Network.BitTorrent.Client.Types
3 ( -- * Core types
4 Handle (..)
5 , Client (..)
6
7 -- * Monad BitTorrent
8 , BitTorrent (..)
9 , runBitTorrent
10 , getClient
11
12 , MonadBitTorrent (..)
13 ) where
14
15import Control.Concurrent
16import Control.Monad.Logger
17import Control.Monad.Reader
18import Control.Monad.Trans.Resource
19import Data.Function
20import Data.HashMap.Strict as HM
21import Data.Ord
22import Network
23import System.Log.FastLogger
24
25import Data.Torrent.InfoHash
26import Network.BitTorrent.Core
27import Network.BitTorrent.DHT as DHT
28import Network.BitTorrent.Tracker as Tracker
29import Network.BitTorrent.Exchange.Message
30
31
32data Handle = Handle
33 { topic :: !InfoHash
34 , private :: !Bool
35 , trackers :: !Tracker.Session
36 }
37
38data Client = Client
39 { clientPeerId :: !PeerId
40 , clientListenerPort :: !PortNumber
41 , allowedExtensions :: !Caps
42 , trackerManager :: !Tracker.Manager
43 , clientNode :: !(Node IPv4)
44 , clientTorrents :: !(MVar (HashMap InfoHash Handle))
45 , clientLogger :: !LogFun
46 }
47
48instance Eq Client where
49 (==) = (==) `on` clientPeerId
50
51instance Ord Client where
52 compare = comparing clientPeerId
53
54{-----------------------------------------------------------------------
55-- BitTorrent monad
56-----------------------------------------------------------------------}
57
58newtype BitTorrent a = BitTorrent
59 { unBitTorrent :: ReaderT Client (ResourceT IO) a
60 } deriving (Functor, Monad, MonadIO)
61
62class MonadBitTorrent m where
63 liftBT :: BitTorrent a -> m a
64
65instance MonadBitTorrent BitTorrent where
66 liftBT = id
67
68instance MonadDHT BitTorrent where
69 liftDHT action = BitTorrent $ do
70 node <- asks clientNode
71 liftIO $ runResourceT $ runDHT node action
72
73instance MonadLogger BitTorrent where
74 monadLoggerLog loc src lvl msg = BitTorrent $ do
75 logger <- asks clientLogger
76 liftIO $ logger loc src lvl (toLogStr msg)
77
78runBitTorrent :: Client -> BitTorrent a -> IO a
79runBitTorrent client action = runResourceT $
80 runReaderT (unBitTorrent action) client
81{-# INLINE runBitTorrent #-}
82
83getClient :: BitTorrent Client
84getClient = BitTorrent ask