diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Network/BitTorrent/Client.hs | 107 |
1 files changed, 94 insertions, 13 deletions
diff --git a/src/Network/BitTorrent/Client.hs b/src/Network/BitTorrent/Client.hs index a6151857..74072706 100644 --- a/src/Network/BitTorrent/Client.hs +++ b/src/Network/BitTorrent/Client.hs | |||
@@ -1,22 +1,46 @@ | |||
1 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
1 | module Network.BitTorrent.Client | 2 | module Network.BitTorrent.Client |
2 | ( Options (..) | 3 | ( -- * Options |
4 | Options (..) | ||
5 | |||
6 | -- * Client session | ||
3 | , Client | 7 | , Client |
8 | |||
9 | -- ** Session data | ||
10 | , clientPeerId | ||
11 | , clientListenerPort | ||
12 | , allowedExtensions | ||
13 | |||
14 | -- ** Session initialization | ||
4 | , newClient | 15 | , newClient |
16 | |||
17 | -- * BitTorrent monad | ||
18 | , BitTorrent | ||
19 | , runBitTorrent | ||
20 | , MonadBitTorrent (..) | ||
21 | , getClient | ||
22 | |||
23 | -- * Operations | ||
5 | , addTorrent | 24 | , addTorrent |
6 | ) where | 25 | ) where |
7 | 26 | ||
8 | import Control.Concurrent.STM | 27 | import Control.Concurrent.STM |
28 | import Control.Monad.Logger | ||
29 | import Control.Monad.Reader | ||
30 | import Control.Monad.Trans.Resource | ||
9 | import Data.Default | 31 | import Data.Default |
10 | import Data.Function | 32 | import Data.Function |
11 | import Data.HashMap.Strict as HM | 33 | import Data.HashMap.Strict as HM |
12 | import Data.Ord | 34 | import Data.Ord |
13 | import Data.Text | 35 | import Data.Text |
14 | import Network | 36 | import Network |
37 | import System.Log.FastLogger | ||
15 | 38 | ||
16 | import Data.Torrent | 39 | import Data.Torrent |
17 | import Data.Torrent.InfoHash | 40 | import Data.Torrent.InfoHash |
18 | import Network.BitTorrent.Client.Swarm | 41 | import Network.BitTorrent.Client.Swarm |
19 | import Network.BitTorrent.Core | 42 | import Network.BitTorrent.Core |
43 | import Network.BitTorrent.DHT | ||
20 | import Network.BitTorrent.Exchange.Message | 44 | import Network.BitTorrent.Exchange.Message |
21 | 45 | ||
22 | 46 | ||
@@ -25,6 +49,8 @@ data Options = Options | |||
25 | , name :: Text | 49 | , name :: Text |
26 | , port :: PortNumber | 50 | , port :: PortNumber |
27 | , extensions :: [Extension] | 51 | , extensions :: [Extension] |
52 | , nodeAddr :: NodeAddr IPv4 | ||
53 | , bootNode :: NodeAddr IPv4 | ||
28 | } | 54 | } |
29 | 55 | ||
30 | instance Default Options where | 56 | instance Default Options where |
@@ -33,13 +59,17 @@ instance Default Options where | |||
33 | , name = "hs-bittorrent" | 59 | , name = "hs-bittorrent" |
34 | , port = 6882 | 60 | , port = 6882 |
35 | , extensions = [] | 61 | , extensions = [] |
62 | , nodeAddr = "0.0.0.0:6882" | ||
36 | } | 63 | } |
37 | 64 | ||
38 | data Client = Client | 65 | data Client = Client |
39 | { clientPeerId :: !PeerId | 66 | { clientPeerId :: !PeerId |
40 | , clientListenerPort :: !PortNumber | 67 | , clientListenerPort :: !PortNumber |
41 | , allowedExtensions :: !Caps | 68 | , allowedExtensions :: !Caps |
42 | , torrents :: TVar (HashMap InfoHash Swarm) | 69 | , clientNode :: !(Node IPv4) |
70 | , clientTorrents :: !(TVar (HashMap InfoHash Swarm)) | ||
71 | , clientLogger :: !LogFun | ||
72 | -- , trackerClient :: !(Manager) | ||
43 | } | 73 | } |
44 | 74 | ||
45 | instance Eq Client where | 75 | instance Eq Client where |
@@ -48,20 +78,71 @@ instance Eq Client where | |||
48 | instance Ord Client where | 78 | instance Ord Client where |
49 | compare = comparing clientPeerId | 79 | compare = comparing clientPeerId |
50 | 80 | ||
51 | newClient :: Options -> IO Client | 81 | newClient :: Options -> LogFun -> IO Client |
52 | newClient Options {..} = do | 82 | newClient Options {..} logger = do |
53 | pid <- genPeerId | 83 | pid <- genPeerId |
54 | ts <- newTVarIO HM.empty | 84 | ts <- newTVarIO HM.empty |
85 | node <- runResourceT $ do | ||
86 | node <- startNode handlers def nodeAddr logger | ||
87 | runDHT node $ bootstrap [bootNode] | ||
88 | return node | ||
89 | |||
55 | return Client | 90 | return Client |
56 | { clientPeerId = pid | 91 | { clientPeerId = pid |
57 | , clientListenerPort = port | 92 | , clientListenerPort = port |
58 | , allowedExtensions = toCaps extensions | 93 | , allowedExtensions = toCaps extensions |
59 | , torrents = ts | 94 | , clientTorrents = ts |
95 | , clientNode = node | ||
96 | , clientLogger = logger | ||
60 | } | 97 | } |
61 | 98 | ||
62 | addTorrent :: Torrent -> Client -> IO () | 99 | closeClient :: Client -> IO () |
63 | addTorrent t Client {..} = do | 100 | closeClient Client {..} = do |
64 | leecher <- newLeecher clientPeerId clientListenerPort t | 101 | return () |
65 | let ih = idInfoHash (tInfoDict t) | 102 | -- closeNode clientNode |
66 | atomically $ modifyTVar' torrents (HM.insert ih leecher) | 103 | |
67 | askPeers leecher >>= print \ No newline at end of file | 104 | {----------------------------------------------------------------------- |
105 | -- BitTorrent monad | ||
106 | -----------------------------------------------------------------------} | ||
107 | |||
108 | class MonadBitTorrent m where | ||
109 | liftBT :: BitTorrent a -> m a | ||
110 | |||
111 | newtype BitTorrent a = BitTorrent | ||
112 | { unBitTorrent :: ReaderT Client (ResourceT IO) a | ||
113 | } deriving (Monad, MonadIO) | ||
114 | |||
115 | instance MonadBitTorrent BitTorrent where | ||
116 | liftBT = id | ||
117 | |||
118 | instance MonadDHT BitTorrent where | ||
119 | liftDHT action = BitTorrent $ do | ||
120 | node <- asks clientNode | ||
121 | liftIO $ runResourceT $ runDHT node action | ||
122 | |||
123 | instance MonadLogger BitTorrent where | ||
124 | monadLoggerLog loc src lvl msg = BitTorrent $ do | ||
125 | logger <- asks clientLogger | ||
126 | liftIO $ logger loc src lvl (toLogStr msg) | ||
127 | |||
128 | runBitTorrent :: Client -> BitTorrent a -> IO a | ||
129 | runBitTorrent client action = runResourceT $ | ||
130 | runReaderT (unBitTorrent action) client | ||
131 | {-# INLINE runBitTorrent #-} | ||
132 | |||
133 | getClient :: BitTorrent Client | ||
134 | getClient = BitTorrent ask | ||
135 | |||
136 | {----------------------------------------------------------------------- | ||
137 | -- Operations | ||
138 | -----------------------------------------------------------------------} | ||
139 | -- All operations should be non blocking! | ||
140 | |||
141 | addTorrent :: Torrent -> BitTorrent () | ||
142 | addTorrent t = do | ||
143 | Client {..} <- getClient | ||
144 | liftIO $ do | ||
145 | leecher <- newLeecher clientPeerId clientListenerPort t | ||
146 | let ih = idInfoHash (tInfoDict t) | ||
147 | atomically $ modifyTVar' clientTorrents (HM.insert ih leecher) | ||
148 | askPeers leecher >>= print \ No newline at end of file | ||