summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Client.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/Client.hs')
-rw-r--r--src/Network/BitTorrent/Client.hs137
1 files changed, 44 insertions, 93 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